pantry-0.7.1: Content addressable Haskell package management
Safe HaskellSafe-Inferred
LanguageHaskell2010

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

data Bytes8 Source #

Instances

Instances details
Data Bytes8 Source # 
Instance details

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 # 
Instance details

Defined in Pantry.Internal.StaticBytes

Associated Types

type Rep Bytes8 :: Type -> Type #

Methods

from :: Bytes8 -> Rep Bytes8 x #

to :: Rep Bytes8 x -> Bytes8 #

Show Bytes8 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

NFData Bytes8 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

rnf :: Bytes8 -> () #

Eq Bytes8 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

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

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

Ord Bytes8 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Hashable Bytes8 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

hashWithSalt :: Int -> Bytes8 -> Int #

hash :: Bytes8 -> Int #

ByteArrayAccess Bytes8 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

length :: Bytes8 -> Int #

withByteArray :: Bytes8 -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: Bytes8 -> Ptr p -> IO () #

StaticBytes Bytes8 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

lengthS :: proxy Bytes8 -> Int

toWordsS :: Bytes8 -> [Word64] -> [Word64]

usePeekS :: Int -> (Int -> IO Word64) -> IO Bytes8

type Rep Bytes8 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

type Rep Bytes8 = D1 ('MetaData "Bytes8" "Pantry.Internal.StaticBytes" "pantry-0.7.1-19D72Scd5zgIQ1LADqS6TJ" 'True) (C1 ('MetaCons "Bytes8" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

data Bytes16 Source #

Instances

Instances details
Data Bytes16 Source # 
Instance details

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 # 
Instance details

Defined in Pantry.Internal.StaticBytes

Associated Types

type Rep Bytes16 :: Type -> Type #

Methods

from :: Bytes16 -> Rep Bytes16 x #

to :: Rep Bytes16 x -> Bytes16 #

Show Bytes16 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

NFData Bytes16 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

rnf :: Bytes16 -> () #

Eq Bytes16 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

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

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

Ord Bytes16 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Hashable Bytes16 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

hashWithSalt :: Int -> Bytes16 -> Int #

hash :: Bytes16 -> Int #

ByteArrayAccess Bytes16 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

length :: Bytes16 -> Int #

withByteArray :: Bytes16 -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: Bytes16 -> Ptr p -> IO () #

StaticBytes Bytes16 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

lengthS :: proxy Bytes16 -> Int

toWordsS :: Bytes16 -> [Word64] -> [Word64]

usePeekS :: Int -> (Int -> IO Word64) -> IO Bytes16

type Rep Bytes16 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

type Rep Bytes16 = D1 ('MetaData "Bytes16" "Pantry.Internal.StaticBytes" "pantry-0.7.1-19D72Scd5zgIQ1LADqS6TJ" '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)))

data Bytes32 Source #

Instances

Instances details
Data Bytes32 Source # 
Instance details

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 # 
Instance details

Defined in Pantry.Internal.StaticBytes

Associated Types

type Rep Bytes32 :: Type -> Type #

Methods

from :: Bytes32 -> Rep Bytes32 x #

to :: Rep Bytes32 x -> Bytes32 #

Show Bytes32 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

NFData Bytes32 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

rnf :: Bytes32 -> () #

Eq Bytes32 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

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

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

Ord Bytes32 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Hashable Bytes32 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

hashWithSalt :: Int -> Bytes32 -> Int #

hash :: Bytes32 -> Int #

ByteArrayAccess Bytes32 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

length :: Bytes32 -> Int #

withByteArray :: Bytes32 -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: Bytes32 -> Ptr p -> IO () #

StaticBytes Bytes32 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

lengthS :: proxy Bytes32 -> Int

toWordsS :: Bytes32 -> [Word64] -> [Word64]

usePeekS :: Int -> (Int -> IO Word64) -> IO Bytes32

type Rep Bytes32 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

type Rep Bytes32 = D1 ('MetaData "Bytes32" "Pantry.Internal.StaticBytes" "pantry-0.7.1-19D72Scd5zgIQ1LADqS6TJ" '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)))

data Bytes64 Source #

Instances

Instances details
Data Bytes64 Source # 
Instance details

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 # 
Instance details

Defined in Pantry.Internal.StaticBytes

Associated Types

type Rep Bytes64 :: Type -> Type #

Methods

from :: Bytes64 -> Rep Bytes64 x #

to :: Rep Bytes64 x -> Bytes64 #

