Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Pantry.Internal.StaticBytes
Description
This is an unstable API, exposed only for testing. Relying on this may break your code! Caveat emptor.
This module can (and perhaps should) be separate into its own package, it's generally useful.
Documentation
Instances
Data Bytes8 Source # | |
Defined in Pantry.Internal.StaticBytes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bytes8 -> c Bytes8 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bytes8 # toConstr :: Bytes8 -> Constr # dataTypeOf :: Bytes8 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bytes8) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes8) # gmapT :: (forall b. Data b => b -> b) -> Bytes8 -> Bytes8 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bytes8 -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bytes8 -> r # gmapQ :: (forall d. Data d => d -> u) -> Bytes8 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bytes8 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bytes8 -> m Bytes8 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes8 -> m Bytes8 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes8 -> m Bytes8 # | |
Generic Bytes8 Source # | |
Show Bytes8 Source # | |
NFData Bytes8 Source # | |
Defined in Pantry.Internal.StaticBytes | |
Eq Bytes8 Source # | |
Ord Bytes8 Source # | |
Hashable Bytes8 Source # | |
Defined in Pantry.Internal.StaticBytes | |
ByteArrayAccess Bytes8 Source # | |
StaticBytes Bytes8 Source # | |
type Rep Bytes8 Source # | |
Defined in Pantry.Internal.StaticBytes |
Instances
Data Bytes16 Source # | |
Defined in Pantry.Internal.StaticBytes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bytes16 -> c Bytes16 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bytes16 # toConstr :: Bytes16 -> Constr # dataTypeOf :: Bytes16 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bytes16) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes16) # gmapT :: (forall b. Data b => b -> b) -> Bytes16 -> Bytes16 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bytes16 -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bytes16 -> r # gmapQ :: (forall d. Data d => d -> u) -> Bytes16 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bytes16 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bytes16 -> m Bytes16 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes16 -> m Bytes16 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes16 -> m Bytes16 # | |
Generic Bytes16 Source # | |
Show Bytes16 Source # | |
NFData Bytes16 Source # | |
Defined in Pantry.Internal.StaticBytes | |
Eq Bytes16 Source # | |
Ord Bytes16 Source # | |
Defined in Pantry.Internal.StaticBytes | |
Hashable Bytes16 Source # | |
Defined in Pantry.Internal.StaticBytes | |
ByteArrayAccess Bytes16 Source # | |
StaticBytes Bytes16 Source # | |
type Rep Bytes16 Source # | |
Defined in Pantry.Internal.StaticBytes type Rep Bytes16 = D1 ('MetaData "Bytes16" "Pantry.Internal.StaticBytes" "pantry-0.8.1-5JB7pN50XjHtfNeoj5rES" 'False) (C1 ('MetaCons "Bytes16" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bytes8) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bytes8))) |
Instances
Data Bytes32 Source # | |
Defined in Pantry.Internal.StaticBytes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bytes32 -> c Bytes32 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bytes32 # toConstr :: Bytes32 -> Constr # dataTypeOf :: Bytes32 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bytes32) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes32) # gmapT :: (forall b. Data b => b -> b) -> Bytes32 -> Bytes32 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bytes32 -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bytes32 -> r # gmapQ :: (forall d. Data d => d -> u) -> Bytes32 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bytes32 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bytes32 -> m Bytes32 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes32 -> m Bytes32 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes32 -> m Bytes32 # | |
Generic Bytes32 Source # | |
Show Bytes32 Source # | |
NFData Bytes32 Source # | |
Defined in Pantry.Internal.StaticBytes | |
Eq Bytes32 Source # | |
Ord Bytes32 Source # | |
Defined in Pantry.Internal.StaticBytes | |
Hashable Bytes32 Source # | |
Defined in Pantry.Internal.StaticBytes | |
ByteArrayAccess Bytes32 Source # | |
StaticBytes Bytes32 Source # | |
type Rep Bytes32 Source # | |
Defined in Pantry.Internal.StaticBytes type Rep Bytes32 = D1 ('MetaData "Bytes32" "Pantry.Internal.StaticBytes" "pantry-0.8.1-5JB7pN50XjHtfNeoj5rES" 'False) (C1 ('MetaCons "Bytes32" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bytes16) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bytes16))) |
Instances
Data Bytes64 Source # | |
Defined in Pantry.Internal.StaticBytes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bytes64 -> c Bytes64 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bytes64 # toConstr :: Bytes64 -> Constr # dataTypeOf :: Bytes64 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bytes64) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes64) # gmapT :: (forall b. Data b => b -> b) -> Bytes64 -> Bytes64 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bytes64 -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bytes64 -> r # gmapQ :: (forall d. Data d => d -> u) -> Bytes64 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bytes64 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bytes64 -> m Bytes64 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes64 -> m Bytes64 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes64 -> m Bytes64 # | |
Generic Bytes64 Source # | |
Show Bytes64 Source # | |
NFData Bytes64 Source # | |
Defined in Pantry.Internal.StaticBytes | |
Eq Bytes64 Source # | |
Ord Bytes64 Source # | |
Defined in Pantry.Internal.StaticBytes | |
Hashable Bytes64 Source # | |
Defined in Pantry.Internal.StaticBytes | |
ByteArrayAccess Bytes64 Source # | |
StaticBytes Bytes64 Source # | |
type Rep Bytes64 Source # | |
Defined in Pantry.Internal.StaticBytes type Rep Bytes64 = D1 ('MetaData "Bytes64" "Pantry.Internal.StaticBytes" "pantry-0.8.1-5JB7pN50XjHtfNeoj5rES" 'False) (C1 ('MetaCons "Bytes64" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bytes32) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bytes32))) |
Instances
Data Bytes128 Source # | |
Defined in Pantry.Internal.StaticBytes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bytes128 -> c Bytes128 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bytes128 # toConstr :: Bytes128 -> Constr # dataTypeOf :: Bytes128 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bytes128) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes128) # gmapT :: (forall b. Data b => b -> b) -> Bytes128 -> Bytes128 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bytes128 -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bytes128 -> r # gmapQ :: (forall d. Data d => d -> u) -> Bytes128 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bytes128 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bytes128 -> m Bytes128 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes128 -> m Bytes128 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes128 -> m Bytes128 # | |
Generic Bytes128 Source # | |
Show Bytes128 Source # | |
NFData Bytes128 Source # | |
Defined in Pantry.Internal.StaticBytes | |
Eq Bytes128 Source # | |
Ord Bytes128 Source # | |
Defined in Pantry.Internal.StaticBytes | |
Hashable Bytes128 Source # | |
Defined in Pantry.Internal.StaticBytes | |
ByteArrayAccess Bytes128 Source # | |
StaticBytes Bytes128 Source # | |
type Rep Bytes128 Source # | |
Defined in Pantry.Internal.StaticBytes type Rep Bytes128 = D1 ('MetaData "Bytes128" "Pantry.Internal.StaticBytes" "pantry-0.8.1-5JB7pN50XjHtfNeoj5rES" 'False) (C1 ('MetaCons "Bytes128" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bytes64) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bytes64))) |
class DynamicBytes dbytes Source #
Minimal complete definition
lengthD, withPeekD, fromWordsD
Instances
DynamicBytes ByteString Source # | |
Defined in Pantry.Internal.StaticBytes Methods lengthD :: ByteString -> Int withPeekD :: ByteString -> ((Int -> IO Word64) -> IO a) -> IO a fromWordsD :: Int -> [Word64] -> ByteString | |
word8 ~ Word8 => DynamicBytes (Vector word8) Source # | |
word8 ~ Word8 => DynamicBytes (Vector word8) Source # | |
word8 ~ Word8 => DynamicBytes (Vector word8) Source # | |
class StaticBytes sbytes Source #
Minimal complete definition
lengthS, toWordsS, usePeekS
data StaticBytesException Source #
Constructors
NotEnoughBytes | |
TooManyBytes |
Instances
Exception StaticBytesException Source # | |
Defined in Pantry.Internal.StaticBytes Methods toException :: StaticBytesException -> SomeException # fromException :: SomeException -> Maybe StaticBytesException # | |
Show StaticBytesException Source # | |
Defined in Pantry.Internal.StaticBytes Methods showsPrec :: Int -> StaticBytesException -> ShowS # show :: StaticBytesException -> String # showList :: [StaticBytesException] -> ShowS # | |
Eq StaticBytesException Source # | |
Defined in Pantry.Internal.StaticBytes Methods (==) :: StaticBytesException -> StaticBytesException -> Bool # (/=) :: StaticBytesException -> StaticBytesException -> Bool # |
toStaticExact :: forall dbytes sbytes. (DynamicBytes dbytes, StaticBytes sbytes) => dbytes -> Either StaticBytesException sbytes Source #
toStaticPad :: forall dbytes sbytes. (DynamicBytes dbytes, StaticBytes sbytes) => dbytes -> Either StaticBytesException sbytes Source #
toStaticTruncate :: forall dbytes sbytes. (DynamicBytes dbytes, StaticBytes sbytes) => dbytes -> Either StaticBytesException sbytes Source #
toStaticPadTruncate :: (DynamicBytes dbytes, StaticBytes sbytes) => dbytes -> sbytes Source #
fromStatic :: forall dbytes sbytes. (DynamicBytes dbytes, StaticBytes sbytes) => sbytes -> dbytes Source #