cue-sheet-2.0.0: Support for construction, rendering, and parsing of CUE sheets

Copyright© 2016–2018 Mark Karpov
LicenseBSD 3 clause
MaintainerMark Karpov <markkarpov92@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.CueSheet

Contents

Description

The module allows to construct, read, and write CUE sheets. The data types are defined in such a way that incorrect CUE sheets are impossible to represent. See parseCueSheet for parsing of plain text CUE sheet files and renderCueSheet for rendering.

Synopsis

Types

data CueSheet Source #

Entire CUE sheet, contains one or more files (see CueFile).

Constructors

CueSheet 

Fields

Instances
Eq CueSheet Source # 
Instance details

Defined in Text.CueSheet.Types

Ord CueSheet Source # 
Instance details

Defined in Text.CueSheet.Types

Show CueSheet Source # 
Instance details

Defined in Text.CueSheet.Types

Generic CueSheet Source # 
Instance details

Defined in Text.CueSheet.Types

Associated Types

type Rep CueSheet :: * -> * #

Methods

from :: CueSheet -> Rep CueSheet x #

to :: Rep CueSheet x -> CueSheet #

Arbitrary CueSheet Source # 
Instance details

Defined in Text.CueSheet.Types

type Rep CueSheet Source # 
Instance details

Defined in Text.CueSheet.Types

data CueFile Source #

A file to be written. Single file can be divided into one or more tracks (see CueTrack).

Constructors

CueFile 

Fields

Instances
Eq CueFile Source # 
Instance details

Defined in Text.CueSheet.Types

Methods

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

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

Ord CueFile Source # 
Instance details

Defined in Text.CueSheet.Types

Show CueFile Source # 
Instance details

Defined in Text.CueSheet.Types

Generic CueFile Source # 
Instance details

Defined in Text.CueSheet.Types

Associated Types

type Rep CueFile :: * -> * #

Methods

from :: CueFile -> Rep CueFile x #

to :: Rep CueFile x -> CueFile #

Arbitrary CueFile Source # 
Instance details

Defined in Text.CueSheet.Types

type Rep CueFile Source # 
Instance details

Defined in Text.CueSheet.Types

type Rep CueFile = D1 (MetaData "CueFile" "Text.CueSheet.Types" "cue-sheet-2.0.0-6h3teGT0ahPIL9F1kK7yIy" False) (C1 (MetaCons "CueFile" PrefixI True) (S1 (MetaSel (Just "cueFileName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilePath) :*: (S1 (MetaSel (Just "cueFileType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 CueFileType) :*: S1 (MetaSel (Just "cueFileTracks") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (NonEmpty CueTrack)))))

data CueFileType Source #

Enumeration of audio or file's data types.

Constructors

Binary

Intel binary file (least significant byte first). Use for data files.

Motorola

Motorola binary file (most significant file first). Use for data files.

Aiff

Audio AIFF file (44.1 kHz, 16 bit stereo).

Wave

Audio WAVE file (44.1 kHz, 16 bit stereo).

MP3

Audio MP3 file (44.1 kHz 16 bit stereo).

Instances
Bounded CueFileType Source # 
Instance details

Defined in Text.CueSheet.Types

Enum CueFileType Source # 
Instance details

Defined in Text.CueSheet.Types

Eq CueFileType Source # 
Instance details

Defined in Text.CueSheet.Types

Ord CueFileType Source # 
Instance details

Defined in Text.CueSheet.Types

Read CueFileType Source # 
Instance details

Defined in Text.CueSheet.Types

Show CueFileType Source # 
Instance details

Defined in Text.CueSheet.Types

Generic CueFileType Source # 
Instance details

Defined in Text.CueSheet.Types

Associated Types

type Rep CueFileType :: * -> * #

Arbitrary CueFileType Source # 
Instance details

Defined in Text.CueSheet.Types

type Rep CueFileType Source # 
Instance details

Defined in Text.CueSheet.Types

