comic-0.0.1: A format for describing comics.

Safe HaskellNone
LanguageHaskell2010

Data.Comic.Flip

Documentation

data Segment Source #

Constructors

Segment 

Fields

  • _sDuration :: !DiffTime

    This is how long, ideally, the segment would air for.

  • _sSplice :: SortedList FrameSplice

    The actual stage directions for playing the content. Times are [0, 1] of the Duration. We keep sorting for a stable Ord instance.

Instances
Eq Segment Source # 
Instance details

Defined in Data.Comic.Flip

Methods

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

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

Ord Segment Source # 
Instance details

Defined in Data.Comic.Flip

Show Segment Source # 
Instance details

Defined in Data.Comic.Flip

Generic Segment Source # 
Instance details

Defined in Data.Comic.Flip

Associated Types

type Rep Segment :: Type -> Type #

Methods

from :: Segment -> Rep Segment x #

to :: Rep Segment x -> Segment #

Semigroup Segment Source # 
Instance details

Defined in Data.Comic.Flip

Monoid Segment Source # 
Instance details

Defined in Data.Comic.Flip

Hashable Segment Source # 
Instance details

Defined in Data.Comic.Flip

Methods

hashWithSalt :: Int -> Segment -> Int #

hash :: Segment -> Int #

ToJSON Segment Source # 
Instance details

Defined in Data.Comic.Flip

FromJSON Segment Source # 
Instance details

Defined in Data.Comic.Flip

NFData Segment Source # 
Instance details

Defined in Data.Comic.Flip

Methods

rnf :: Segment -> () #

type Rep Segment Source # 
Instance details

Defined in Data.Comic.Flip

type Rep Segment = D1 (MetaData "Segment" "Data.Comic.Flip" "comic-0.0.1-GvijLpXnXAw1uVTGer44ST" False) (C1 (MetaCons "Segment" PrefixI True) (S1 (MetaSel (Just "_sDuration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DiffTime) :*: S1 (MetaSel (Just "_sSplice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SortedList FrameSplice))))

data ScheduledSegment Source #

Constructors

ScheduledSegment 

Fields

Instances
Eq ScheduledSegment Source # 
Instance details

Defined in Data.Comic.Flip

Ord ScheduledSegment Source # 
Instance details

Defined in Data.Comic.Flip

Show ScheduledSegment Source # 
Instance details

Defined in Data.Comic.Flip

Generic ScheduledSegment Source # 
Instance details

Defined in Data.Comic.Flip

Associated Types

type Rep ScheduledSegment :: Type -> Type #

ToJSON ScheduledSegment Source # 
Instance details

Defined in Data.Comic.Flip

FromJSON ScheduledSegment Source # 
Instance details

Defined in Data.Comic.Flip

NFData ScheduledSegment Source # 
Instance details

Defined in Data.Comic.Flip

Methods

rnf :: ScheduledSegment -> () #

type Rep ScheduledSegment Source # 
Instance details

Defined in Data.Comic.Flip

type Rep ScheduledSegment = D1 (MetaData "ScheduledSegment" "Data.Comic.Flip" "comic-0.0.1-GvijLpXnXAw1uVTGer44ST" False) (C1 (MetaCons "ScheduledSegment" PrefixI True) (S1 (MetaSel (Just "_ssSegment") SourceUnpack SourceStrict DecidedStrict) (Rec0 Segment) :*: (S1 (MetaSel (Just "_ssSegID") SourceUnpack SourceStrict DecidedStrict) (Rec0 UUID) :*: S1 (MetaSel (Just "_ssPlayTill") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DiffTime))))

data FrameSplice Source #

Instances
Eq FrameSplice Source # 
Instance details

Defined in Data.Comic.Flip

Ord FrameSplice Source # 
Instance details

Defined in Data.Comic.Flip

Read FrameSplice Source # 
Instance details

Defined in Data.Comic.Flip

Show FrameSplice Source # 
Instance details

Defined in Data.Comic.Flip

Generic FrameSplice Source # 
Instance details

