idiii-0.1.3.3: ID3v2 (tagging standard for MP3 files) library

Safe HaskellNone

ID3.Parser.General

Description

This module contain different general parsers.

Synopsis

Documentation

type Token = Word8Source

Just a synonim for one item of input stream

data St Source

Parsers state

Constructors

State 

Fields

id3TagVersion :: TagVersion
 
headerFlags :: TagFlags

flags from tag's header

tagPos :: Integer

current position in tag , frFlags :: [Bool]} -- ^ current frame flags

curSize :: Integer

current frame size

Instances

posUpdate :: (Integer -> Integer) -> TagParser ()Source

Updates tagPos with given function.

posSet :: Integer -> TagParser ()Source

Sets tagPos with given value.

posDec :: TagParser ()Source

Decrements tagPos.

posInc :: TagParser ()Source

Incremets tagPos.

sizeUpdate :: (Integer -> Integer) -> TagParser ()Source

Updates curSize with given function.

sizeSet :: Integer -> TagParser ()Source

Sets curSize with given value.

sizeDec :: TagParser ()Source

Decrements curSize.

ifSize :: TagParser [a] -> TagParser [a]Source

Wrapper for reiterative parsers. Mnemonic: if curSize > 0 then continue else stop

withSize :: TagParser b -> TagParser bSource

Wrapper for atomic parsers. Increases tagPos and decreases curSize.

many' :: TagParser a -> TagParser [a]Source

many' p parses a list of elements with individual parser p. Cannot fail, since an empty list is a valid return value. Unlike default many, stops if curSize became 0.

many1' :: TagParser a -> TagParser [a]Source

Parse a non-empty list of items.

manyTill' :: TagParser a -> TagParser z -> TagParser [a]Source

manyTill' p end parses a possibly-empty sequence of p's, terminated by a end.

manyTill1' :: TagParser a -> TagParser z -> TagParser [a]Source

'manyTill1\' p end' parses a non-empty sequence of p's, terminated by a end.

sepBy' :: TagParser a -> TagParser sep -> TagParser [a]Source

Parse a list of items separated by discarded junk.

sepBy1' :: TagParser a -> TagParser sep -> TagParser [a]Source

Parse a non-empty list of items separated by discarded junk.

count :: (Num n, Eq n) => n -> TagParser a -> TagParser [a]Source

'count n p' parses a precise number of items, n, using the parser p, in sequence.

count' :: (Num n, Eq n) => n -> TagParser a -> TagParser [a]Source

count n p' parses a precise number of items, n, using the parser p, in sequence.

countSepBy' :: (Num n, Eq n) => n -> TagParser a -> TagParser sep -> TagParser [a]Source

Hybrid of count and 'sepBy\''

parseUntilWord8Null :: TagParser [Token]Source

Parses one value (as [Token]) till termination symbol

parseEncoding :: TagParser CharEncodingSource

Parses a character-encoding code, a one-byte value that should be 0, 1, 2, or 3

parseString :: CharEncoding -> TagParser StringSource

Parses one value and returns it as a String

parseNumber :: TagParser IntegerSource

Parses one value and returns it as a Integer

parseLanguage :: TagParser StringSource

Parses 3 bytes of language value (as a String) and returns a pair (Language, value)

parsers :: [TagParser a] -> TagParser [a]Source

Takes a list of Parsers and applies them by turns.

word8 :: Token -> TagParser TokenSource

Parses given Token.

word8s :: [Token] -> TagParser [Token]Source

Parses given list of Tokens.

byteString :: ByteString -> TagParser ByteStringSource

Parses given ByteString.

string :: String -> TagParser ByteStringSource

Same as byteString but argument is simple String.

upper :: TagParser TokenSource

Parses upper-case letters (as Token)

digit :: TagParser TokenSource

Parses digit-symbol (as Token)

parseSize :: Integer -> Bool -> TagParser SizeSource

'parseSize n unsynchDecode' parses n bytes, doing decoding of unsynchronized data when unsynchDecode is True, and returns the represented Integer value.