|
| OpenAFP.Types.Chunk | | Portability | non-portable (GHC-only) | | Stability | experimental | | Maintainer | audreyt@audreyt.org |
|
|
|
| Description |
| This module handles pre-parsed chunks in AFP files.
|
|
| Synopsis |
|
| type NStr = Buffer0 | | | type AStr = NStr | | | type ChunkWriter c = WriterT (ChunkQueue c) | | | type WriterStateIO v a = (Chunk c, MonadReader v m) => ChunkWriter c m a | | | _NStr :: NStr | | | packAStr :: AStr -> ByteString | | | fromAStr :: AStr -> String | | | toAStr :: String -> AStr | | | packNStr :: NStr -> ByteString | | | fromNStr :: NStr -> [N1] | | | toNStr :: [N1] -> NStr | | | newtype ChunkType = MkChunkType Int | | | typeInt :: TypeRep -> Int | | | chunkTypeOf :: Typeable a => a -> ChunkType | | | class (Show c, Typeable c, Buf (BufOf c), Enum (N c), Num (N c)) => Chunk c where | | | | class (Rec r, Chunk (ChunkOf r)) => RecChunk r where | | | | class (Rec a, Rec b, DataOf a ~ b, RecOf b ~ a) => RecData a b where | | | | (~~) :: (Chunk c, Typeable t) => c -> t -> Bool | | | (<~~) :: (Monad m, Chunk c, Typeable t, Rec r) => t -> [c] -> m r | | | (~~>) :: (Monad m, Chunk c, Typeable t, Rec r) => [c] -> t -> m r | | | (==>) :: (Chunk c, Monad m) => [c] -> [(ChunkType, c -> m [c])] -> m [c] | | | (<==) :: (Chunk c, Monad m) => [(ChunkType, c -> m [c])] -> [c] -> m [c] | | | (..>) :: (Chunk c, Monad m) => [c] -> [(ChunkType, c -> m [c])] -> m () | | | (<..) :: (Chunk c, Monad m) => [(ChunkType, c -> m [c])] -> [c] -> m () | | | processChunk :: (Monad m, Rec r, Chunk c) => r -> (r -> ChunkWriter c m a) -> c -> m [c] | | | inspectChunk :: (Monad m, Rec a, Chunk c) => a -> (a -> m t) -> c -> m [c] | | | push :: (Chunk c, Monad m, Rec a) => a -> ChunkWriter c m () | | | filterChunks :: (Monad m, RecChunk r, Chunk c) => r -> [(ChunkType, ChunkOf r -> ChunkWriter c m [ChunkOf r])] -> ChunkWriter c m () | | |
|
|
| Documentation |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| Constructors | | Instances | |
|
|
|
|
|
|
|
| The Chunk class represents non-parsed chunks, constructed from a
(ChunkType, Buffer) tuple.
| | | Associated Types | | | | Methods | | chunkApply :: N c -> c -> (forall a. Rec a => a -> x) -> x | Source |
| | | | | | | | | | | | | | | | | | | | | | | | |
| | Instances | |
|
|
|
| The RecChunk class unifies a Rec (parent) with its contained
chunk types (children).
| | | Associated Types | | | | Methods | | | Instances | |
|
|
|
| The RecData class unifies a Rec (parent) with its contained
Rec data type (children).
| | | Associated Types | | | | Methods | | | Instances | |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| Constructors | | ChunkQueue [a] | | | ChunkItem a | |
| Instances | |
|
|
| Produced by Haddock version 2.3.0 |