tinytools-0.1.0.5: tinytools is a monospace unicode diagram editor
Safe HaskellSafe-Inferred
LanguageHaskell2010

Potato.Flow.Serialization.Versions.V1.SElts

Synopsis

Documentation

data FillStyle Source #

Instances

Instances details
Generic FillStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Associated Types

type Rep FillStyle :: Type -> Type #

Show FillStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Binary FillStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

NFData FillStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

rnf :: FillStyle -> () #

Default FillStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

def :: FillStyle

Eq FillStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

FromJSON FillStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

parseJSON :: Value -> Parser FillStyle

parseJSONList :: Value -> Parser [FillStyle]

ToJSON FillStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

toJSON :: FillStyle -> Value

toEncoding :: FillStyle -> Encoding

toJSONList :: [FillStyle] -> Value

toEncodingList :: [FillStyle] -> Encoding

type Rep FillStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep FillStyle = D1 ('MetaData "FillStyle" "Potato.Flow.Serialization.Versions.V1.SElts" "tinytools-0.1.0.5-inplace" 'False) (C1 ('MetaCons "FillStyle_Blank" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FillStyle_Simple" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PChar)))

data SuperStyle Source #

Instances

Instances details
Generic SuperStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Associated Types

type Rep SuperStyle :: Type -> Type #

Show SuperStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Binary SuperStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

NFData SuperStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

rnf :: SuperStyle -> () #

Default SuperStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

def :: SuperStyle

Eq SuperStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

FromJSON SuperStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

parseJSON :: Value -> Parser SuperStyle

parseJSONList :: Value -> Parser [SuperStyle]

ToJSON SuperStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

toJSON :: SuperStyle -> Value

toEncoding :: SuperStyle -> Encoding

toJSONList :: [SuperStyle] -> Value

toEncodingList :: [SuperStyle] -> Encoding

Delta SuperStyle DeltaSuperStyle Source # 
Instance details

Defined in Potato.Flow.Types

type Rep SuperStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep SuperStyle = D1 ('MetaData "SuperStyle" "Potato.Flow.Serialization.Versions.V1.SElts" "tinytools-0.1.0.5-inplace" 'False) (C1 ('MetaCons "SuperStyle" 'PrefixI 'True) (((S1 ('MetaSel ('Just "_superStyle_tl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MPChar) :*: S1 ('MetaSel ('Just "_superStyle_tr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MPChar)) :*: (S1 ('MetaSel ('Just "_superStyle_bl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MPChar) :*: S1 ('MetaSel ('Just "_superStyle_br") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MPChar))) :*: ((S1 ('MetaSel ('Just "_superStyle_vertical") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MPChar) :*: S1 ('MetaSel ('Just "_superStyle_horizontal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MPChar)) :*: (S1 ('MetaSel ('Just "_superStyle_point") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MPChar) :*: S1 ('MetaSel ('Just "_superStyle_fill") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FillStyle)))))

data TextAlign Source #

 

Instances

Instances details
Generic TextAlign Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Associated Types

type Rep TextAlign :: Type -> Type #

Show TextAlign Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Binary TextAlign Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

NFData TextAlign Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

rnf :: TextAlign -> () #

Default TextAlign Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

def :: TextAlign

Eq TextAlign Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

FromJSON TextAlign Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

parseJSON :: Value -> Parser TextAlign

parseJSONList :: Value -> Parser [TextAlign]

ToJSON TextAlign Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

toJSON :: TextAlign -> Value

toEncoding :: TextAlign -> Encoding

toJSONList :: [TextAlign] -> Value

toEncodingList :: [TextAlign] -> Encoding

Delta TextAlign DeltaTextAlign Source # 
Instance details

Defined in Potato.Flow.Types

type Rep TextAlign Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep TextAlign = D1 ('MetaData "TextAlign" "Potato.Flow.Serialization.Versions.V1.SElts" "tinytools-0.1.0.5-inplace" 'False) (C1 ('MetaCons "TextAlign_Left" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TextAlign_Right" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TextAlign_Center" 'PrefixI 'False) (U1 :: Type -> Type)))

data TextStyle Source #

 

Constructors

TextStyle 

Instances

Instances details
Generic TextStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Associated Types

type Rep TextStyle :: Type -> Type #

Show TextStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Binary TextStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

NFData TextStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

rnf :: TextStyle -> () #

Default TextStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

def :: TextStyle

Eq TextStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

FromJSON TextStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

parseJSON :: Value -> Parser TextStyle

parseJSONList :: Value -> Parser [TextStyle]

ToJSON TextStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

toJSON :: TextStyle -> Value

toEncoding :: TextStyle -> Encoding

toJSONList :: [TextStyle] -> Value

toEncodingList :: [TextStyle] -> Encoding

Delta TextStyle DeltaTextStyle Source # 
Instance details

Defined in Potato.Flow.Types

type Rep TextStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep TextStyle = D1 ('MetaData "TextStyle" "Potato.Flow.Serialization.Versions.V1.SElts" "tinytools-0.1.0.5-inplace" 'False) (C1 ('MetaCons "TextStyle" 'PrefixI 'True) (S1 ('MetaSel ('Just "_textStyle_alignment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TextAlign)))

data AttachmentLocation Source #

Constructors

AL_Top 
AL_Bot 
AL_Left 
AL_Right 
AL_Any 

Instances

Instances details
Generic AttachmentLocation Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Associated Types

type Rep AttachmentLocation :: Type -> Type #

Show AttachmentLocation Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Binary AttachmentLocation Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

NFData AttachmentLocation Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

rnf :: AttachmentLocation -> () #

Eq AttachmentLocation Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

FromJSON AttachmentLocation Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

parseJSON :: Value -> Parser AttachmentLocation

parseJSONList :: Value -> Parser [AttachmentLocation]

ToJSON AttachmentLocation Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

TransformMe AttachmentLocation Source # 
Instance details

Defined in Potato.Flow.Methods.LineTypes

type Rep AttachmentLocation Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep AttachmentLocation = D1 ('MetaData "AttachmentLocation" "Potato.Flow.Serialization.Versions.V1.SElts" "tinytools-0.1.0.5-inplace" 'False) ((C1 ('MetaCons "AL_Top" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AL_Bot" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AL_Left" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AL_Right" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AL_Any" 'PrefixI 'False) (U1 :: Type -> Type))))

data Attachment Source #

Instances

Instances details
Generic Attachment Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Associated Types

type Rep Attachment :: Type -> Type #

Show Attachment Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Binary Attachment Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

NFData Attachment Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

rnf :: Attachment -> () #

Eq Attachment Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

FromJSON Attachment Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

parseJSON :: Value -> Parser Attachment

parseJSONList :: Value -> Parser [Attachment]

ToJSON Attachment Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

toJSON :: Attachment -> Value

toEncoding :: Attachment -> Encoding

toJSONList :: [Attachment] -> Value

toEncodingList :: [Attachment] -> Encoding

type Rep Attachment Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep Attachment = D1 ('MetaData "Attachment" "Potato.Flow.Serialization.Versions.V1.SElts" "tinytools-0.1.0.5-inplace" 'False) (C1 ('MetaCons "Attachment" 'PrefixI 'True) (S1 ('MetaSel ('Just "_attachment_target") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 REltId) :*: (S1 ('MetaSel ('Just "_attachment_location") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AttachmentLocation) :*: S1 ('MetaSel ('Just "_attachment_offset_rel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AttachmentOffsetRatio))))

data SBoxTitle Source #

 

Instances

Instances details
Generic SBoxTitle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Associated Types

type Rep SBoxTitle :: Type -> Type #

Show SBoxTitle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Binary SBoxTitle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

NFData SBoxTitle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

rnf :: SBoxTitle -> () #

Default SBoxTitle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

def :: SBoxTitle

Eq SBoxTitle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

FromJSON SBoxTitle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

parseJSON :: Value -> Parser SBoxTitle

parseJSONList :: Value -> Parser [SBoxTitle]

ToJSON SBoxTitle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

toJSON :: SBoxTitle -> Value

toEncoding :: SBoxTitle -> Encoding

toJSONList :: [SBoxTitle] -> Value

toEncodingList :: [SBoxTitle] -> Encoding

type Rep SBoxTitle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep SBoxTitle = D1 ('MetaData "SBoxTitle" "Potato.Flow.Serialization.Versions.V1.SElts" "tinytools-0.1.0.5-inplace" 'False) (C1 ('MetaCons "SBoxTitle" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sBoxTitle_title") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "_sBoxTitle_align") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TextAlign)))

data SBoxText Source #

 

Instances

Instances details
Generic SBoxText Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Associated Types

type Rep SBoxText :: Type -> Type #

Methods

from :: SBoxText -> Rep SBoxText x #

to :: Rep SBoxText x -> SBoxText #

Show SBoxText Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Binary SBoxText Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

put :: SBoxText -> Put #

get :: Get SBoxText #

putList :: [SBoxText] -> Put #

NFData SBoxText Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

rnf :: SBoxText -> () #

Default SBoxText Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

def :: SBoxText

Eq SBoxText Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

FromJSON SBoxText Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

parseJSON :: Value -> Parser SBoxText

parseJSONList :: Value -> Parser [SBoxText]

ToJSON SBoxText Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

toJSON :: SBoxText -> Value

toEncoding :: SBoxText -> Encoding

toJSONList :: [SBoxText] -> Value

toEncodingList :: [SBoxText] -> Encoding

Delta SBoxText CBoxText Source # 
Instance details

Defined in Potato.Flow.Types

type Rep SBoxText Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep SBoxText = D1 ('MetaData "SBoxText" "Potato.Flow.Serialization.Versions.V1.SElts" "tinytools-0.1.0.5-inplace" 'False) (C1 ('MetaCons "SBoxText" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sBoxText_text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "_sBoxText_style") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TextStyle)))

data SBoxType Source #

Instances

Instances details
Generic SBoxType Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Associated Types

type Rep SBoxType :: Type -> Type #

Methods

from :: SBoxType -> Rep SBoxType x #

to :: Rep SBoxType x -> SBoxType #

Show SBoxType Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Binary SBoxType Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

put :: SBoxType -> Put #

get :: Get SBoxType #

putList :: [SBoxType] -> Put #

NFData SBoxType Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

rnf :: SBoxType -> () #

Default SBoxType Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

def :: SBoxType

Eq SBoxType Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

FromJSON SBoxType Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

parseJSON :: Value -> Parser SBoxType

parseJSONList :: Value -> Parser [SBoxType]

ToJSON SBoxType Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

toJSON :: SBoxType -> Value

toEncoding :: SBoxType -> Encoding

toJSONList :: [SBoxType] -> Value

toEncodingList :: [SBoxType] -> Encoding

type Rep SBoxType Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep SBoxType = D1 ('MetaData "SBoxType" "Potato.Flow.Serialization.Versions.V1.SElts" "tinytools-0.1.0.5-inplace" 'False) ((C1 ('MetaCons "SBoxType_Box" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SBoxType_NoBox" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SBoxType_BoxText" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SBoxType_NoBoxText" 'PrefixI 'False) (U1 :: Type -> Type)))

data SBox Source #

 

Instances

Instances details
Generic SBox Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Associated Types

type Rep SBox :: Type -> Type #

Methods

from :: SBox -> Rep SBox x #

to :: Rep SBox x -> SBox #

Show SBox Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

showsPrec :: Int -> SBox -> ShowS #

show :: SBox -> String #

showList :: [SBox] -> ShowS #

Binary SBox Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

put :: SBox -> Put #

get :: Get SBox #

putList :: [SBox] -> Put #

NFData SBox Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

rnf :: SBox -> () #

Default SBox Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

def :: SBox

Eq SBox Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

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

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

FromJSON SBox Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

parseJSON :: Value -> Parser SBox

parseJSONList :: Value -> Parser [SBox]

ToJSON SBox Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

toJSON :: SBox -> Value

toEncoding :: SBox -> Encoding

toJSONList :: [SBox] -> Value

toEncodingList :: [SBox] -> Encoding

Delta SBox CBoxText Source # 
Instance details

Defined in Potato.Flow.Types

Delta SBox CBoxType Source # 
Instance details

Defined in Potato.Flow.Types

type Rep SBox Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep SBox = D1 ('MetaData "SBox" "Potato.Flow.Serialization.Versions.V1.SElts" "tinytools-0.1.0.5-inplace" 'False) (C1 ('MetaCons "SBox" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_sBox_box") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LBox) :*: S1 ('MetaSel ('Just "_sBox_superStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SuperStyle)) :*: (S1 ('MetaSel ('Just "_sBox_title") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SBoxTitle) :*: (S1 ('MetaSel ('Just "_sBox_text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SBoxText) :*: S1 ('MetaSel ('Just "_sBox_boxType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SBoxType)))))

data LineAutoStyle Source #

Instances

Instances details
Generic LineAutoStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Associated Types

type Rep LineAutoStyle :: Type -> Type #

Show LineAutoStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Binary LineAutoStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

NFData LineAutoStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

rnf :: LineAutoStyle -> () #

Default LineAutoStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

def :: LineAutoStyle

Eq LineAutoStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

FromJSON LineAutoStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

parseJSON :: Value -> Parser LineAutoStyle

parseJSONList :: Value -> Parser [LineAutoStyle]

ToJSON LineAutoStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

toJSON :: LineAutoStyle -> Value

toEncoding :: LineAutoStyle -> Encoding

toJSONList :: [LineAutoStyle] -> Value

toEncodingList :: [LineAutoStyle] -> Encoding

type Rep LineAutoStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep LineAutoStyle = D1 ('MetaData "LineAutoStyle" "Potato.Flow.Serialization.Versions.V1.SElts" "tinytools-0.1.0.5-inplace" 'False) ((C1 ('MetaCons "LineAutoStyle_Auto" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LineAutoStyle_AutoStraight" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LineAutoStyle_StraightAlwaysHorizontal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LineAutoStyle_StraightAlwaysVertical" 'PrefixI 'False) (U1 :: Type -> Type)))

data LineStyle Source #

Instances

Instances details
Generic LineStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Associated Types

type Rep LineStyle :: Type -> Type #

Show LineStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Binary LineStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

NFData LineStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

rnf :: LineStyle -> () #

Default LineStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

def :: LineStyle

Eq LineStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

FromJSON LineStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

parseJSON :: Value -> Parser LineStyle

parseJSONList :: Value -> Parser [LineStyle]

ToJSON LineStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

toJSON :: LineStyle -> Value

toEncoding :: LineStyle -> Encoding

toJSONList :: [LineStyle] -> Value

toEncodingList :: [LineStyle] -> Encoding

Delta LineStyle DeltaLineStyle Source # 
Instance details

Defined in Potato.Flow.Types

type Rep LineStyle Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep LineStyle = D1 ('MetaData "LineStyle" "Potato.Flow.Serialization.Versions.V1.SElts" "tinytools-0.1.0.5-inplace" 'False) (C1 ('MetaCons "LineStyle" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_lineStyle_leftArrows") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "_lineStyle_rightArrows") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "_lineStyle_upArrows") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "_lineStyle_downArrows") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

data SAutoLineConstraint Source #

Instances

Instances details
Generic SAutoLineConstraint Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Associated Types

type Rep SAutoLineConstraint :: Type -> Type #

Show SAutoLineConstraint Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Binary SAutoLineConstraint Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

NFData SAutoLineConstraint Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

rnf :: SAutoLineConstraint -> () #

Eq SAutoLineConstraint Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

FromJSON SAutoLineConstraint Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

parseJSON :: Value -> Parser SAutoLineConstraint

parseJSONList :: Value -> Parser [SAutoLineConstraint]

ToJSON SAutoLineConstraint Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep SAutoLineConstraint Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep SAutoLineConstraint = D1 ('MetaData "SAutoLineConstraint" "Potato.Flow.Serialization.Versions.V1.SElts" "tinytools-0.1.0.5-inplace" 'False) (C1 ('MetaCons "SAutoLineConstraintFixed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 XY)))

data SAutoLineLabelPosition Source #

Instances

Instances details
Generic SAutoLineLabelPosition Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Associated Types

type Rep SAutoLineLabelPosition :: Type -> Type #

Show SAutoLineLabelPosition Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Binary SAutoLineLabelPosition Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

NFData SAutoLineLabelPosition Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

rnf :: SAutoLineLabelPosition -> () #

Eq SAutoLineLabelPosition Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

FromJSON SAutoLineLabelPosition Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

parseJSON :: Value -> Parser SAutoLineLabelPosition

parseJSONList :: Value -> Parser [SAutoLineLabelPosition]

ToJSON SAutoLineLabelPosition Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep SAutoLineLabelPosition Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep SAutoLineLabelPosition = D1 ('MetaData "SAutoLineLabelPosition" "Potato.Flow.Serialization.Versions.V1.SElts" "tinytools-0.1.0.5-inplace" 'False) (C1 ('MetaCons "SAutoLineLabelPositionRelative" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float)))

data SAutoLineLabel Source #

Instances

Instances details
Generic SAutoLineLabel Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Associated Types

type Rep SAutoLineLabel :: Type -> Type #

Show SAutoLineLabel Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Binary SAutoLineLabel Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

NFData SAutoLineLabel Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

rnf :: SAutoLineLabel -> () #

Default SAutoLineLabel Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Eq SAutoLineLabel Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

FromJSON SAutoLineLabel Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

parseJSON :: Value -> Parser SAutoLineLabel

parseJSONList :: Value -> Parser [SAutoLineLabel]

ToJSON SAutoLineLabel Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

toJSON :: SAutoLineLabel -> Value

toEncoding :: SAutoLineLabel -> Encoding

toJSONList :: [SAutoLineLabel] -> Value

toEncodingList :: [SAutoLineLabel] -> Encoding

type Rep SAutoLineLabel Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep SAutoLineLabel = D1 ('MetaData "SAutoLineLabel" "Potato.Flow.Serialization.Versions.V1.SElts" "tinytools-0.1.0.5-inplace" 'False) (C1 ('MetaCons "SAutoLineLabel" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sAutoLineLabel_index") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "_sAutoLineLabel_position") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SAutoLineLabelPosition) :*: S1 ('MetaSel ('Just "_sAutoLineLabel_text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

data SAutoLine Source #

 

Instances

Instances details
Generic SAutoLine Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Associated Types

type Rep SAutoLine :: Type -> Type #

Show SAutoLine Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Binary SAutoLine Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

NFData SAutoLine Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

rnf :: SAutoLine -> () #

Default SAutoLine Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

def :: SAutoLine

Eq SAutoLine Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

FromJSON SAutoLine Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

parseJSON :: Value -> Parser SAutoLine

parseJSONList :: Value -> Parser [SAutoLine]

ToJSON SAutoLine Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

toJSON :: SAutoLine -> Value

toEncoding :: SAutoLine -> Encoding

toJSONList :: [SAutoLine] -> Value

toEncodingList :: [SAutoLine] -> Encoding

Delta SAutoLine CLine Source # 
Instance details

Defined in Potato.Flow.Types

type Rep SAutoLine Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep SAutoLine = D1 ('MetaData "SAutoLine" "Potato.Flow.Serialization.Versions.V1.SElts" "tinytools-0.1.0.5-inplace" 'False) (C1 ('MetaCons "SAutoLine" 'PrefixI 'True) (((S1 ('MetaSel ('Just "_sAutoLine_start") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 XY) :*: S1 ('MetaSel ('Just "_sAutoLine_end") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 XY)) :*: (S1 ('MetaSel ('Just "_sAutoLine_superStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SuperStyle) :*: S1 ('MetaSel ('Just "_sAutoLine_lineStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LineStyle))) :*: ((S1 ('MetaSel ('Just "_sAutoLine_lineStyleEnd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LineStyle) :*: S1 ('MetaSel ('Just "_sAutoLine_attachStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Attachment))) :*: (S1 ('MetaSel ('Just "_sAutoLine_attachEnd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Attachment)) :*: (S1 ('MetaSel ('Just "_sAutoLine_midpoints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SAutoLineConstraint]) :*: S1 ('MetaSel ('Just "_sAutoLine_labels") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SAutoLineLabel]))))))

data STextArea Source #

abitrary text confined to a box

Instances

Instances details
Generic STextArea Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Associated Types

type Rep STextArea :: Type -> Type #

Show STextArea Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Binary STextArea Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

NFData STextArea Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

rnf :: STextArea -> () #

Default STextArea Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

def :: STextArea

Eq STextArea Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

FromJSON STextArea Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

parseJSON :: Value -> Parser STextArea

parseJSONList :: Value -> Parser [STextArea]

ToJSON STextArea Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

toJSON :: STextArea -> Value

toEncoding :: STextArea -> Encoding

toJSONList :: [STextArea] -> Value

toEncodingList :: [STextArea] -> Encoding

type Rep STextArea Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep STextArea = D1 ('MetaData "STextArea" "Potato.Flow.Serialization.Versions.V1.SElts" "tinytools-0.1.0.5-inplace" 'False) (C1 ('MetaCons "STextArea" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sTextArea_box") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LBox) :*: (S1 ('MetaSel ('Just "_sTextArea_text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TextAreaMapping) :*: S1 ('MetaSel ('Just "_sTextArea_transparent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

data SElt Source #

Instances

Instances details
Generic SElt Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Associated Types

type Rep SElt :: Type -> Type #

Methods

from :: SElt -> Rep SElt x #

to :: Rep SElt x -> SElt #

Show SElt Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

showsPrec :: Int -> SElt -> ShowS #

show :: SElt -> String #

showList :: [SElt] -> ShowS #

Binary SElt Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

put :: SElt -> Put #

get :: Get SElt #

putList :: [SElt] -> Put #

NFData SElt Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

rnf :: SElt -> () #

Eq SElt Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

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

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

FromJSON SElt Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

parseJSON :: Value -> Parser SElt

parseJSONList :: Value -> Parser [SElt]

ToJSON SElt Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

toJSON :: SElt -> Value

toEncoding :: SElt -> Encoding

toJSONList :: [SElt] -> Value

toEncodingList :: [SElt] -> Encoding

Delta SElt DeltaTextAreaToggle Source # 
Instance details

Defined in Potato.Flow.Types

type Rep SElt Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep SElt = D1 ('MetaData "SElt" "Potato.Flow.Serialization.Versions.V1.SElts" "tinytools-0.1.0.5-inplace" 'False) ((C1 ('MetaCons "SEltNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SEltFolderStart" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SEltFolderEnd" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "SEltBox" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SBox)) :+: (C1 ('MetaCons "SEltLine" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SAutoLine)) :+: C1 ('MetaCons "SEltTextArea" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 STextArea)))))

data SEltLabel Source #

Constructors

SEltLabel 

Instances

Instances details
Generic SEltLabel Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Associated Types

type Rep SEltLabel :: Type -> Type #

Show SEltLabel Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Binary SEltLabel Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

NFData SEltLabel Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

rnf :: SEltLabel -> () #

Eq SEltLabel Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

FromJSON SEltLabel Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

parseJSON :: Value -> Parser SEltLabel

parseJSONList :: Value -> Parser [SEltLabel]

ToJSON SEltLabel Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

Methods

toJSON :: SEltLabel -> Value

toEncoding :: SEltLabel -> Encoding

toJSONList :: [SEltLabel] -> Value

toEncodingList :: [SEltLabel] -> Encoding

Delta SEltLabel CRename Source # 
Instance details

Defined in Potato.Flow.Types

type Rep SEltLabel Source # 
Instance details

Defined in Potato.Flow.Serialization.Versions.V1.SElts

type Rep SEltLabel = D1 ('MetaData "SEltLabel" "Potato.Flow.Serialization.Versions.V1.SElts" "tinytools-0.1.0.5-inplace" 'False) (C1 ('MetaCons "SEltLabel" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sEltLabel_name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "_sEltLabel_sElt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SElt)))