cue-sheet-2.0.2: Support for construction, rendering, and parsing of CUE sheets
Copyright© 2016–present Mark Karpov
LicenseBSD 3 clause
MaintainerMark Karpov <markkarpov92@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.CueSheet.Parser

Description

The modules contains a CUE sheet parser. You probably want to import Text.CueSheet instead.

Synopsis

Documentation

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

Instances details
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 :: forall r r'. (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 :: Type -> Type #

ShowErrorComponent CueParserFailure Source # 
Instance details

Defined in Text.CueSheet.Parser

type Rep CueParserFailure Source # 
Instance details

Defined in Text.CueSheet.Parser

type Rep CueParserFailure = D1 ('MetaData "CueParserFailure" "Text.CueSheet.Parser" "cue-sheet-2.0.2-GGixdMe9eW2IdNm87otXvp" 'False) (((C1 ('MetaCons "CueParserTrivialError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ErrorItem Word8))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set (ErrorItem Word8)))) :+: C1 ('MetaCons "CueParserInvalidCatalog" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :+: (C1 ('MetaCons "CueParserInvalidCueText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "CueParserTrackOutOfOrder" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CueParserInvalidTrackIsrc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "CueParserInvalidSeconds" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural))) :+: (C1 ('MetaCons "CueParserInvalidFrames" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural)) :+: C1 ('MetaCons "CueParserTrackIndexOutOfOrder" 'PrefixI 'False) (U1 :: Type -> Type))))

data Eec Source #

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

Instances

Instances details
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 :: forall r r'. (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 :: Type -> Type #

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

type Rep Eec = D1 ('MetaData "Eec" "Text.CueSheet.Parser" "cue-sheet-2.0.2-GGixdMe9eW2IdNm87otXvp" 'False) (C1 ('MetaCons "Eec" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CueParserFailure)))