stack-1.7.1: The Haskell Tool Stack

Safe HaskellNone
LanguageHaskell2010

Stack.StaticBytes

Documentation

data Bytes8 Source #

Instances

Eq Bytes8 Source # 

Methods

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

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

Data Bytes8 Source # 

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 :: (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 #

Ord Bytes8 Source # 
Show Bytes8 Source # 
Generic Bytes8 Source # 

Associated Types

type Rep Bytes8 :: * -> * #

Methods

from :: Bytes8 -> Rep Bytes8 x #

to :: Rep Bytes8 x -> Bytes8 #

NFData Bytes8 Source # 

Methods

rnf :: Bytes8 -> () #

Hashable Bytes8 Source # 

Methods

hashWithSalt :: Int -> Bytes8 -> Int #

hash :: Bytes8 -> Int #

ByteArrayAccess Bytes8 Source # 

Methods

length :: Bytes8 -> Int #

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

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

Store Bytes8 Source # 

Methods

size :: Size Bytes8 #

poke :: Bytes8 -> Poke () #

peek :: Peek Bytes8 #

StaticBytes Bytes8 Source # 

Methods

lengthS :: proxy Bytes8 -> Int

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

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

type Rep Bytes8 Source # 
type Rep Bytes8 = D1 * (MetaData "Bytes8" "Stack.StaticBytes" "stack-1.7.1-8x9NSKj6gz3B3M9RWkyZVt" True) (C1 * (MetaCons "Bytes8" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word64)))

data Bytes16 Source #

Instances

Eq Bytes16 Source # 

Methods

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

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

Data Bytes16 Source # 

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 :: (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 #

Ord Bytes16 Source # 
Show Bytes16 Source # 
Generic Bytes16 Source # 

Associated Types

type Rep Bytes16 :: * -> * #

Methods

from :: Bytes16 -> Rep Bytes16 x #

to :: Rep Bytes16 x -> Bytes16 #

NFData Bytes16 Source # 

Methods

rnf :: Bytes16 -> () #

Hashable Bytes16 Source # 

Methods

hashWithSalt :: Int -> Bytes16 -> Int #

hash :: Bytes16 -> Int #

ByteArrayAccess Bytes16 Source # 

Methods

length :: Bytes16 -> Int #

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

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

Store Bytes16 Source # 
StaticBytes Bytes16 Source # 

Methods

lengthS :: proxy Bytes16 -> Int

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

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

type Rep Bytes16 Source # 
type Rep Bytes16 = D1 * (MetaData "Bytes16" "Stack.StaticBytes" "stack-1.7.1-8x9NSKj6gz3B3M9RWkyZVt" False) (C1 * (MetaCons "Bytes16" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bytes8)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bytes8))))

data Bytes32 Source #

Instances

Eq Bytes32 Source # 

Methods

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

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

Data Bytes32 Source # 

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 :: (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 #

Ord Bytes32 Source # 
Show Bytes32 Source # 
Generic Bytes32 Source # 

Associated Types

type Rep Bytes32 :: * -> * #

Methods

from :: Bytes32 -> Rep Bytes32 x #

to :: Rep Bytes32 x -> Bytes32 #

NFData Bytes32 Source # 

Methods

rnf :: Bytes32 -> () #

Hashable Bytes32 Source # 

Methods

hashWithSalt :: Int -> Bytes32 -> Int #

hash :: Bytes32 -> Int #

ByteArrayAccess Bytes32 Source # 

Methods

length :: Bytes32 -> Int #

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

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

Store Bytes32 Source # 
StaticBytes Bytes32 Source # 

Methods

lengthS :: proxy Bytes32 -> Int

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

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

type Rep Bytes32 Source # 

data Bytes64 Source #

Instances

Eq Bytes64 Source # 

Methods

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

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

Data Bytes64 Source # 

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 :: (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 #

Ord Bytes64 Source # 
Show Bytes64 Source # 
Generic Bytes64 Source # 

Associated Types

type Rep Bytes64 :: * -> * #

Methods

from :: Bytes64 -> Rep Bytes64 x #

to :: Rep Bytes64 x -> Bytes64 #

NFData Bytes64 Source # 

Methods

rnf :: Bytes64 -> () #

Hashable Bytes64 Source # 

Methods

hashWithSalt :: Int -> Bytes64 -> Int #

hash :: Bytes64 -> Int #

ByteArrayAccess Bytes64 Source # 

Methods

length :: Bytes64 -> Int #

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

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

Store Bytes64 Source # 
StaticBytes Bytes64 Source # 

Methods

lengthS :: proxy Bytes64 -> Int

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

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

type Rep Bytes64 Source # 

data Bytes128 Source #

Instances

Eq Bytes128 Source # 
Data Bytes128 Source # 

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 :: (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 #

Ord Bytes128 Source # 
Show Bytes128 Source # 
Generic Bytes128 Source # 

Associated Types

type Rep Bytes128 :: * -> * #

Methods

from :: Bytes128 -> Rep Bytes128 x #

to :: Rep Bytes128 x -> Bytes128 #

NFData Bytes128 Source # 

Methods

rnf :: Bytes128 -> () #

Hashable Bytes128 Source # 

Methods

hashWithSalt :: Int -> Bytes128 -> Int #

hash :: Bytes128 -> Int #

ByteArrayAccess Bytes128 Source # 

Methods

length :: Bytes128 -> Int #

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

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

Store Bytes128 Source # 
StaticBytes Bytes128 Source # 

Methods

lengthS :: proxy Bytes128 -> Int

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

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

type Rep Bytes128 Source # 
type Rep Bytes128 = D1 * (MetaData "Bytes128" "Stack.StaticBytes" "stack-1.7.1-8x9NSKj6gz3B3M9RWkyZVt" False) (C1 * (MetaCons "Bytes128" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bytes64)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bytes64))))

class DynamicBytes dbytes Source #

Minimal complete definition

lengthD, withPeekD, fromWordsD

Instances

DynamicBytes ByteString Source # 

Methods

lengthD :: ByteString -> Int

withPeekD :: ByteString -> ((Int -> IO Word64) -> IO a) -> IO a

fromWordsD :: Int -> [Word64] -> ByteString

(~) * word8 Word8 => DynamicBytes (Vector word8) Source # 

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 # 

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 # 

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

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 #