Defined in Data.Comic.Flip

Associated Types

type Rep FrameSplice :: Type -> Type #

Hashable FrameSplice Source # 
Instance details

Defined in Data.Comic.Flip

ToJSON FrameSplice Source # 
Instance details

Defined in Data.Comic.Flip

FromJSON FrameSplice Source # 
Instance details

Defined in Data.Comic.Flip

NFData FrameSplice Source # 
Instance details

Defined in Data.Comic.Flip

Methods

rnf :: FrameSplice -> () #

type Rep FrameSplice Source # 
Instance details

Defined in Data.Comic.Flip

data TextType Source #

Instances
Enum TextType Source # 
Instance details

Defined in Data.Comic.Flip

Eq TextType Source # 
Instance details

Defined in Data.Comic.Flip

Ord TextType Source # 
Instance details

Defined in Data.Comic.Flip

Read TextType Source # 
Instance details

Defined in Data.Comic.Flip

Show TextType Source # 
Instance details

Defined in Data.Comic.Flip

Generic TextType Source # 
Instance details

Defined in Data.Comic.Flip

Associated Types

type Rep TextType :: Type -> Type #

Methods

from :: TextType -> Rep TextType x #

to :: Rep TextType x -> TextType #

Hashable TextType Source # 
Instance details

Defined in Data.Comic.Flip

Methods

hashWithSalt :: Int -> TextType -> Int #

hash :: TextType -> Int #

ToJSON TextType Source # 
Instance details

Defined in Data.Comic.Flip

FromJSON TextType Source # 
Instance details

Defined in Data.Comic.Flip

NFData TextType Source # 
Instance details

Defined in Data.Comic.Flip

Methods

rnf :: TextType -> () #

type Rep TextType Source # 
Instance details

Defined in Data.Comic.Flip