type Rep CueFileType = D1 (MetaData "CueFileType" "Text.CueSheet.Types" "cue-sheet-2.0.0-6h3teGT0ahPIL9F1kK7yIy" False) ((C1 (MetaCons "Binary" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Motorola" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Aiff" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Wave" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "MP3" PrefixI False) (U1 :: * -> *))))

data CueTrack Source #

A track. Single track can have one or more indices.

Constructors

CueTrack 

Fields

Instances
Eq CueTrack Source # 
Instance details

Defined in Text.CueSheet.Types

Ord CueTrack Source # 
Instance details

Defined in Text.CueSheet.Types

Show CueTrack Source # 
Instance details

Defined in Text.CueSheet.Types

Generic CueTrack Source # 
Instance details

Defined in Text.CueSheet.Types

Associated Types

type Rep CueTrack :: * -> * #

Methods

from :: CueTrack -> Rep CueTrack x #

to :: Rep CueTrack x -> CueTrack #

Arbitrary CueTrack Source # 
Instance details

Defined in Text.CueSheet.Types

type Rep CueTrack Source # 
Instance details

Defined in Text.CueSheet.Types

type Rep CueTrack = D1 (MetaData "CueTrack" "Text.CueSheet.Types" "cue-sheet-2.0.0-6h3teGT0ahPIL9F1kK7yIy" False) (C1 (MetaCons "CueTrack" PrefixI True) (((S1 (MetaSel (Just "cueTrackDigitalCopyPermitted") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: (S1 (MetaSel (Just "cueTrackFourChannelAudio") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: S1 (MetaSel (Just "cueTrackPreemphasisEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool))) :*: (S1 (MetaSel (Just "cueTrackSerialCopyManagement") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: (S1 (MetaSel (Just "cueTrackType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 CueTrackType) :*: S1 (MetaSel (Just "cueTrackIsrc") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Isrc))))) :*: ((S1 (MetaSel (Just "cueTrackTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CueText)) :*: (S1 (MetaSel (Just "cueTrackPerformer") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CueText)) :*: S1 (MetaSel (Just "cueTrackSongwriter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CueText)))) :*: ((S1 (MetaSel (Just "cueTrackPregap") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CueTime)) :*: S1 (MetaSel (Just "cueTrackPregapIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CueTime))) :*: (S1 (MetaSel (Just "cueTrackIndices") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (NonEmpty CueTime)) :*: S1 (MetaSel (Just "cueTrackPostgap") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CueTime)))))))

data CueTrackType Source #

Track datatype.

Constructors

CueTrackAudio

Audio/Music (2352).

CueTrackCdg

Karaoke CD+G (2448).

CueTrackMode1_2048

CD-ROM Mode1 data (cooked).

CueTrackMode1_2352

CD-ROM Mode1 data (raw).

CueTrackMode2_2336

CD-ROM XA Mode2 data.

CueTrackMode2_2352

CD-ROM XA Mode2 data.

CueTrackCdi2336

CD-I Mode2 data.

CueTrackCdi2352

CD-I Mode2 data.

Instances
Bounded CueTrackType Source # 
Instance details

Defined in Text.CueSheet.Types

Enum CueTrackType Source # 
Instance details

Defined in Text.CueSheet.Types

Eq CueTrackType Source # 
Instance details

Defined in Text.CueSheet.Types

Ord CueTrackType Source # 
Instance details

Defined in Text.CueSheet.Types

Read CueTrackType Source # 
Instance details

Defined in Text.CueSheet.Types

Show CueTrackType Source # 
Instance details

Defined in Text.CueSheet.Types

Generic CueTrackType Source # 
Instance details

Defined in Text.CueSheet.Types

Associated Types

type Rep CueTrackType :: * -> * #

Arbitrary CueTrackType Source # 
Instance details

Defined in Text.CueSheet.Types

type Rep CueTrackType Source # 
Instance details

Defined in Text.CueSheet.Types

type Rep CueTrackType = D1 (MetaData "CueTrackType" "Text.CueSheet.Types" "cue-sheet-2.0.0-6h3teGT0ahPIL9F1kK7yIy" False) (((C1 (MetaCons "CueTrackAudio" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CueTrackCdg" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "CueTrackMode1_2048" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CueTrackMode1_2352" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "CueTrackMode2_2336" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CueTrackMode2_2352" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "CueTrackCdi2336" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CueTrackCdi2352" PrefixI False) (U1 :: * -> *))))

newtype CueTime Source #

This datatype is used to indicate duration and position in time. It contains number of frames. There are 75 frames in one second.

Constructors

CueTime Natural 
Instances
Eq CueTime Source # 
Instance details

Defined in Text.CueSheet.Types

Methods

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

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

Ord CueTime Source # 
Instance details

Defined in Text.CueSheet.Types

Read CueTime Source # 
Instance details

Defined in Text.CueSheet.Types

Show CueTime Source # 
Instance details

Defined in Text.CueSheet.Types

Generic CueTime Source # 
Instance details

Defined in Text.CueSheet.Types

Associated Types

type Rep CueTime :: * -> * #

Methods

from :: CueTime -> Rep CueTime x #

to :: Rep CueTime x -> CueTime #

Arbitrary CueTime Source # 
Instance details

Defined in Text.CueSheet.Types

type Rep CueTime Source # 
Instance details

Defined in Text.CueSheet.Types

type Rep CueTime = D1 (MetaData "CueTime" "Text.CueSheet.Types" "cue-sheet-2.0.0-6h3teGT0ahPIL9F1kK7yIy" True) (C1 (MetaCons "CueTime" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Natural)))

fromMmSsFf Source #

Arguments

:: MonadThrow m 
=> Natural

Number of minutes, no limit here

-> Natural

Number of seconds, 0–59 inclusive

-> Natural

Number of frames, 0–74 inclusive

-> m CueTime

The result

Construct CueTime from minutes, seconds, and frames. There are 75 frames per second. If number of seconds or frames is invalid, InvalidSeconds or InvalidFrames will be thrown.

toMmSsFf :: CueTime -> (Natural, Natural, Natural) Source #

Get minutes, seconds, and frames from a CueTime value.

showMmSsFf :: CueTime -> Text Source #

Render representation of CueTime in mm:ss:ff format.

data Mcn Source #

Disc's Media Catalog Number (MCN), must be 13 characters long, all the characters must be numeric.

Instances
Eq Mcn Source # 
Instance details

Defined in Text.CueSheet.Types

Methods

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

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

Ord Mcn Source # 
Instance details

Defined in Text.CueSheet.Types

Methods

compare :: Mcn -> Mcn -> Ordering #

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

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

(>) :: Mcn -> Mcn -> Bool #

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

max :: Mcn -> Mcn -> Mcn #

min :: Mcn -> Mcn -> Mcn #

Show Mcn Source # 
Instance details

Defined in Text.CueSheet.Types

Methods

showsPrec :: Int -> Mcn -> ShowS #

show :: Mcn -> String #

showList :: [Mcn] -> ShowS #

Generic Mcn Source # 
Instance details

Defined in Text.CueSheet.Types

Associated Types

type Rep Mcn :: * -> * #

Methods

from :: Mcn -> Rep Mcn x #

to :: Rep Mcn x -> Mcn #

Arbitrary Mcn Source # 
Instance details

Defined in Text.CueSheet.Types

Methods

arbitrary :: Gen Mcn #

shrink :: Mcn -> [Mcn] #

type Rep Mcn Source # 
Instance details

Defined in Text.CueSheet.Types

type Rep Mcn = D1 (MetaData "Mcn" "Text.CueSheet.Types" "cue-sheet-2.0.0-6h3teGT0ahPIL9F1kK7yIy" True) (C1 (MetaCons "Mcn" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

mkMcn :: MonadThrow m => Text -> m Mcn Source #

Make a Mcn. If the provided Text value is not a valid MCN, throw the InvalidMcnException.

unMcn :: Mcn -> Text Source #

Get Text from Mcn.

data CueText Source #

A type for things like title or performer that should have length between 1 and 80 characters as per spec. We also demand that it does not contain " and newline characters, as it's not clear from the spec how to escape them properly.

Instances
Eq CueText Source # 
Instance details

Defined in Text.CueSheet.Types

Methods

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

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

Ord CueText Source # 
Instance details

Defined in Text.CueSheet.Types

Show CueText Source # 
Instance details

Defined in Text.CueSheet.Types

Generic CueText Source # 
Instance details

Defined in Text.CueSheet.Types

Associated Types

type Rep CueText :: * -> * #

Methods

from :: CueText -> Rep CueText x #

to :: Rep CueText x -> CueText #

Arbitrary CueText Source # 
Instance details

Defined in Text.CueSheet.Types

type Rep CueText Source # 
Instance details

Defined in Text.CueSheet.Types

type Rep CueText = D1 (MetaData "CueText" "Text.CueSheet.Types" "cue-sheet-2.0.0-6h3teGT0ahPIL9F1kK7yIy" True) (C1 (MetaCons "CueText" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

mkCueText :: MonadThrow m => Text -> m CueText Source #

Make a CueText. If the provided Text value is not a valid CUE text, throw the InvalidCueText exception.

data Isrc Source #

The track's International Standard Recording Code (ISRC). It must be 12 characters in length. The first five characters are alphanumeric, the last seven are numeric only.

Instances
Eq Isrc Source # 
Instance details

Defined in Text.CueSheet.Types

Methods

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

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

Ord Isrc Source # 
Instance details

Defined in Text.CueSheet.Types

Methods

compare :: Isrc -> Isrc -> Ordering #

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

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

(>) :: Isrc -> Isrc -> Bool #

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

max :: Isrc -> Isrc -> Isrc #

min :: Isrc -> Isrc -> Isrc #

Show Isrc Source # 
Instance details

Defined in Text.CueSheet.Types

Methods

showsPrec :: Int -> Isrc -> ShowS #

show :: Isrc -> String #

showList :: [Isrc] -> ShowS #

Generic Isrc Source # 
Instance details

Defined in Text.CueSheet.Types

Associated Types

type Rep Isrc :: * -> * #

Methods

from :: Isrc -> Rep Isrc x #

to :: Rep Isrc x -> Isrc #

Arbitrary Isrc Source # 
Instance details

Defined in Text.CueSheet.Types

Methods

arbitrary :: Gen Isrc #

shrink :: Isrc -> [Isrc] #

type Rep Isrc Source # 
Instance details

Defined in Text.CueSheet.Types

type Rep Isrc = D1 (MetaData "Isrc" "Text.CueSheet.Types" "cue-sheet-2.0.0-6h3teGT0ahPIL9F1kK7yIy" True) (C1 (MetaCons "Isrc" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

mkIsrc :: MonadThrow m => Text -> m Isrc Source #

Make an Isrc, if the provided Text value is not a valid ISRC, throw the InvalidIsrc exception.

unIsrc :: Isrc -> Text Source #

Get Text from Isrc.

data CueSheetException Source #

Exception type for the bad things that may happen while you use the library.

Constructors

InvalidSeconds Natural

The value is greater than 59 and thus is invalid for fromMmSsFf.

InvalidFrames Natural

The value is greater than 74 and thus is invalid for fromMmSsFf.

InvalidMcn Text

Provided text wasn't a correct media catalog number (MCN).

InvalidCueText Text

Provided text wasn't a valid CUE text.

InvalidIsrc Text

Provided text wasn't a valid ISRC.

Instances
Eq CueSheetException Source # 
Instance details

Defined in Text.CueSheet.Types

Ord CueSheetException Source # 
Instance details

Defined in Text.CueSheet.Types

Read CueSheetException Source # 
Instance details

Defined in Text.CueSheet.Types

Show CueSheetException Source # 
Instance details

Defined in Text.CueSheet.Types

Generic CueSheetException Source # 
Instance details

Defined in Text.CueSheet.Types

Associated Types

type Rep CueSheetException :: * -> * #

Exception CueSheetException Source # 
Instance details

Defined in Text.CueSheet.Types

type Rep CueSheetException Source # 
Instance details

Defined in Text.CueSheet.Types

Parsing

parseCueSheet Source #

Arguments

:: String

File name to include in error messages

-> ByteString

CUE sheet to parse as a lazy ByteString

-> Either (ParseErrorBundle ByteString Eec) CueSheet

ParseError or result

Parse a CUE sheet from a lazy ByteString.

data CueParserFailure Source #

The enumeration of all failures that may happen during running of parseCueSheet.

Constructors

CueParserTrivialError (Maybe (ErrorItem Word8)) (Set (ErrorItem Word8))

A wrapper for a trivial error

CueParserInvalidCatalog Text

We ran into an invalid media catalog number

CueParserInvalidCueText Text

We ran into an invalid text literal

CueParserTrackOutOfOrder

We spotted a track out of order

CueParserInvalidTrackIsrc Text

We ran into an invalid ISRC

CueParserInvalidSeconds Natural

We ran into an invalid number of seconds

CueParserInvalidFrames Natural

We ran into an invalid number of frames

CueParserTrackIndexOutOfOrder

We spotted a track index out of order

Instances
Eq CueParserFailure Source # 
Instance details

Defined in Text.CueSheet.Parser

Data CueParserFailure Source # 
Instance details

Defined in Text.CueSheet.Parser

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CueParserFailure -> c CueParserFailure #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CueParserFailure #

toConstr :: CueParserFailure -> Constr #

dataTypeOf :: CueParserFailure -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CueParserFailure) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CueParserFailure) #

gmapT :: (forall b. Data b => b -> b) -> CueParserFailure -> CueParserFailure #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CueParserFailure -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CueParserFailure -> r #

gmapQ :: (forall d. Data d => d -> u) -> CueParserFailure -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CueParserFailure -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CueParserFailure -> m CueParserFailure #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CueParserFailure -> m CueParserFailure #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CueParserFailure -> m CueParserFailure #

Ord CueParserFailure Source # 
Instance details

Defined in Text.CueSheet.Parser

Show CueParserFailure Source # 
Instance details

Defined in Text.CueSheet.Parser

Generic CueParserFailure Source # 
Instance details

Defined in Text.CueSheet.Parser

Associated Types

type Rep CueParserFailure :: * -> * #

ShowErrorComponent CueParserFailure Source # 
Instance details

Defined in Text.CueSheet.Parser

type Rep CueParserFailure Source # 
Instance details

Defined in Text.CueSheet.Parser

data Eec Source #

Extended error component with support for storing number of track declaration in which a parsing error has occurred.

Instances
Eq Eec Source # 
Instance details

Defined in Text.CueSheet.Parser

Methods

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

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

Data Eec Source # 
Instance details

Defined in Text.CueSheet.Parser

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Eec -> c Eec #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Eec #

toConstr :: Eec -> Constr #

dataTypeOf :: Eec -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Eec) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Eec) #

gmapT :: (forall b. Data b => b -> b) -> Eec -> Eec #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Eec -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Eec -> r #

gmapQ :: (forall d. Data d => d -> u) -> Eec -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Eec -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Eec -> m Eec #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Eec -> m Eec #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Eec -> m Eec #

Ord Eec Source # 
Instance details

Defined in Text.CueSheet.Parser

Methods

compare :: Eec -> Eec -> Ordering #

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

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

(>) :: Eec -> Eec -> Bool #

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

max :: Eec -> Eec -> Eec #

min :: Eec -> Eec -> Eec #

Show Eec Source # 
Instance details

Defined in Text.CueSheet.Parser

Methods

showsPrec :: Int -> Eec -> ShowS #

show :: Eec -> String #

showList :: [Eec] -> ShowS #

Generic Eec Source # 
Instance details

Defined in Text.CueSheet.Parser

Associated Types

type Rep Eec :: * -> * #

Methods

from :: Eec -> Rep Eec x #

to :: Rep Eec x -> Eec #

ShowErrorComponent Eec Source # 
Instance details

Defined in Text.CueSheet.Parser

type Rep Eec Source # 
Instance details

Defined in Text.CueSheet.Parser

Rendering

renderCueSheet Source #

Arguments

:: Bool

Use CRLF sequence as “end of line” separator

-> CueSheet

The CueSheet to render

-> ByteString

The result

Render a CUE sheet as a lazy ByteString. All Text values in the CueSheet will be UTF-8 encoded.