tinytools-0.1.0.0
Safe HaskellSafe-Inferred
LanguageHaskell2010

Potato.Flow.Types

Synopsis

Documentation

type ControllersWithId = IntMap Controller Source #

indexed my REltId

controllers

data CRename Source #

Constructors

CRename 

Instances

Instances details
Generic CRename Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep CRename :: Type -> Type #

Methods

from :: CRename -> Rep CRename x #

to :: Rep CRename x -> CRename #

Show CRename Source # 
Instance details

Defined in Potato.Flow.Types

NFData CRename Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: CRename -> () #

Eq CRename Source # 
Instance details

Defined in Potato.Flow.Types

Methods

(==) :: CRename -> CRename -> Bool #

(/=) :: CRename -> CRename -> Bool #

Delta SEltLabel CRename Source # 
Instance details

Defined in Potato.Flow.Types

type Rep CRename Source # 
Instance details

Defined in Potato.Flow.Types

type Rep CRename = D1 ('MetaData "CRename" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "CRename" 'PrefixI 'True) (S1 ('MetaSel ('Just "_cRename_deltaLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DeltaText)))

data CLine Source #

Instances

Instances details
Generic CLine Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep CLine :: Type -> Type #

Methods

from :: CLine -> Rep CLine x #

to :: Rep CLine x -> CLine #

Show CLine Source # 
Instance details

Defined in Potato.Flow.Types

Methods

showsPrec :: Int -> CLine -> ShowS #

show :: CLine -> String #

showList :: [CLine] -> ShowS #

Default CLine Source # 
Instance details

Defined in Potato.Flow.Types

Methods

def :: CLine #

NFData CLine Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: CLine -> () #

Eq CLine Source # 
Instance details

Defined in Potato.Flow.Types

Methods

(==) :: CLine -> CLine -> Bool #

(/=) :: CLine -> CLine -> Bool #

Delta SAutoLine CLine Source # 
Instance details

Defined in Potato.Flow.Types

type Rep CLine Source # 
Instance details

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))))))

data CBoxText Source #

Constructors

CBoxText 

Instances

Instances details
Generic CBoxText Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep CBoxText :: Type -> Type #

Methods

from :: CBoxText -> Rep CBoxText x #

to :: Rep CBoxText x -> CBoxText #

Show CBoxText Source # 
Instance details

Defined in Potato.Flow.Types

NFData CBoxText Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: CBoxText -> () #

Eq CBoxText Source # 
Instance details

Defined in Potato.Flow.Types

Delta SBox CBoxText Source # 
Instance details

Defined in Potato.Flow.Types

Delta SBoxText CBoxText Source # 
Instance details

Defined in Potato.Flow.Types

type Rep CBoxText Source # 
Instance details

Defined in Potato.Flow.Types

type Rep CBoxText = D1 ('MetaData "CBoxText" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "CBoxText" 'PrefixI 'True) (S1 ('MetaSel ('Just "_cBoxText_deltaText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DeltaText)))

data CBoxType Source #

Constructors

CBoxType (SBoxType, SBoxType) 

Instances

Instances details
Generic CBoxType Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep CBoxType :: Type -> Type #

Methods

from :: CBoxType -> Rep CBoxType x #

to :: Rep CBoxType x -> CBoxType #

Show CBoxType Source # 
Instance details

Defined in Potato.Flow.Types

NFData CBoxType Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: CBoxType -> () #

Eq CBoxType Source # 
Instance details

Defined in Potato.Flow.Types

Delta SBox CBoxType Source # 
Instance details

Defined in Potato.Flow.Types

type Rep CBoxType Source # 
Instance details

Defined in Potato.Flow.Types

type Rep CBoxType = D1 ('MetaData "CBoxType" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "CBoxType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SBoxType, SBoxType))))

data CBoundingBox Source #

Instances

Instances details
Generic CBoundingBox Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep CBoundingBox :: Type -> Type #

Show CBoundingBox Source # 
Instance details

Defined in Potato.Flow.Types

NFData CBoundingBox Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: CBoundingBox -> () #

Eq CBoundingBox Source # 
Instance details

Defined in Potato.Flow.Types

type Rep CBoundingBox Source # 
Instance details

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)))

