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

Copyright© 2016 Mark Karpov
LicenseBSD 3 clause
MaintainerMark Karpov <markkarpov@openmailbox.org>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.CueSheet.Parser

Description

The modules contains just 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 parsec as a lazy ByteString

-> Either (ParseError Char Eec) CueSheet

ParseError or result

Parse a CUE sheet from a lazy ByteString.

data CueParserFailure Source #

Enumeration of all failures that may happen during run of parseCueSheet.

Instances

Eq CueParserFailure Source # 
Data CueParserFailure Source # 

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 # 
Show CueParserFailure Source # 
Generic CueParserFailure Source # 
ShowErrorComponent CueParserFailure Source # 
type Rep CueParserFailure Source # 
type Rep CueParserFailure = D1 (MetaData "CueParserFailure" "Text.CueSheet.Parser" "cue-sheet-0.1.0-EXRuIcDxl2p6S6r2zlU6RS" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CueParserFail" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) (C1 (MetaCons "CueParserIndentation" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Ordering)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pos)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pos)))))) ((:+:) (C1 (MetaCons "CueParserInvalidCatalog" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) (C1 (MetaCons "CueParserInvalidCueText" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))) ((:+:) ((:+:) (C1 (MetaCons "CueParserTrackOutOfOrder" PrefixI False) U1) (C1 (MetaCons "CueParserInvalidTrackIsrc" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))) ((:+:) (C1 (MetaCons "CueParserInvalidSeconds" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Natural))) ((:+:) (C1 (MetaCons "CueParserInvalidFrames" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Natural))) (C1 (MetaCons "CueParserTrackIndexOutOfOrder" PrefixI False) U1)))))

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 # 

Methods

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

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

Data Eec Source # 

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 # 

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 # 

Methods

showsPrec :: Int -> Eec -> ShowS #

show :: Eec -> String #

showList :: [Eec] -> ShowS #

Generic Eec Source # 

Associated Types

type Rep Eec :: * -> * #

Methods

from :: Eec -> Rep Eec x #

to :: Rep Eec x -> Eec #

ErrorComponent Eec Source # 
ShowErrorComponent Eec Source # 
type Rep Eec Source #