Show Bytes64 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

NFData Bytes64 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

rnf :: Bytes64 -> () #

Eq Bytes64 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

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

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

Ord Bytes64 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Hashable Bytes64 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

hashWithSalt :: Int -> Bytes64 -> Int #

hash :: Bytes64 -> Int #

ByteArrayAccess Bytes64 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

length :: Bytes64 -> Int #

withByteArray :: Bytes64 -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: Bytes64 -> Ptr p -> IO () #

StaticBytes Bytes64 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

lengthS :: proxy Bytes64 -> Int

toWordsS :: Bytes64 -> [Word64] -> [Word64]

usePeekS :: Int -> (Int -> IO Word64) -> IO Bytes64

type Rep Bytes64 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

type Rep Bytes64 = D1 ('MetaData "Bytes64" "Pantry.Internal.StaticBytes" "pantry-0.7.1-19D72Scd5zgIQ1LADqS6TJ" '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)))

data Bytes128 Source #

Instances

Instances details
Data Bytes128 Source # 
Instance details

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 # 
Instance details

Defined in Pantry.Internal.StaticBytes

Associated Types

type Rep Bytes128 :: Type -> Type #

Methods

from :: Bytes128 -> Rep Bytes128 x #

to :: Rep Bytes128 x -> Bytes128 #

Show Bytes128 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

NFData Bytes128 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

rnf :: Bytes128 -> () #

Eq Bytes128 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Ord Bytes128 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Hashable Bytes128 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

hashWithSalt :: Int -> Bytes128 -> Int #

hash :: Bytes128 -> Int #

ByteArrayAccess Bytes128 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

length :: Bytes128 -> Int #

withByteArray :: Bytes128 -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: Bytes128 -> Ptr p -> IO () #

StaticBytes Bytes128 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

lengthS :: proxy Bytes128 -> Int

toWordsS :: Bytes128 -> [Word64] -> [Word64]

usePeekS :: Int -> (Int -> IO Word64) -> IO Bytes128

type Rep Bytes128 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

type Rep Bytes128 = D1 ('MetaData "Bytes128" "Pantry.Internal.StaticBytes" "pantry-0.7.1-19D72Scd5zgIQ1LADqS6TJ" '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

Instances details
DynamicBytes ByteString Source # 
Instance details

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 # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

lengthD :: Vector word8 -> Int

withPeekD :: Vector word8 -> ((Int -> IO Word64) -> IO a) -> IO a

fromWordsD :: Int -> [Word64] -> Vector word8

word8 ~ Word8 => DynamicBytes (Vector word8) Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

lengthD :: Vector word8 -> Int

withPeekD :: Vector word8 -> ((Int -> IO Word64) -> IO a) -> IO a

fromWordsD :: Int -> [Word64] -> Vector word8

word8 ~ Word8 => DynamicBytes (Vector word8) Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

lengthD :: Vector word8 -> Int

withPeekD :: Vector word8 -> ((Int -> IO Word64) -> IO a) -> IO a

fromWordsD :: Int -> [Word64] -> Vector word8

class StaticBytes sbytes Source #

Minimal complete definition

lengthS, toWordsS, usePeekS

Instances

Instances details
StaticBytes Bytes128 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

lengthS :: proxy Bytes128 -> Int

toWordsS :: Bytes128 -> [Word64] -> [Word64]

usePeekS :: Int -> (Int -> IO Word64) -> IO Bytes128

StaticBytes Bytes16 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

lengthS :: proxy Bytes16 -> Int

toWordsS :: Bytes16 -> [Word64] -> [Word64]

usePeekS :: Int -> (Int -> IO Word64) -> IO Bytes16

StaticBytes Bytes32 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

lengthS :: proxy Bytes32 -> Int

toWordsS :: Bytes32 -> [Word64] -> [Word64]

usePeekS :: Int -> (Int -> IO Word64) -> IO Bytes32

StaticBytes Bytes64 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

lengthS :: proxy Bytes64 -> Int

toWordsS :: Bytes64 -> [Word64] -> [Word64]

usePeekS :: Int -> (Int -> IO Word64) -> IO Bytes64

StaticBytes Bytes8 Source # 
Instance details

Defined in Pantry.Internal.StaticBytes

Methods

lengthS :: proxy Bytes8 -> Int

toWordsS :: Bytes8 -> [Word64] -> [Word64]

usePeekS :: Int -> (Int -> IO Word64) -> IO Bytes8

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 #