data CTag a where Source #

Instances

Instances details
NFData Controller Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: Controller -> () #

GCompare CTag Source # 
Instance details

Defined in Potato.Flow.Types

Methods

gcompare :: forall (a :: k) (b :: k). CTag a -> CTag b -> GOrdering a b #

GEq CTag Source # 
Instance details

Defined in Potato.Flow.Types

Methods

geq :: forall (a :: k) (b :: k). CTag a -> CTag b -> Maybe (a :~: b) #

GShow CTag Source # 
Instance details

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 # 
Instance details

Defined in Potato.Flow.Types

Methods

has :: forall (a :: k) r. CTag a -> (c a => r) -> r #

argDict :: forall (a :: k). CTag a -> Dict (c a) #

data CTextStyle Source #

Instances

Instances details
Generic CTextStyle Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep CTextStyle :: Type -> Type #

Show CTextStyle Source # 
Instance details

Defined in Potato.Flow.Types

NFData CTextStyle Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: CTextStyle -> () #

Eq CTextStyle Source # 
Instance details

Defined in Potato.Flow.Types

type Rep CTextStyle Source # 
Instance details

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 #

Instances

Instances details
Generic CSuperStyle Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep CSuperStyle :: Type -> Type #

Show CSuperStyle Source # 
Instance details

Defined in Potato.Flow.Types

NFData CSuperStyle Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: CSuperStyle -> () #

Eq CSuperStyle Source # 
Instance details

Defined in Potato.Flow.Types

type Rep CSuperStyle Source # 
Instance details

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 #

Instances

Instances details
Generic CLineStyle Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep CLineStyle :: Type -> Type #

Show CLineStyle Source # 
Instance details

Defined in Potato.Flow.Types

NFData CLineStyle Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: CLineStyle -> () #

Eq CLineStyle Source # 
Instance details

Defined in Potato.Flow.Types

type Rep CLineStyle Source # 
Instance details

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 #

Instances

Instances details
Generic CTextAlign Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep CTextAlign :: Type -> Type #

Show CTextAlign Source # 
Instance details

Defined in Potato.Flow.Types

NFData CTextAlign Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: CTextAlign -> () #

Eq CTextAlign Source # 
Instance details

Defined in Potato.Flow.Types

type Rep CTextAlign Source # 
Instance details

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 #

Instances

Instances details
Generic CMaybeText Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep CMaybeText :: Type -> Type #

Show CMaybeText Source # 
Instance details

Defined in Potato.Flow.Types

NFData CMaybeText Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: CMaybeText -> () #

Eq CMaybeText Source # 
Instance details

Defined in Potato.Flow.Types

type Rep CMaybeText Source # 
Instance details

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)))

data CTextArea Source #

Constructors

CTextArea DeltaTextArea 

Instances

Instances details
Generic CTextArea Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep CTextArea :: Type -> Type #

Show CTextArea Source # 
Instance details

Defined in Potato.Flow.Types

NFData CTextArea Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: CTextArea -> () #

Eq CTextArea Source # 
Instance details

Defined in Potato.Flow.Types

type Rep CTextArea Source # 
Instance details

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 #

Instances

Instances details
Generic CTextAreaToggle Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep CTextAreaToggle :: Type -> Type #

Show CTextAreaToggle Source # 
Instance details

Defined in Potato.Flow.Types

NFData CTextAreaToggle Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: CTextAreaToggle -> () #

Eq CTextAreaToggle Source # 
Instance details

Defined in Potato.Flow.Types

type Rep CTextAreaToggle Source # 
Instance details

Defined in Potato.Flow.Types

