| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Potato.Flow.Types
Synopsis
- type REltIdMap a = IntMap a
 - type ControllersWithId = IntMap Controller
 - controllerWithId_isParams :: ControllersWithId -> Bool
 - type AttachmentMap = REltIdMap IntSet
 - type LayerPos = Int
 - type SuperSEltLabel = (REltId, LayerPos, SEltLabel)
 - type SEltLabelChanges = REltIdMap (Maybe SEltLabel)
 - type SEltLabelChangesWithLayerPos = REltIdMap (Maybe (LayerPos, SEltLabel))
 - type LayerPosMap = REltIdMap LayerPos
 - data CRename = CRename {}
 - data CLine = CLine {}
 - data CBoxText = CBoxText {}
 - data CBoxType = CBoxType (SBoxType, SBoxType)
 - data CBoundingBox = CBoundingBox {}
 - data CTag a where
- CTagRename :: CTag CRename
 - CTagLine :: CTag CLine
 - CTagBoxText :: CTag CBoxText
 - CTagBoxType :: CTag CBoxType
 - CTagBoxTextStyle :: CTag CTextStyle
 - CTagBoxLabelAlignment :: CTag CTextAlign
 - CTagBoxLabelText :: CTag CMaybeText
 - CTagTextArea :: CTag CTextArea
 - CTagTextAreaToggle :: CTag CTextAreaToggle
 - CTagSuperStyle :: CTag CSuperStyle
 - CTagLineStyle :: CTag CLineStyle
 - CTagBoundingBox :: CTag CBoundingBox
 
 - data CTextStyle = CTextStyle DeltaTextStyle
 - data CSuperStyle = CSuperStyle DeltaSuperStyle
 - data CLineStyle = CLineStyle DeltaLineStyle
 - data CTextAlign = CTextAlign DeltaTextAlign
 - data CMaybeText = CMaybeText DeltaMaybeText
 - data CTextArea = CTextArea DeltaTextArea
 - data CTextAreaToggle = CTextAreaToggle DeltaTextAreaToggle
 - type Controller = DSum CTag Identity
 - type DeltaText = (Text, Text)
 - data DeltaSuperStyle = DeltaSuperStyle (SuperStyle, SuperStyle)
 - data DeltaLineStyle = DeltaLineStyle (LineStyle, LineStyle)
 - data DeltaTextStyle = DeltaTextStyle (TextStyle, TextStyle)
 - data DeltaTextAlign = DeltaTextAlign (TextAlign, TextAlign)
 - data DeltaMaybeText = DeltaMaybeText (Maybe Text, Maybe Text)
 - data DeltaTextArea = DeltaTextArea (Map XY (Maybe PChar, Maybe PChar))
 - data DeltaTextAreaToggle = DeltaTextAreaToggle SElt
 - type SEltTree = [(REltId, SEltLabel)]
 - data SCanvas = SCanvas {
- _sCanvas_box :: LBox
 
 - data SPotatoFlow = SPotatoFlow {}
 
Documentation
type ControllersWithId = IntMap Controller Source #
indexed my REltId
type AttachmentMap = REltIdMap IntSet Source #
type LayerPosMap = REltIdMap LayerPos Source #
controllers
Constructors
| CRename | |
Fields  | |
Constructors
| CLine | |
Instances
| Generic CLine Source # | |
| Show CLine Source # | |
| Default CLine Source # | |
Defined in Potato.Flow.Types  | |
| NFData CLine Source # | |
Defined in Potato.Flow.Types  | |
| Eq CLine Source # | |
| Delta SAutoLine CLine Source # | |
| type Rep CLine Source # | |
Defined in Potato.Flow.Types type Rep CLine = D1 ('MetaData "CLine" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "CLine" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_cLine_deltaStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DeltaXY)) :*: S1 ('MetaSel ('Just "_cLine_deltaEnd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DeltaXY))) :*: (S1 ('MetaSel ('Just "_cLine_deltaAttachStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Maybe Attachment, Maybe Attachment))) :*: S1 ('MetaSel ('Just "_cLine_deltaAttachEnd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Maybe Attachment, Maybe Attachment))))))  | |
Constructors
| CBoxText | |
Fields  | |
data CBoundingBox Source #
Constructors
| CBoundingBox | |
Fields  | |
Instances
| Generic CBoundingBox Source # | |
Defined in Potato.Flow.Types Associated Types type Rep CBoundingBox :: Type -> Type #  | |
| Show CBoundingBox Source # | |
Defined in Potato.Flow.Types Methods showsPrec :: Int -> CBoundingBox -> ShowS # show :: CBoundingBox -> String # showList :: [CBoundingBox] -> ShowS #  | |
| NFData CBoundingBox Source # | |
Defined in Potato.Flow.Types Methods rnf :: CBoundingBox -> () #  | |
| Eq CBoundingBox Source # | |
Defined in Potato.Flow.Types  | |
| type Rep CBoundingBox Source # | |
Defined in Potato.Flow.Types type Rep CBoundingBox = D1 ('MetaData "CBoundingBox" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "CBoundingBox" 'PrefixI 'True) (S1 ('MetaSel ('Just "_cBoundingBox_deltaBox") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DeltaLBox)))  | |
Constructors
Instances
| NFData Controller Source # | |
Defined in Potato.Flow.Types Methods rnf :: Controller -> () #  | |
| GCompare CTag Source # | |
| GEq CTag Source # | |
| GShow CTag Source # | |
Defined in Potato.Flow.Types Methods gshowsPrec :: forall (a :: k). Int -> CTag a -> ShowS #  | |
| (c CRename, c CLine, c CBoxText, c CBoxType, c CTextStyle, c CTextAlign, c CMaybeText, c CTextArea, c CTextAreaToggle, c CSuperStyle, c CLineStyle, c CBoundingBox) => Has (c :: Type -> Constraint) CTag Source # | |
data CTextStyle Source #
Constructors
| CTextStyle DeltaTextStyle | 
Instances
| Generic CTextStyle Source # | |
Defined in Potato.Flow.Types Associated Types type Rep CTextStyle :: Type -> Type #  | |
| Show CTextStyle Source # | |
Defined in Potato.Flow.Types Methods showsPrec :: Int -> CTextStyle -> ShowS # show :: CTextStyle -> String # showList :: [CTextStyle] -> ShowS #  | |
| NFData CTextStyle Source # | |
Defined in Potato.Flow.Types Methods rnf :: CTextStyle -> () #  | |
| Eq CTextStyle Source # | |
Defined in Potato.Flow.Types  | |
| type Rep CTextStyle Source # | |
Defined in Potato.Flow.Types type Rep CTextStyle = D1 ('MetaData "CTextStyle" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "CTextStyle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DeltaTextStyle)))  | |
data CSuperStyle Source #
Constructors
| CSuperStyle DeltaSuperStyle | 
Instances
| Generic CSuperStyle Source # | |
Defined in Potato.Flow.Types Associated Types type Rep CSuperStyle :: Type -> Type #  | |
| Show CSuperStyle Source # | |
Defined in Potato.Flow.Types Methods showsPrec :: Int -> CSuperStyle -> ShowS # show :: CSuperStyle -> String # showList :: [CSuperStyle] -> ShowS #  | |
| NFData CSuperStyle Source # | |
Defined in Potato.Flow.Types Methods rnf :: CSuperStyle -> () #  | |
| Eq CSuperStyle Source # | |
Defined in Potato.Flow.Types  | |
| type Rep CSuperStyle Source # | |
Defined in Potato.Flow.Types type Rep CSuperStyle = D1 ('MetaData "CSuperStyle" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "CSuperStyle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DeltaSuperStyle)))  | |
data CLineStyle Source #
Constructors
| CLineStyle DeltaLineStyle | 
Instances
| Generic CLineStyle Source # | |
Defined in Potato.Flow.Types Associated Types type Rep CLineStyle :: Type -> Type #  | |
| Show CLineStyle Source # | |
Defined in Potato.Flow.Types Methods showsPrec :: Int -> CLineStyle -> ShowS # show :: CLineStyle -> String # showList :: [CLineStyle] -> ShowS #  | |
| NFData CLineStyle Source # | |
Defined in Potato.Flow.Types Methods rnf :: CLineStyle -> () #  | |
| Eq CLineStyle Source # | |
Defined in Potato.Flow.Types  | |
| type Rep CLineStyle Source # | |
Defined in Potato.Flow.Types type Rep CLineStyle = D1 ('MetaData "CLineStyle" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "CLineStyle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DeltaLineStyle)))  | |
data CTextAlign Source #
Constructors
| CTextAlign DeltaTextAlign | 
Instances
| Generic CTextAlign Source # | |
Defined in Potato.Flow.Types Associated Types type Rep CTextAlign :: Type -> Type #  | |
| Show CTextAlign Source # | |
Defined in Potato.Flow.Types Methods showsPrec :: Int -> CTextAlign -> ShowS # show :: CTextAlign -> String # showList :: [CTextAlign] -> ShowS #  | |
| NFData CTextAlign Source # | |
Defined in Potato.Flow.Types Methods rnf :: CTextAlign -> () #  | |
| Eq CTextAlign Source # | |
Defined in Potato.Flow.Types  | |
| type Rep CTextAlign Source # | |
Defined in Potato.Flow.Types type Rep CTextAlign = D1 ('MetaData "CTextAlign" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "CTextAlign" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DeltaTextAlign)))  | |
data CMaybeText Source #
Constructors
| CMaybeText DeltaMaybeText | 
Instances
| Generic CMaybeText Source # | |
Defined in Potato.Flow.Types Associated Types type Rep CMaybeText :: Type -> Type #  | |
| Show CMaybeText Source # | |
Defined in Potato.Flow.Types Methods showsPrec :: Int -> CMaybeText -> ShowS # show :: CMaybeText -> String # showList :: [CMaybeText] -> ShowS #  | |
| NFData CMaybeText Source # | |
Defined in Potato.Flow.Types Methods rnf :: CMaybeText -> () #  | |
| Eq CMaybeText Source # | |
Defined in Potato.Flow.Types  | |
| type Rep CMaybeText Source # | |
Defined in Potato.Flow.Types type Rep CMaybeText = D1 ('MetaData "CMaybeText" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "CMaybeText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DeltaMaybeText)))  | |
Constructors
| CTextArea DeltaTextArea | 
Instances
| Generic CTextArea Source # | |
| Show CTextArea Source # | |
| NFData CTextArea Source # | |
Defined in Potato.Flow.Types  | |
| Eq CTextArea Source # | |
| type Rep CTextArea Source # | |
Defined in Potato.Flow.Types type Rep CTextArea = D1 ('MetaData "CTextArea" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "CTextArea" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DeltaTextArea)))  | |
data CTextAreaToggle Source #
Constructors
| CTextAreaToggle DeltaTextAreaToggle | 
Instances
delta types
data DeltaSuperStyle Source #
Constructors
| DeltaSuperStyle (SuperStyle, SuperStyle) | 
Instances
data DeltaLineStyle Source #
Constructors
| DeltaLineStyle (LineStyle, LineStyle) | 
Instances
data DeltaTextStyle Source #
Constructors
| DeltaTextStyle (TextStyle, TextStyle) | 
Instances
data DeltaTextAlign Source #
Constructors
| DeltaTextAlign (TextAlign, TextAlign) | 
Instances
data DeltaMaybeText Source #
Constructors
| DeltaMaybeText (Maybe Text, Maybe Text) | 
Instances
data DeltaTextArea Source #
Instances
data DeltaTextAreaToggle Source #
Constructors
| DeltaTextAreaToggle SElt | 
Instances
serialized types
Constructors
| SCanvas | |
Fields 
  | |
data SPotatoFlow Source #
Constructors
| SPotatoFlow | |
Fields  | |