type Rep TextType = D1 (MetaData "TextType" "Data.Comic.Flip" "comic-0.0.1-GvijLpXnXAw1uVTGer44ST" False) ((C1 (MetaCons "TxtStatic" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TxtScroll" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TxtSpeech" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TxtBreaking" PrefixI False) (U1 :: Type -> Type)))

data OnScreen Source #

Constructors

OnScreen 

Fields

Instances
Eq OnScreen Source # 
Instance details

Defined in Data.Comic.Flip

Ord OnScreen Source # 
Instance details

Defined in Data.Comic.Flip

Read OnScreen Source # 
Instance details

Defined in Data.Comic.Flip

Show OnScreen Source # 
Instance details

Defined in Data.Comic.Flip

Generic OnScreen Source # 
Instance details

Defined in Data.Comic.Flip

Associated Types

type Rep OnScreen :: Type -> Type #

Methods

from :: OnScreen -> Rep OnScreen x #

to :: Rep OnScreen x -> OnScreen #

Hashable OnScreen Source # 
Instance details

Defined in Data.Comic.Flip

Methods

hashWithSalt :: Int -> OnScreen -> Int #

hash :: OnScreen -> Int #

NFData OnScreen Source # 
Instance details

Defined in Data.Comic.Flip

Methods

rnf :: OnScreen -> () #

type Rep OnScreen Source # 
Instance details

Defined in Data.Comic.Flip

data Box Source #

Constructors

Box 

Fields

Instances
Eq Box Source # 
Instance details

Defined in Data.Comic.Flip

Methods

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

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

Ord Box Source # 
Instance details

Defined in Data.Comic.Flip

Methods

compare :: Box -> Box -> Ordering #

(<) :: Box -> Box -> Bool #

(<=) :: Box -> Box -> Bool #

(>) :: Box -> Box -> Bool #

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

max :: Box -> Box -> Box #

min :: Box -> Box -> Box #

Read Box Source # 
Instance details

Defined in Data.Comic.Flip

Show Box Source # 
Instance details

Defined in Data.Comic.Flip

Methods

showsPrec :: Int -> Box -> ShowS #

show :: Box -> String #

showList :: [Box] -> ShowS #

Generic Box Source # 
Instance details

Defined in Data.Comic.Flip

Associated Types

type Rep Box :: Type -> Type #

Methods

from :: Box -> Rep Box x #

to :: Rep Box x -> Box #

Hashable Box Source # 
Instance details

Defined in Data.Comic.Flip

Methods

hashWithSalt :: Int -> Box -> Int #

hash :: Box -> Int #

NFData Box Source # 
Instance details

Defined in Data.Comic.Flip

Methods

rnf :: Box -> () #

type Rep Box Source # 
Instance details

Defined in Data.Comic.Flip

type Rep Box = D1 (MetaData "Box" "Data.Comic.Flip" "comic-0.0.1-GvijLpXnXAw1uVTGer44ST" False) (C1 (MetaCons "Box" PrefixI True) (S1 (MetaSel (Just "_bTl") SourceUnpack SourceStrict DecidedStrict) (Rec0 RelPosition) :*: S1 (MetaSel (Just "_bBr") SourceUnpack SourceStrict DecidedStrict) (Rec0 RelPosition)))

data RelPosition Source #

Constructors

RPos 

Fields

Instances
Eq RelPosition Source # 
Instance details

Defined in Data.Comic.Types

Ord RelPosition Source # 
Instance details

Defined in Data.Comic.Types

Read RelPosition Source # 
Instance details

Defined in Data.Comic.Types

Show RelPosition Source # 
Instance details

Defined in Data.Comic.Types

Generic RelPosition Source # 
Instance details

Defined in Data.Comic.Types

Associated Types

type Rep RelPosition :: Type -> Type #

Hashable RelPosition Source # 
Instance details

Defined in Data.Comic.Types

ToJSON RelPosition Source # 
Instance details

Defined in Data.Comic.Types

FromJSON RelPosition Source # 
Instance details

Defined in Data.Comic.Types

NFData RelPosition Source # 
Instance details

Defined in Data.Comic.Types

Methods

rnf :: RelPosition -> () #

type Rep RelPosition Source # 
Instance details

Defined in Data.Comic.Types

type Rep RelPosition = D1 (MetaData "RelPosition" "Data.Comic.Types" "comic-0.0.1-GvijLpXnXAw1uVTGer44ST" False) (C1 (MetaCons "RPos" PrefixI True) (S1 (MetaSel (Just "_rX") SourceUnpack SourceStrict DecidedStrict) (Rec0 Float) :*: S1 (MetaSel (Just "_rY") SourceUnpack SourceStrict DecidedStrict) (Rec0 Float)))

data Font Source #

Constructors

Font !FontName !FontSize !RGBA 
Instances
Eq Font Source # 
Instance details

Defined in Data.Comic.Types

Methods

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

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

Ord Font Source # 
Instance details

Defined in Data.Comic.Types

Methods

compare :: Font -> Font -> Ordering #

(<) :: Font -> Font -> Bool #

(<=) :: Font -> Font -> Bool #

(>) :: Font -> Font -> Bool #

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

max :: Font -> Font -> Font #

min :: Font -> Font -> Font #

Read Font Source # 
Instance details

Defined in Data.Comic.Types

Show Font Source # 
Instance details

Defined in Data.Comic.Types

Methods

showsPrec :: Int -> Font -> ShowS #

show :: Font -> String #

showList :: [Font] -> ShowS #

Generic Font Source # 
Instance details

Defined in Data.Comic.Types

Associated Types

type Rep Font :: Type -> Type #

Methods

from :: Font -> Rep Font x #

to :: Rep Font x -> Font #

Hashable Font Source # 
Instance details

Defined in Data.Comic.Types

Methods

hashWithSalt :: Int -> Font -> Int #

hash :: Font -> Int #

NFData Font Source # 
Instance details

Defined in Data.Comic.Types

Methods

rnf :: Font -> () #

type Rep Font Source # 
Instance details

Defined in Data.Comic.Types

data TextLayout Source #

Instances
Eq TextLayout Source # 
Instance details

Defined in Data.Comic.Flip

Ord TextLayout Source # 
Instance details

Defined in Data.Comic.Flip

Read TextLayout Source # 
Instance details

Defined in Data.Comic.Flip

Show TextLayout Source # 
Instance details

Defined in Data.Comic.Flip

Generic TextLayout Source # 
Instance details

Defined in Data.Comic.Flip

Associated Types

type Rep TextLayout :: Type -> Type #

Hashable TextLayout Source # 
Instance details

Defined in Data.Comic.Flip

NFData TextLayout Source # 
Instance details

Defined in Data.Comic.Flip

Methods

rnf :: TextLayout -> () #

type Rep TextLayout Source # 
Instance details

Defined in Data.Comic.Flip

type Rep TextLayout = D1 (MetaData "TextLayout" "Data.Comic.Flip" "comic-0.0.1-GvijLpXnXAw1uVTGer44ST" False) (C1 (MetaCons "TextLayout" PrefixI True) (S1 (MetaSel (Just "_tlHorizontal") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HAlignment) :*: (S1 (MetaSel (Just "_tlVertical") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 VAlignment) :*: S1 (MetaSel (Just "_tlShrink") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool))))

data HAlignment Source #

Constructors

HALeft 
HACenter 
HARight 
Instances
Enum HAlignment Source # 
Instance details

Defined in Data.Comic.Flip

Eq HAlignment Source # 
Instance details

Defined in Data.Comic.Flip

Ord HAlignment Source # 
Instance details

Defined in Data.Comic.Flip

Read HAlignment Source # 
Instance details

Defined in Data.Comic.Flip

Show HAlignment Source # 
Instance details

Defined in Data.Comic.Flip

Generic HAlignment Source # 
Instance details

Defined in Data.Comic.Flip

Associated Types

type Rep HAlignment :: Type -> Type #

Hashable HAlignment Source # 
Instance details

Defined in Data.Comic.Flip

ToJSON HAlignment Source # 
Instance details

Defined in Data.Comic.Flip

FromJSON HAlignment Source # 
Instance details

Defined in Data.Comic.Flip

NFData HAlignment Source # 
Instance details

Defined in Data.Comic.Flip

Methods

rnf :: HAlignment -> () #

type Rep HAlignment Source # 
Instance details

Defined in Data.Comic.Flip

type Rep HAlignment = D1 (MetaData "HAlignment" "Data.Comic.Flip" "comic-0.0.1-GvijLpXnXAw1uVTGer44ST" False) (C1 (MetaCons "HALeft" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "HACenter" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HARight" PrefixI False) (U1 :: Type -> Type)))

data VAlignment Source #

Constructors

VATop 
VACenter 
VABottom 
Instances
Enum VAlignment Source # 
Instance details

Defined in Data.Comic.Flip

Eq VAlignment Source # 
Instance details

Defined in Data.Comic.Flip

Ord VAlignment Source # 
Instance details

Defined in Data.Comic.Flip

Read VAlignment Source # 
Instance details

Defined in Data.Comic.Flip

Show VAlignment Source # 
Instance details

Defined in Data.Comic.Flip

Generic VAlignment Source # 
Instance details

Defined in Data.Comic.Flip

Associated Types

type Rep VAlignment :: Type -> Type #

Hashable VAlignment Source # 
Instance details

Defined in Data.Comic.Flip

ToJSON VAlignment Source # 
Instance details

Defined in Data.Comic.Flip

FromJSON VAlignment Source # 
Instance details

Defined in Data.Comic.Flip

NFData VAlignment Source # 
Instance details

Defined in Data.Comic.Flip

Methods

rnf :: VAlignment -> () #

type Rep VAlignment Source # 
Instance details

Defined in Data.Comic.Flip

type Rep VAlignment = D1 (MetaData "VAlignment" "Data.Comic.Flip" "comic-0.0.1-GvijLpXnXAw1uVTGer44ST" False) (C1 (MetaCons "VATop" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "VACenter" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VABottom" PrefixI False) (U1 :: Type -> Type)))