OpenAFP-1.4.3: IBM AFP document format parser and generator

Copyright(c) Audrey Tang 2004-2011
LicensePublicDomain
Maintaineraudreyt@audreyt.org
Stabilityexperimental
Portabilitynon-portable (GHC-only)
Safe HaskellNone
LanguageHaskell98

OpenAFP.Types.Chunk

Contents

Description

This module handles pre-parsed "chunks" in AFP files.

Synopsis

Documentation

type AStr = NStr Source #

type WriterStateIO v a = forall c m. (Chunk c, MonadReader v m) => ChunkWriter c m a Source #

class (Show c, Typeable c, Buf (BufOf c), Enum (N c), Num (N c)) => Chunk c where Source #

The Chunk class represents non-parsed chunks, constructed from a (ChunkType, Buffer) tuple.

Minimal complete definition

chunkApply, chunkDecon, chunkTypeLookup

Associated Types

type N c Source #

type BufOf c Source #

Methods

chunkApply :: N c -> c -> (forall a. Rec a => a -> x) -> x Source #

mkChunk :: N c -> BufOf c -> c Source #

chunkCon :: (N c, BufOf c) -> c Source #

chunkDecon :: c -> (N c, BufOf c) Source #

chunkType :: c -> ChunkType Source #

chunkTypeLookup :: c -> N c -> ChunkType Source #

packChunk :: c -> PStringLen Source #

chunkMapFiltersM_ :: Monad m => c -> [(ChunkType, c -> m [c])] -> m () Source #

chunkMapFiltersM :: Monad m => c -> [(ChunkType, c -> m [c])] -> m [c] Source #

chunksMapFiltersM :: Monad m => [c] -> [(ChunkType, c -> m [c])] -> m [c] Source #

chunksMapFiltersM_ :: Monad m => [c] -> [(ChunkType, c -> m [c])] -> m () Source #

decodeChunk :: Binary (Record r) => c -> r Source #

encodeChunk :: (Binary r, Storable r, Rec r) => r -> c Source #

class (Rec r, Chunk (ChunkOf r)) => RecChunk r where Source #

The RecChunk class unifies a Rec (parent) with its contained chunk types (children).

Associated Types

type ChunkOf r Source #

Methods

readChunks :: r -> [ChunkOf r] Source #

writeChunks :: Monad m => r -> m [ChunkOf r] -> m r Source #

class (Rec a, Rec b) => RecData a b where Source #

The RecData class unifies a Rec (parent) with its contained Rec data type (children).

Associated Types

type DataOf a Source #

type RecOf b Source #

Methods

readData :: (DataOf a ~ b, RecOf b ~ a) => a -> [Record b] Source #

writeData :: (DataOf a ~ b, RecOf b ~ a) => a -> [Record b] -> a Source #

(~~) :: (Chunk c, Typeable t) => c -> t -> Bool infixl 4 Source #

(<~~) :: (Monad m, Chunk c, Typeable t, Rec r) => t -> [c] -> m r infixl 4 Source #

(~~>) :: (Monad m, Chunk c, Typeable t, Rec r) => [c] -> t -> m r infixl 4 Source #

(==>) :: (Chunk c, Monad m) => [c] -> [(ChunkType, c -> m [c])] -> m [c] infixl 4 Source #

(<==) :: (Chunk c, Monad m) => [(ChunkType, c -> m [c])] -> [c] -> m [c] infixl 4 Source #

(..>) :: (Chunk c, Monad m) => [c] -> [(ChunkType, c -> m [c])] -> m () infixl 4 Source #

(<..) :: (Chunk c, Monad m) => [(ChunkType, c -> m [c])] -> [c] -> m () infixl 4 Source #

(===) :: (Chunk c, Rec r, Monad m) => r -> (r -> ChunkWriter c m a) -> (ChunkType, c -> m [c]) infixr 4 Source #

processChunk :: (Monad m, Rec r, Chunk c) => r -> (r -> ChunkWriter c m a) -> c -> m [c] Source #

(...) :: (Chunk c, Rec a, Monad m) => a -> (a -> m t) -> (ChunkType, c -> m [c]) infixr 4 Source #

(....) :: (Monad (t m), Monad m, MonadTrans t, Chunk c, Rec a) => a -> (a -> m t1) -> (ChunkType, c -> t m [c]) infixr 4 Source #

(.....) :: (Monad (t m), Monad (t1 (t m)), Monad m, MonadTrans t, MonadTrans t1, Chunk c, Rec a) => a -> (a -> m t2) -> (ChunkType, c -> t1 (t m) [c]) infixr 4 Source #

inspectChunk :: (Monad m, Rec a, Chunk c) => a -> (a -> m t) -> c -> m [c] Source #

push :: (Chunk c, Monad m, Rec a) => a -> ChunkWriter c m () Source #

filterChunks :: (Monad m, RecChunk r, Chunk c) => r -> [(ChunkType, ChunkOf r -> ChunkWriter c m [ChunkOf r])] -> ChunkWriter c m () Source #

data ChunkQueue a Source #

Constructors

ChunkQueue [a] 
ChunkItem a 

Orphan instances

Storable NStr Source # 

Methods

sizeOf :: NStr -> Int #

alignment :: NStr -> Int #

peekElemOff :: Ptr NStr -> Int -> IO NStr #

pokeElemOff :: Ptr NStr -> Int -> NStr -> IO () #

peekByteOff :: Ptr b -> Int -> IO NStr #

pokeByteOff :: Ptr b -> Int -> NStr -> IO () #

peek :: Ptr NStr -> IO NStr #

poke :: Ptr NStr -> NStr -> IO () #

(Rec a, Binary a) => Storable [a] Source # 

Methods

sizeOf :: [a] -> Int #

alignment :: [a] -> Int #

peekElemOff :: Ptr [a] -> Int -> IO [a] #

pokeElemOff :: Ptr [a] -> Int -> [a] -> IO () #

peekByteOff :: Ptr b -> Int -> IO [a] #

pokeByteOff :: Ptr b -> Int -> [a] -> IO () #

peek :: Ptr [a] -> IO [a] #

poke :: Ptr [a] -> [a] -> IO () #