type Rep CTextAreaToggle = D1 ('MetaData "CTextAreaToggle" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "CTextAreaToggle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DeltaTextAreaToggle)))

type Controller = DSum CTag Identity Source #

Controllers represent changes to SElts

delta types

type DeltaText = (Text, Text) Source #

(old text, new text)

data DeltaSuperStyle Source #

Instances

Instances details
Generic DeltaSuperStyle Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep DeltaSuperStyle :: Type -> Type #

Show DeltaSuperStyle Source # 
Instance details

Defined in Potato.Flow.Types

NFData DeltaSuperStyle Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: DeltaSuperStyle -> () #

Eq DeltaSuperStyle Source # 
Instance details

Defined in Potato.Flow.Types

Delta SuperStyle DeltaSuperStyle Source # 
Instance details

Defined in Potato.Flow.Types

type Rep DeltaSuperStyle Source # 
Instance details

Defined in Potato.Flow.Types

type Rep DeltaSuperStyle = D1 ('MetaData "DeltaSuperStyle" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "DeltaSuperStyle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SuperStyle, SuperStyle))))

data DeltaLineStyle Source #

Instances

Instances details
Generic DeltaLineStyle Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep DeltaLineStyle :: Type -> Type #

Show DeltaLineStyle Source # 
Instance details

Defined in Potato.Flow.Types

NFData DeltaLineStyle Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: DeltaLineStyle -> () #

Eq DeltaLineStyle Source # 
Instance details

Defined in Potato.Flow.Types

Delta LineStyle DeltaLineStyle Source # 
Instance details

Defined in Potato.Flow.Types

type Rep DeltaLineStyle Source # 
Instance details

Defined in Potato.Flow.Types

type Rep DeltaLineStyle = D1 ('MetaData "DeltaLineStyle" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "DeltaLineStyle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LineStyle, LineStyle))))

data DeltaTextStyle Source #

Instances

Instances details
Generic DeltaTextStyle Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep DeltaTextStyle :: Type -> Type #

Show DeltaTextStyle Source # 
Instance details

Defined in Potato.Flow.Types

NFData DeltaTextStyle Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: DeltaTextStyle -> () #

Eq DeltaTextStyle Source # 
Instance details

Defined in Potato.Flow.Types

Delta TextStyle DeltaTextStyle Source # 
Instance details

Defined in Potato.Flow.Types

type Rep DeltaTextStyle Source # 
Instance details

Defined in Potato.Flow.Types

type Rep DeltaTextStyle = D1 ('MetaData "DeltaTextStyle" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "DeltaTextStyle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TextStyle, TextStyle))))

data DeltaTextAlign Source #

Instances

Instances details
Generic DeltaTextAlign Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep DeltaTextAlign :: Type -> Type #

Show DeltaTextAlign Source # 
Instance details

Defined in Potato.Flow.Types

NFData DeltaTextAlign Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: DeltaTextAlign -> () #

Eq DeltaTextAlign Source # 
Instance details

Defined in Potato.Flow.Types

Delta TextAlign DeltaTextAlign Source # 
Instance details

Defined in Potato.Flow.Types

type Rep DeltaTextAlign Source # 
Instance details

Defined in Potato.Flow.Types

type Rep DeltaTextAlign = D1 ('MetaData "DeltaTextAlign" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "DeltaTextAlign" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TextAlign, TextAlign))))

data DeltaMaybeText Source #

Instances

Instances details
Generic DeltaMaybeText Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep DeltaMaybeText :: Type -> Type #

Show DeltaMaybeText Source # 
Instance details

Defined in Potato.Flow.Types

NFData DeltaMaybeText Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: DeltaMaybeText -> () #

Eq DeltaMaybeText Source # 
Instance details

Defined in Potato.Flow.Types

Delta (Maybe Text) DeltaMaybeText Source # 
Instance details

Defined in Potato.Flow.Types

type Rep DeltaMaybeText Source # 
Instance details

Defined in Potato.Flow.Types

type Rep DeltaMaybeText = D1 ('MetaData "DeltaMaybeText" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "DeltaMaybeText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text, Maybe Text))))

data DeltaTextArea Source #

Instances

Instances details
Generic DeltaTextArea Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep DeltaTextArea :: Type -> Type #

Show DeltaTextArea Source # 
Instance details

Defined in Potato.Flow.Types

NFData DeltaTextArea Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: DeltaTextArea -> () #

Eq DeltaTextArea Source # 
Instance details

Defined in Potato.Flow.Types

Delta TextAreaMapping DeltaTextArea Source # 
Instance details

Defined in Potato.Flow.Types

type Rep DeltaTextArea Source # 
Instance details

Defined in Potato.Flow.Types

type Rep DeltaTextArea = D1 ('MetaData "DeltaTextArea" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "DeltaTextArea" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map XY (Maybe PChar, Maybe PChar)))))

data DeltaTextAreaToggle Source #

Instances

Instances details
Generic DeltaTextAreaToggle Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep DeltaTextAreaToggle :: Type -> Type #

Show DeltaTextAreaToggle Source # 
Instance details

Defined in Potato.Flow.Types

NFData DeltaTextAreaToggle Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: DeltaTextAreaToggle -> () #

Eq DeltaTextAreaToggle Source # 
Instance details

Defined in Potato.Flow.Types

Delta SElt DeltaTextAreaToggle Source # 
Instance details

Defined in Potato.Flow.Types

type Rep DeltaTextAreaToggle Source # 
Instance details

Defined in Potato.Flow.Types

type Rep DeltaTextAreaToggle = D1 ('MetaData "DeltaTextAreaToggle" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "DeltaTextAreaToggle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SElt)))

serialized types

data SCanvas Source #

Constructors

SCanvas 

Fields

Instances

Instances details
FromJSON SCanvas Source # 
Instance details

Defined in Potato.Flow.Types

ToJSON SCanvas Source # 
Instance details

Defined in Potato.Flow.Types

Generic SCanvas Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep SCanvas :: Type -> Type #

Methods

from :: SCanvas -> Rep SCanvas x #

to :: Rep SCanvas x -> SCanvas #

Show SCanvas Source # 
Instance details

Defined in Potato.Flow.Types

Binary SCanvas Source # 
Instance details

Defined in Potato.Flow.Types

Methods

put :: SCanvas -> Put #

get :: Get SCanvas #

putList :: [SCanvas] -> Put #

NFData SCanvas Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: SCanvas -> () #

Eq SCanvas Source # 
Instance details

Defined in Potato.Flow.Types

Methods

(==) :: SCanvas -> SCanvas -> Bool #

(/=) :: SCanvas -> SCanvas -> Bool #

type Rep SCanvas Source # 
Instance details

Defined in Potato.Flow.Types

type Rep SCanvas = D1 ('MetaData "SCanvas" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "SCanvas" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sCanvas_box") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LBox)))

data SPotatoFlow Source #

Instances

Instances details
FromJSON SPotatoFlow Source # 
Instance details

Defined in Potato.Flow.Types

ToJSON SPotatoFlow Source # 
Instance details

Defined in Potato.Flow.Types

Generic SPotatoFlow Source # 
Instance details

Defined in Potato.Flow.Types

Associated Types

type Rep SPotatoFlow :: Type -> Type #

Show SPotatoFlow Source # 
Instance details

Defined in Potato.Flow.Types

Binary SPotatoFlow Source # 
Instance details

Defined in Potato.Flow.Types

NFData SPotatoFlow Source # 
Instance details

Defined in Potato.Flow.Types

Methods

rnf :: SPotatoFlow -> () #

Eq SPotatoFlow Source # 
Instance details

Defined in Potato.Flow.Types

type Rep SPotatoFlow Source # 
Instance details

Defined in Potato.Flow.Types

type Rep SPotatoFlow = D1 ('MetaData "SPotatoFlow" "Potato.Flow.Types" "tinytools-0.1.0.0-DrleRpyeSqeBtRJXQdRmv7" 'False) (C1 ('MetaCons "SPotatoFlow" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sPotatoFlow_sCanvas") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SCanvas) :*: S1 ('MetaSel ('Just "_sPotatoFlow_sEltTree") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SEltTree)))