{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE NoImplicitPrelude #-}
-- | 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.

module Pantry.Internal.StaticBytes
  ( Bytes8
  , Bytes16
  , Bytes32
  , Bytes64
  , Bytes128
  , DynamicBytes
  , StaticBytes
  , StaticBytesException (..)
  , toStaticExact
  , toStaticPad
  , toStaticTruncate
  , toStaticPadTruncate
  , fromStatic
  ) where

import RIO hiding (words)
import qualified Data.ByteString as B
import qualified Data.ByteString.Internal as B
import qualified Data.Vector.Primitive as VP
import qualified Data.Vector.Unboxed as VU
import qualified Data.Vector.Unboxed.Base as VU
import qualified Data.Vector.Storable as VS
import System.IO.Unsafe (unsafePerformIO)
import Foreign.Ptr
import Foreign.ForeignPtr
import Foreign.Storable
import Data.Bits
import qualified Data.Primitive.ByteArray as BA
import Data.ByteArray

newtype Bytes8 = Bytes8 Word64
  deriving (Bytes8 -> Bytes8 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Bytes8 -> Bytes8 -> Bool
$c/= :: Bytes8 -> Bytes8 -> Bool
== :: Bytes8 -> Bytes8 -> Bool
$c== :: Bytes8 -> Bytes8 -> Bool
Eq, Eq Bytes8
Bytes8 -> Bytes8 -> Bool
Bytes8 -> Bytes8 -> Ordering
Bytes8 -> Bytes8 -> Bytes8
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Bytes8 -> Bytes8 -> Bytes8
$cmin :: Bytes8 -> Bytes8 -> Bytes8
max :: Bytes8 -> Bytes8 -> Bytes8
$cmax :: Bytes8 -> Bytes8 -> Bytes8
>= :: Bytes8 -> Bytes8 -> Bool
$c>= :: Bytes8 -> Bytes8 -> Bool
> :: Bytes8 -> Bytes8 -> Bool
$c> :: Bytes8 -> Bytes8 -> Bool
<= :: Bytes8 -> Bytes8 -> Bool
$c<= :: Bytes8 -> Bytes8 -> Bool
< :: Bytes8 -> Bytes8 -> Bool
$c< :: Bytes8 -> Bytes8 -> Bool
compare :: Bytes8 -> Bytes8 -> Ordering
$ccompare :: Bytes8 -> Bytes8 -> Ordering
Ord, forall x. Rep Bytes8 x -> Bytes8
forall x. Bytes8 -> Rep Bytes8 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Bytes8 x -> Bytes8
$cfrom :: forall x. Bytes8 -> Rep Bytes8 x
Generic, Bytes8 -> ()
forall a. (a -> ()) -> NFData a
rnf :: Bytes8 -> ()
$crnf :: Bytes8 -> ()
NFData, Eq Bytes8
Int -> Bytes8 -> Int
Bytes8 -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Bytes8 -> Int
$chash :: Bytes8 -> Int
hashWithSalt :: Int -> Bytes8 -> Int
$chashWithSalt :: Int -> Bytes8 -> Int
Hashable, Typeable Bytes8
Bytes8 -> DataType
Bytes8 -> Constr
(forall b. Data b => b -> b) -> Bytes8 -> Bytes8
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Bytes8 -> u
forall u. (forall d. Data d => d -> u) -> Bytes8 -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bytes8 -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bytes8 -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Bytes8 -> m Bytes8
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes8 -> m Bytes8
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Bytes8
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bytes8 -> c Bytes8
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Bytes8)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes8)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes8 -> m Bytes8
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes8 -> m Bytes8
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes8 -> m Bytes8
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes8 -> m Bytes8
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Bytes8 -> m Bytes8
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Bytes8 -> m Bytes8
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Bytes8 -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Bytes8 -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Bytes8 -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Bytes8 -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bytes8 -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bytes8 -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bytes8 -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bytes8 -> r
gmapT :: (forall b. Data b => b -> b) -> Bytes8 -> Bytes8
$cgmapT :: (forall b. Data b => b -> b) -> Bytes8 -> Bytes8
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes8)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes8)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Bytes8)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Bytes8)
dataTypeOf :: Bytes8 -> DataType
$cdataTypeOf :: Bytes8 -> DataType
toConstr :: Bytes8 -> Constr
$ctoConstr :: Bytes8 -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Bytes8
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Bytes8
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bytes8 -> c Bytes8
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bytes8 -> c Bytes8
Data)
instance Show Bytes8 where
  show :: Bytes8 -> String
show (Bytes8 Word64
w) = forall a. Show a => a -> String
show (forall dbytes. DynamicBytes dbytes => Int -> [Word64] -> dbytes
fromWordsD Int
8 [Word64
w] :: B.ByteString)
data Bytes16 = Bytes16 !Bytes8 !Bytes8
  deriving (Int -> Bytes16 -> ShowS
[Bytes16] -> ShowS
Bytes16 -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Bytes16] -> ShowS
$cshowList :: [Bytes16] -> ShowS
show :: Bytes16 -> String
$cshow :: Bytes16 -> String
showsPrec :: Int -> Bytes16 -> ShowS
$cshowsPrec :: Int -> Bytes16 -> ShowS
Show, Bytes16 -> Bytes16 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Bytes16 -> Bytes16 -> Bool
$c/= :: Bytes16 -> Bytes16 -> Bool
== :: Bytes16 -> Bytes16 -> Bool
$c== :: Bytes16 -> Bytes16 -> Bool
Eq, Eq Bytes16
Bytes16 -> Bytes16 -> Bool
Bytes16 -> Bytes16 -> Ordering
Bytes16 -> Bytes16 -> Bytes16
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Bytes16 -> Bytes16 -> Bytes16
$cmin :: Bytes16 -> Bytes16 -> Bytes16
max :: Bytes16 -> Bytes16 -> Bytes16
$cmax :: Bytes16 -> Bytes16 -> Bytes16
>= :: Bytes16 -> Bytes16 -> Bool
$c>= :: Bytes16 -> Bytes16 -> Bool
> :: Bytes16 -> Bytes16 -> Bool
$c> :: Bytes16 -> Bytes16 -> Bool
<= :: Bytes16 -> Bytes16 -> Bool
$c<= :: Bytes16 -> Bytes16 -> Bool
< :: Bytes16 -> Bytes16 -> Bool
$c< :: Bytes16 -> Bytes16 -> Bool
compare :: Bytes16 -> Bytes16 -> Ordering
$ccompare :: Bytes16 -> Bytes16 -> Ordering
Ord, forall x. Rep Bytes16 x -> Bytes16
forall x. Bytes16 -> Rep Bytes16 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Bytes16 x -> Bytes16
$cfrom :: forall x. Bytes16 -> Rep Bytes16 x
Generic, Bytes16 -> ()
forall a. (a -> ()) -> NFData a
rnf :: Bytes16 -> ()
$crnf :: Bytes16 -> ()
NFData, Eq Bytes16
Int -> Bytes16 -> Int
Bytes16 -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Bytes16 -> Int
$chash :: Bytes16 -> Int
hashWithSalt :: Int -> Bytes16 -> Int
$chashWithSalt :: Int -> Bytes16 -> Int
Hashable, Typeable Bytes16
Bytes16 -> DataType
Bytes16 -> Constr
(forall b. Data b => b -> b) -> Bytes16 -> Bytes16
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Bytes16 -> u
forall u. (forall d. Data d => d -> u) -> Bytes16 -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes16 -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes16 -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Bytes16 -> m Bytes16
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes16 -> m Bytes16
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Bytes16
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bytes16 -> c Bytes16
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Bytes16)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes16)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes16 -> m Bytes16
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes16 -> m Bytes16
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes16 -> m Bytes16
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes16 -> m Bytes16
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Bytes16 -> m Bytes16
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Bytes16 -> m Bytes16
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Bytes16 -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Bytes16 -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Bytes16 -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Bytes16 -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes16 -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes16 -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes16 -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes16 -> r
gmapT :: (forall b. Data b => b -> b) -> Bytes16 -> Bytes16
$cgmapT :: (forall b. Data b => b -> b) -> Bytes16 -> Bytes16
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes16)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes16)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Bytes16)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Bytes16)
dataTypeOf :: Bytes16 -> DataType
$cdataTypeOf :: Bytes16 -> DataType
toConstr :: Bytes16 -> Constr
$ctoConstr :: Bytes16 -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Bytes16
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Bytes16
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bytes16 -> c Bytes16
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bytes16 -> c Bytes16
Data)
data Bytes32 = Bytes32 !Bytes16 !Bytes16
  deriving (Int -> Bytes32 -> ShowS
[Bytes32] -> ShowS
Bytes32 -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Bytes32] -> ShowS
$cshowList :: [Bytes32] -> ShowS
show :: Bytes32 -> String
$cshow :: Bytes32 -> String
showsPrec :: Int -> Bytes32 -> ShowS
$cshowsPrec :: Int -> Bytes32 -> ShowS
Show, Bytes32 -> Bytes32 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Bytes32 -> Bytes32 -> Bool
$c/= :: Bytes32 -> Bytes32 -> Bool
== :: Bytes32 -> Bytes32 -> Bool
$c== :: Bytes32 -> Bytes32 -> Bool
Eq, Eq Bytes32
Bytes32 -> Bytes32 -> Bool
Bytes32 -> Bytes32 -> Ordering
Bytes32 -> Bytes32 -> Bytes32
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Bytes32 -> Bytes32 -> Bytes32
$cmin :: Bytes32 -> Bytes32 -> Bytes32
max :: Bytes32 -> Bytes32 -> Bytes32
$cmax :: Bytes32 -> Bytes32 -> Bytes32
>= :: Bytes32 -> Bytes32 -> Bool
$c>= :: Bytes32 -> Bytes32 -> Bool
> :: Bytes32 -> Bytes32 -> Bool
$c> :: Bytes32 -> Bytes32 -> Bool
<= :: Bytes32 -> Bytes32 -> Bool
$c<= :: Bytes32 -> Bytes32 -> Bool
< :: Bytes32 -> Bytes32 -> Bool
$c< :: Bytes32 -> Bytes32 -> Bool
compare :: Bytes32 -> Bytes32 -> Ordering
$ccompare :: Bytes32 -> Bytes32 -> Ordering
Ord, forall x. Rep Bytes32 x -> Bytes32
forall x. Bytes32 -> Rep Bytes32 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Bytes32 x -> Bytes32
$cfrom :: forall x. Bytes32 -> Rep Bytes32 x
Generic, Bytes32 -> ()
forall a. (a -> ()) -> NFData a
rnf :: Bytes32 -> ()
$crnf :: Bytes32 -> ()
NFData, Eq Bytes32
Int -> Bytes32 -> Int
Bytes32 -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Bytes32 -> Int
$chash :: Bytes32 -> Int
hashWithSalt :: Int -> Bytes32 -> Int
$chashWithSalt :: Int -> Bytes32 -> Int
Hashable, Typeable Bytes32
Bytes32 -> DataType
Bytes32 -> Constr
(forall b. Data b => b -> b) -> Bytes32 -> Bytes32
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Bytes32 -> u
forall u. (forall d. Data d => d -> u) -> Bytes32 -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes32 -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes32 -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Bytes32 -> m Bytes32
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes32 -> m Bytes32
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Bytes32
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bytes32 -> c Bytes32
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Bytes32)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes32)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes32 -> m Bytes32
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes32 -> m Bytes32
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes32 -> m Bytes32
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes32 -> m Bytes32
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Bytes32 -> m Bytes32
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Bytes32 -> m Bytes32
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Bytes32 -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Bytes32 -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Bytes32 -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Bytes32 -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes32 -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes32 -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes32 -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes32 -> r
gmapT :: (forall b. Data b => b -> b) -> Bytes32 -> Bytes32
$cgmapT :: (forall b. Data b => b -> b) -> Bytes32 -> Bytes32
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes32)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes32)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Bytes32)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Bytes32)
dataTypeOf :: Bytes32 -> DataType
$cdataTypeOf :: Bytes32 -> DataType
toConstr :: Bytes32 -> Constr
$ctoConstr :: Bytes32 -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Bytes32
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Bytes32
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bytes32 -> c Bytes32
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bytes32 -> c Bytes32
Data)
data Bytes64 = Bytes64 !Bytes32 !Bytes32
  deriving (Int -> Bytes64 -> ShowS
[Bytes64] -> ShowS
Bytes64 -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Bytes64] -> ShowS
$cshowList :: [Bytes64] -> ShowS
show :: Bytes64 -> String
$cshow :: Bytes64 -> String
showsPrec :: Int -> Bytes64 -> ShowS
$cshowsPrec :: Int -> Bytes64 -> ShowS
Show, Bytes64 -> Bytes64 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Bytes64 -> Bytes64 -> Bool
$c/= :: Bytes64 -> Bytes64 -> Bool
== :: Bytes64 -> Bytes64 -> Bool
$c== :: Bytes64 -> Bytes64 -> Bool
Eq, Eq Bytes64
Bytes64 -> Bytes64 -> Bool
Bytes64 -> Bytes64 -> Ordering
Bytes64 -> Bytes64 -> Bytes64
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Bytes64 -> Bytes64 -> Bytes64
$cmin :: Bytes64 -> Bytes64 -> Bytes64
max :: Bytes64 -> Bytes64 -> Bytes64
$cmax :: Bytes64 -> Bytes64 -> Bytes64
>= :: Bytes64 -> Bytes64 -> Bool
$c>= :: Bytes64 -> Bytes64 -> Bool
> :: Bytes64 -> Bytes64 -> Bool
$c> :: Bytes64 -> Bytes64 -> Bool
<= :: Bytes64 -> Bytes64 -> Bool
$c<= :: Bytes64 -> Bytes64 -> Bool
< :: Bytes64 -> Bytes64 -> Bool
$c< :: Bytes64 -> Bytes64 -> Bool
compare :: Bytes64 -> Bytes64 -> Ordering
$ccompare :: Bytes64 -> Bytes64 -> Ordering
Ord, forall x. Rep Bytes64 x -> Bytes64
forall x. Bytes64 -> Rep Bytes64 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Bytes64 x -> Bytes64
$cfrom :: forall x. Bytes64 -> Rep Bytes64 x
Generic, Bytes64 -> ()
forall a. (a -> ()) -> NFData a
rnf :: Bytes64 -> ()
$crnf :: Bytes64 -> ()
NFData, Eq Bytes64
Int -> Bytes64 -> Int
Bytes64 -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Bytes64 -> Int
$chash :: Bytes64 -> Int
hashWithSalt :: Int -> Bytes64 -> Int
$chashWithSalt :: Int -> Bytes64 -> Int
Hashable, Typeable Bytes64
Bytes64 -> DataType
Bytes64 -> Constr
(forall b. Data b => b -> b) -> Bytes64 -> Bytes64
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Bytes64 -> u
forall u. (forall d. Data d => d -> u) -> Bytes64 -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes64 -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes64 -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Bytes64 -> m Bytes64
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes64 -> m Bytes64
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Bytes64
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bytes64 -> c Bytes64
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Bytes64)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes64)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes64 -> m Bytes64
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes64 -> m Bytes64
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes64 -> m Bytes64
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes64 -> m Bytes64
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Bytes64 -> m Bytes64
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Bytes64 -> m Bytes64
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Bytes64 -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Bytes64 -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Bytes64 -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Bytes64 -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes64 -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes64 -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes64 -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes64 -> r
gmapT :: (forall b. Data b => b -> b) -> Bytes64 -> Bytes64
$cgmapT :: (forall b. Data b => b -> b) -> Bytes64 -> Bytes64
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes64)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes64)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Bytes64)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Bytes64)
dataTypeOf :: Bytes64 -> DataType
$cdataTypeOf :: Bytes64 -> DataType
toConstr :: Bytes64 -> Constr
$ctoConstr :: Bytes64 -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Bytes64
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Bytes64
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bytes64 -> c Bytes64
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bytes64 -> c Bytes64
Data)
data Bytes128 = Bytes128 !Bytes64 !Bytes64
  deriving (Int -> Bytes128 -> ShowS
[Bytes128] -> ShowS
Bytes128 -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Bytes128] -> ShowS
$cshowList :: [Bytes128] -> ShowS
show :: Bytes128 -> String
$cshow :: Bytes128 -> String
showsPrec :: Int -> Bytes128 -> ShowS
$cshowsPrec :: Int -> Bytes128 -> ShowS
Show, Bytes128 -> Bytes128 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Bytes128 -> Bytes128 -> Bool
$c/= :: Bytes128 -> Bytes128 -> Bool
== :: Bytes128 -> Bytes128 -> Bool
$c== :: Bytes128 -> Bytes128 -> Bool
Eq, Eq Bytes128
Bytes128 -> Bytes128 -> Bool
Bytes128 -> Bytes128 -> Ordering
Bytes128 -> Bytes128 -> Bytes128
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Bytes128 -> Bytes128 -> Bytes128
$cmin :: Bytes128 -> Bytes128 -> Bytes128
max :: Bytes128 -> Bytes128 -> Bytes128
$cmax :: Bytes128 -> Bytes128 -> Bytes128
>= :: Bytes128 -> Bytes128 -> Bool
$c>= :: Bytes128 -> Bytes128 -> Bool
> :: Bytes128 -> Bytes128 -> Bool
$c> :: Bytes128 -> Bytes128 -> Bool
<= :: Bytes128 -> Bytes128 -> Bool
$c<= :: Bytes128 -> Bytes128 -> Bool
< :: Bytes128 -> Bytes128 -> Bool
$c< :: Bytes128 -> Bytes128 -> Bool
compare :: Bytes128 -> Bytes128 -> Ordering
$ccompare :: Bytes128 -> Bytes128 -> Ordering
Ord, forall x. Rep Bytes128 x -> Bytes128
forall x. Bytes128 -> Rep Bytes128 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Bytes128 x -> Bytes128
$cfrom :: forall x. Bytes128 -> Rep Bytes128 x
Generic, Bytes128 -> ()
forall a. (a -> ()) -> NFData a
rnf :: Bytes128 -> ()
$crnf :: Bytes128 -> ()
NFData, Eq Bytes128
Int -> Bytes128 -> Int
Bytes128 -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Bytes128 -> Int
$chash :: Bytes128 -> Int
hashWithSalt :: Int -> Bytes128 -> Int
$chashWithSalt :: Int -> Bytes128 -> Int
Hashable, Typeable Bytes128
Bytes128 -> DataType
Bytes128 -> Constr
(forall b. Data b => b -> b) -> Bytes128 -> Bytes128
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Bytes128 -> u
forall u. (forall d. Data d => d -> u) -> Bytes128 -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes128 -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes128 -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Bytes128 -> m Bytes128
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes128 -> m Bytes128
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Bytes128
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bytes128 -> c Bytes128
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Bytes128)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes128)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes128 -> m Bytes128
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes128 -> m Bytes128
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes128 -> m Bytes128
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Bytes128 -> m Bytes128
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Bytes128 -> m Bytes128
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Bytes128 -> m Bytes128
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Bytes128 -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Bytes128 -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Bytes128 -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Bytes128 -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes128 -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes128 -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes128 -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bytes128 -> r
gmapT :: (forall b. Data b => b -> b) -> Bytes128 -> Bytes128
$cgmapT :: (forall b. Data b => b -> b) -> Bytes128 -> Bytes128
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes128)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes128)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Bytes128)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Bytes128)
dataTypeOf :: Bytes128 -> DataType
$cdataTypeOf :: Bytes128 -> DataType
toConstr :: Bytes128 -> Constr
$ctoConstr :: Bytes128 -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Bytes128
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Bytes128
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bytes128 -> c Bytes128
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bytes128 -> c Bytes128
Data)

data StaticBytesException
  = NotEnoughBytes
  | TooManyBytes
  deriving (Int -> StaticBytesException -> ShowS
[StaticBytesException] -> ShowS
StaticBytesException -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StaticBytesException] -> ShowS
$cshowList :: [StaticBytesException] -> ShowS
show :: StaticBytesException -> String
$cshow :: StaticBytesException -> String
showsPrec :: Int -> StaticBytesException -> ShowS
$cshowsPrec :: Int -> StaticBytesException -> ShowS
Show, StaticBytesException -> StaticBytesException -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StaticBytesException -> StaticBytesException -> Bool
$c/= :: StaticBytesException -> StaticBytesException -> Bool
== :: StaticBytesException -> StaticBytesException -> Bool
$c== :: StaticBytesException -> StaticBytesException -> Bool
Eq, Typeable)
instance Exception StaticBytesException

-- All lengths below are given in bytes


class DynamicBytes dbytes where
  lengthD :: dbytes -> Int
  -- | Yeah, it looks terrible to use a list here, but fusion should

  -- kick in

  withPeekD :: dbytes -> ((Int -> IO Word64) -> IO a) -> IO a
  -- | May throw a runtime exception if invariants are violated!

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

fromWordsForeign
  :: (ForeignPtr a -> Int -> b)
  -> Int
  -> [Word64]
  -> b
fromWordsForeign :: forall a b. (ForeignPtr a -> Int -> b) -> Int -> [Word64] -> b
fromWordsForeign ForeignPtr a -> Int -> b
wrapper Int
len [Word64]
words0 = forall a. IO a -> a
unsafePerformIO forall a b. (a -> b) -> a -> b
$ do
  ForeignPtr a
fptr <- forall a. Int -> IO (ForeignPtr a)
B.mallocByteString Int
len
  forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr a
fptr forall a b. (a -> b) -> a -> b
$ \Ptr a
ptr -> do
    let loop :: Int -> [Word64] -> IO ()
loop Int
_ [] = forall (m :: * -> *) a. Monad m => a -> m a
return ()
        loop Int
off (Word64
w:[Word64]
ws) = do
          forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff (forall a b. Ptr a -> Ptr b
castPtr Ptr a
ptr) Int
off Word64
w
          Int -> [Word64] -> IO ()
loop (Int
off forall a. Num a => a -> a -> a
+ Int
1) [Word64]
ws
    Int -> [Word64] -> IO ()
loop Int
0 [Word64]
words0
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ForeignPtr a -> Int -> b
wrapper ForeignPtr a
fptr Int
len

withPeekForeign
  :: (ForeignPtr a, Int, Int)
  -> ((Int -> IO Word64) -> IO b)
  -> IO b
withPeekForeign :: forall a b.
(ForeignPtr a, Int, Int) -> ((Int -> IO Word64) -> IO b) -> IO b
withPeekForeign (ForeignPtr a
fptr, Int
off, Int
len) (Int -> IO Word64) -> IO b
inner =
  forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr a
fptr forall a b. (a -> b) -> a -> b
$ \Ptr a
ptr -> do
    let f :: Int -> IO Word64
f Int
off'
          | Int
off' forall a. Ord a => a -> a -> Bool
>= Int
len = forall (m :: * -> *) a. Monad m => a -> m a
return Word64
0
          | Int
off' forall a. Num a => a -> a -> a
+ Int
8 forall a. Ord a => a -> a -> Bool
> Int
len = do
              let loop :: Word64 -> Int -> IO Word64
loop Word64
w64 Int
i
                    | Int
off' forall a. Num a => a -> a -> a
+ Int
i forall a. Ord a => a -> a -> Bool
>= Int
len = forall (m :: * -> *) a. Monad m => a -> m a
return Word64
w64
                    | Bool
otherwise = do
                        Word8
w8 :: Word8 <- forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr a
ptr (Int
off forall a. Num a => a -> a -> a
+ Int
off' forall a. Num a => a -> a -> a
+ Int
i)
                        let w64' :: Word64
w64' = forall a. Bits a => a -> Int -> a
shiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w8) (Int
i forall a. Num a => a -> a -> a
* Int
8) forall a. Bits a => a -> a -> a
.|. Word64
w64
                        Word64 -> Int -> IO Word64
loop Word64
w64' (Int
i forall a. Num a => a -> a -> a
+ Int
1)
              Word64 -> Int -> IO Word64
loop Word64
0 Int
0
          | Bool
otherwise = forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr a
ptr (Int
off forall a. Num a => a -> a -> a
+ Int
off')
    (Int -> IO Word64) -> IO b
inner Int -> IO Word64
f

instance DynamicBytes B.ByteString where
  lengthD :: ByteString -> Int
lengthD = ByteString -> Int
B.length
  fromWordsD :: Int -> [Word64] -> ByteString
fromWordsD = forall a b. (ForeignPtr a -> Int -> b) -> Int -> [Word64] -> b
fromWordsForeign (\ForeignPtr Word8
fptr Int
len -> ForeignPtr Word8 -> Int -> Int -> ByteString
B.fromForeignPtr ForeignPtr Word8
fptr Int
0 Int
len)
  withPeekD :: forall a. ByteString -> ((Int -> IO Word64) -> IO a) -> IO a
withPeekD = forall a b.
(ForeignPtr a, Int, Int) -> ((Int -> IO Word64) -> IO b) -> IO b
withPeekForeign forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> (ForeignPtr Word8, Int, Int)
B.toForeignPtr

instance word8 ~ Word8 => DynamicBytes (VS.Vector word8) where
  lengthD :: Vector word8 -> Int
lengthD = forall a. Storable a => Vector a -> Int
VS.length
  fromWordsD :: Int -> [Word64] -> Vector word8
fromWordsD = forall a b. (ForeignPtr a -> Int -> b) -> Int -> [Word64] -> b
fromWordsForeign forall a. ForeignPtr a -> Int -> Vector a
VS.unsafeFromForeignPtr0
  withPeekD :: forall a. Vector word8 -> ((Int -> IO Word64) -> IO a) -> IO a
withPeekD = forall a b.
(ForeignPtr a, Int, Int) -> ((Int -> IO Word64) -> IO b) -> IO b
withPeekForeign forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Vector a -> (ForeignPtr a, Int, Int)
VS.unsafeToForeignPtr

instance word8 ~ Word8 => DynamicBytes (VP.Vector word8) where
  lengthD :: Vector word8 -> Int
lengthD = forall a. Prim a => Vector a -> Int
VP.length
  fromWordsD :: Int -> [Word64] -> Vector word8
fromWordsD Int
len [Word64]
words0 = forall a. IO a -> a
unsafePerformIO forall a b. (a -> b) -> a -> b
$ do
    MutableByteArray RealWorld
ba <- forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
BA.newByteArray Int
len
    let loop :: Int -> [Word64] -> IO (Vector word8)
loop Int
_ [] =
          forall a. Int -> Int -> ByteArray -> Vector a
VP.Vector Int
0 Int
len forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
BA.unsafeFreezeByteArray MutableByteArray RealWorld
ba
        loop Int
i (Word64
w:[Word64]
ws) = do
          forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
BA.writeByteArray MutableByteArray RealWorld
ba Int
i Word64
w
          Int -> [Word64] -> IO (Vector word8)
loop (Int
i forall a. Num a => a -> a -> a
+ Int
1) [Word64]
ws
    Int -> [Word64] -> IO (Vector word8)
loop Int
0 [Word64]
words0
  withPeekD :: forall a. Vector word8 -> ((Int -> IO Word64) -> IO a) -> IO a
withPeekD (VP.Vector Int
off Int
len ByteArray
ba) (Int -> IO Word64) -> IO a
inner = do
    let f :: Int -> IO Word64
f Int
off'
          | Int
off' forall a. Ord a => a -> a -> Bool
>= Int
len = forall (m :: * -> *) a. Monad m => a -> m a
return Word64
0
          | Int
off' forall a. Num a => a -> a -> a
+ Int
8 forall a. Ord a => a -> a -> Bool
> Int
len = do
              let loop :: Word64 -> Int -> IO Word64
loop Word64
w64 Int
i
                    | Int
off' forall a. Num a => a -> a -> a
+ Int
i forall a. Ord a => a -> a -> Bool
>= Int
len = forall (m :: * -> *) a. Monad m => a -> m a
return Word64
w64
                    | Bool
otherwise = do
                        let Word8
w8 :: Word8 = forall a. Prim a => ByteArray -> Int -> a
BA.indexByteArray ByteArray
ba (Int
off forall a. Num a => a -> a -> a
+ Int
off' forall a. Num a => a -> a -> a
+ Int
i)
                        let w64' :: Word64
w64' = forall a. Bits a => a -> Int -> a
shiftL (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w8) (Int
i forall a. Num a => a -> a -> a
* Int
8) forall a. Bits a => a -> a -> a
.|. Word64
w64
                        Word64 -> Int -> IO Word64
loop Word64
w64' (Int
i forall a. Num a => a -> a -> a
+ Int
1)
              Word64 -> Int -> IO Word64
loop Word64
0 Int
0
          | Bool
otherwise = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Prim a => ByteArray -> Int -> a
BA.indexByteArray ByteArray
ba (Int
off forall a. Num a => a -> a -> a
+ (Int
off' forall a. Integral a => a -> a -> a
`div` Int
8))
    (Int -> IO Word64) -> IO a
inner Int -> IO Word64
f

instance word8 ~ Word8 => DynamicBytes (VU.Vector word8) where
  lengthD :: Vector word8 -> Int
lengthD = forall a. Unbox a => Vector a -> Int
VU.length
  fromWordsD :: Int -> [Word64] -> Vector word8
fromWordsD Int
len [Word64]
words = Vector Word8 -> Vector Word8
VU.V_Word8 (forall dbytes. DynamicBytes dbytes => Int -> [Word64] -> dbytes
fromWordsD Int
len [Word64]
words)
  withPeekD :: forall a. Vector word8 -> ((Int -> IO Word64) -> IO a) -> IO a
withPeekD (VU.V_Word8 Vector Word8
v) = forall dbytes a.
DynamicBytes dbytes =>
dbytes -> ((Int -> IO Word64) -> IO a) -> IO a
withPeekD Vector Word8
v

class StaticBytes sbytes where
  lengthS :: proxy sbytes -> Int -- use type level literals instead?

  -- difference list

  toWordsS :: sbytes -> [Word64] -> [Word64]
  usePeekS :: Int -> (Int -> IO Word64) -> IO sbytes

instance StaticBytes Bytes8 where
  lengthS :: forall (proxy :: * -> *). proxy Bytes8 -> Int
lengthS proxy Bytes8
_ = Int
8
  toWordsS :: Bytes8 -> [Word64] -> [Word64]
toWordsS (Bytes8 Word64
w) = (Word64
wforall a. a -> [a] -> [a]
:)
  usePeekS :: Int -> (Int -> IO Word64) -> IO Bytes8
usePeekS Int
off Int -> IO Word64
f = Word64 -> Bytes8
Bytes8 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> IO Word64
f Int
off

instance StaticBytes Bytes16 where
  lengthS :: forall (proxy :: * -> *). proxy Bytes16 -> Int
lengthS proxy Bytes16
_ = Int
16
  toWordsS :: Bytes16 -> [Word64] -> [Word64]
toWordsS (Bytes16 Bytes8
b1 Bytes8
b2) = forall sbytes. StaticBytes sbytes => sbytes -> [Word64] -> [Word64]
toWordsS Bytes8
b1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall sbytes. StaticBytes sbytes => sbytes -> [Word64] -> [Word64]
toWordsS Bytes8
b2
  usePeekS :: Int -> (Int -> IO Word64) -> IO Bytes16
usePeekS Int
off Int -> IO Word64
f = Bytes8 -> Bytes8 -> Bytes16
Bytes16 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall sbytes.
StaticBytes sbytes =>
Int -> (Int -> IO Word64) -> IO sbytes
usePeekS Int
off Int -> IO Word64
f forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall sbytes.
StaticBytes sbytes =>
Int -> (Int -> IO Word64) -> IO sbytes
usePeekS (Int
off forall a. Num a => a -> a -> a
+ Int
8) Int -> IO Word64
f

instance StaticBytes Bytes32 where
  lengthS :: forall (proxy :: * -> *). proxy Bytes32 -> Int
lengthS proxy Bytes32
_ = Int
32
  toWordsS :: Bytes32 -> [Word64] -> [Word64]
toWordsS (Bytes32 Bytes16
b1 Bytes16
b2) = forall sbytes. StaticBytes sbytes => sbytes -> [Word64] -> [Word64]
toWordsS Bytes16
b1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall sbytes. StaticBytes sbytes => sbytes -> [Word64] -> [Word64]
toWordsS Bytes16
b2
  usePeekS :: Int -> (Int -> IO Word64) -> IO Bytes32
usePeekS Int
off Int -> IO Word64
f = Bytes16 -> Bytes16 -> Bytes32
Bytes32 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall sbytes.
StaticBytes sbytes =>
Int -> (Int -> IO Word64) -> IO sbytes
usePeekS Int
off Int -> IO Word64
f forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall sbytes.
StaticBytes sbytes =>
Int -> (Int -> IO Word64) -> IO sbytes
usePeekS (Int
off forall a. Num a => a -> a -> a
+ Int
16) Int -> IO Word64
f

instance StaticBytes Bytes64 where
  lengthS :: forall (proxy :: * -> *). proxy Bytes64 -> Int
lengthS proxy Bytes64
_ = Int
64
  toWordsS :: Bytes64 -> [Word64] -> [Word64]
toWordsS (Bytes64 Bytes32
b1 Bytes32
b2) = forall sbytes. StaticBytes sbytes => sbytes -> [Word64] -> [Word64]
toWordsS Bytes32
b1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall sbytes. StaticBytes sbytes => sbytes -> [Word64] -> [Word64]
toWordsS Bytes32
b2
  usePeekS :: Int -> (Int -> IO Word64) -> IO Bytes64
usePeekS Int
off Int -> IO Word64
f = Bytes32 -> Bytes32 -> Bytes64
Bytes64 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall sbytes.
StaticBytes sbytes =>
Int -> (Int -> IO Word64) -> IO sbytes
usePeekS Int
off Int -> IO Word64
f forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall sbytes.
StaticBytes sbytes =>
Int -> (Int -> IO Word64) -> IO sbytes
usePeekS (Int
off forall a. Num a => a -> a -> a
+ Int
32) Int -> IO Word64
f

instance StaticBytes Bytes128 where
  lengthS :: forall (proxy :: * -> *). proxy Bytes128 -> Int
lengthS proxy Bytes128
_ = Int
128
  toWordsS :: Bytes128 -> [Word64] -> [Word64]
toWordsS (Bytes128 Bytes64
b1 Bytes64
b2) = forall sbytes. StaticBytes sbytes => sbytes -> [Word64] -> [Word64]
toWordsS Bytes64
b1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall sbytes. StaticBytes sbytes => sbytes -> [Word64] -> [Word64]
toWordsS Bytes64
b2
  usePeekS :: Int -> (Int -> IO Word64) -> IO Bytes128
usePeekS Int
off Int -> IO Word64
f = Bytes64 -> Bytes64 -> Bytes128
Bytes128 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall sbytes.
StaticBytes sbytes =>
Int -> (Int -> IO Word64) -> IO sbytes
usePeekS Int
off Int -> IO Word64
f forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall sbytes.
StaticBytes sbytes =>
Int -> (Int -> IO Word64) -> IO sbytes
usePeekS (Int
off forall a. Num a => a -> a -> a
+ Int
64) Int -> IO Word64
f

instance ByteArrayAccess Bytes8 where
  length :: Bytes8 -> Int
length Bytes8
_ = Int
8
  withByteArray :: forall p a. Bytes8 -> (Ptr p -> IO a) -> IO a
withByteArray = forall sbytes p a.
StaticBytes sbytes =>
sbytes -> (Ptr p -> IO a) -> IO a
withByteArrayS
instance ByteArrayAccess Bytes16 where
  length :: Bytes16 -> Int
length Bytes16
_ = Int
16
  withByteArray :: forall p a. Bytes16 -> (Ptr p -> IO a) -> IO a
withByteArray = forall sbytes p a.
StaticBytes sbytes =>
sbytes -> (Ptr p -> IO a) -> IO a
withByteArrayS
instance ByteArrayAccess Bytes32 where
  length :: Bytes32 -> Int
length Bytes32
_ = Int
32
  withByteArray :: forall p a. Bytes32 -> (Ptr p -> IO a) -> IO a
withByteArray = forall sbytes p a.
StaticBytes sbytes =>
sbytes -> (Ptr p -> IO a) -> IO a
withByteArrayS
instance ByteArrayAccess Bytes64 where
  length :: Bytes64 -> Int
length Bytes64
_ = Int
64
  withByteArray :: forall p a. Bytes64 -> (Ptr p -> IO a) -> IO a
withByteArray = forall sbytes p a.
StaticBytes sbytes =>
sbytes -> (Ptr p -> IO a) -> IO a
withByteArrayS
instance ByteArrayAccess Bytes128 where
  length :: Bytes128 -> Int
length Bytes128
_ = Int
128
  withByteArray :: forall p a. Bytes128 -> (Ptr p -> IO a) -> IO a
withByteArray = forall sbytes p a.
StaticBytes sbytes =>
sbytes -> (Ptr p -> IO a) -> IO a
withByteArrayS

withByteArrayS :: StaticBytes sbytes => sbytes -> (Ptr p -> IO a) -> IO a
withByteArrayS :: forall sbytes p a.
StaticBytes sbytes =>
sbytes -> (Ptr p -> IO a) -> IO a
withByteArrayS sbytes
sbytes = forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
withByteArray (forall dbytes sbytes.
(DynamicBytes dbytes, StaticBytes sbytes) =>
sbytes -> dbytes
fromStatic sbytes
sbytes :: ByteString)

toStaticExact
  :: forall dbytes sbytes.
     (DynamicBytes dbytes, StaticBytes sbytes)
  => dbytes
  -> Either StaticBytesException sbytes
toStaticExact :: forall dbytes sbytes.
(DynamicBytes dbytes, StaticBytes sbytes) =>
dbytes -> Either StaticBytesException sbytes
toStaticExact dbytes
dbytes =
  case forall a. Ord a => a -> a -> Ordering
compare (forall dbytes. DynamicBytes dbytes => dbytes -> Int
lengthD dbytes
dbytes) (forall sbytes (proxy :: * -> *).
StaticBytes sbytes =>
proxy sbytes -> Int
lengthS (forall a. Maybe a
Nothing :: Maybe sbytes)) of
    Ordering
LT -> forall a b. a -> Either a b
Left StaticBytesException
NotEnoughBytes
    Ordering
GT -> forall a b. a -> Either a b
Left StaticBytesException
TooManyBytes
    Ordering
EQ -> forall a b. b -> Either a b
Right (forall dbytes sbytes.
(DynamicBytes dbytes, StaticBytes sbytes) =>
dbytes -> sbytes
toStaticPadTruncate dbytes
dbytes)

toStaticPad
  :: forall dbytes sbytes.
     (DynamicBytes dbytes, StaticBytes sbytes)
  => dbytes
  -> Either StaticBytesException sbytes
toStaticPad :: forall dbytes sbytes.
(DynamicBytes dbytes, StaticBytes sbytes) =>
dbytes -> Either StaticBytesException sbytes
toStaticPad dbytes
dbytes =
  case forall a. Ord a => a -> a -> Ordering
compare (forall dbytes. DynamicBytes dbytes => dbytes -> Int
lengthD dbytes
dbytes) (forall sbytes (proxy :: * -> *).
StaticBytes sbytes =>
proxy sbytes -> Int
lengthS (forall a. Maybe a
Nothing :: Maybe sbytes)) of
    Ordering
GT -> forall a b. a -> Either a b
Left StaticBytesException
TooManyBytes
    Ordering
_  -> forall a b. b -> Either a b
Right (forall dbytes sbytes.
(DynamicBytes dbytes, StaticBytes sbytes) =>
dbytes -> sbytes
toStaticPadTruncate dbytes
dbytes)

toStaticTruncate
  :: forall dbytes sbytes.
     (DynamicBytes dbytes, StaticBytes sbytes)
  => dbytes
  -> Either StaticBytesException sbytes
toStaticTruncate :: forall dbytes sbytes.
(DynamicBytes dbytes, StaticBytes sbytes) =>
dbytes -> Either StaticBytesException sbytes
toStaticTruncate dbytes
dbytes =
  case forall a. Ord a => a -> a -> Ordering
compare (forall dbytes. DynamicBytes dbytes => dbytes -> Int
lengthD dbytes
dbytes) (forall sbytes (proxy :: * -> *).
StaticBytes sbytes =>
proxy sbytes -> Int
lengthS (forall a. Maybe a
Nothing :: Maybe sbytes)) of
    Ordering
LT -> forall a b. a -> Either a b
Left StaticBytesException
NotEnoughBytes
    Ordering
_  -> forall a b. b -> Either a b
Right (forall dbytes sbytes.
(DynamicBytes dbytes, StaticBytes sbytes) =>
dbytes -> sbytes
toStaticPadTruncate dbytes
dbytes)

toStaticPadTruncate
  :: (DynamicBytes dbytes, StaticBytes sbytes)
  => dbytes
  -> sbytes
toStaticPadTruncate :: forall dbytes sbytes.
(DynamicBytes dbytes, StaticBytes sbytes) =>
dbytes -> sbytes
toStaticPadTruncate dbytes
dbytes = forall a. IO a -> a
unsafePerformIO (forall dbytes a.
DynamicBytes dbytes =>
dbytes -> ((Int -> IO Word64) -> IO a) -> IO a
withPeekD dbytes
dbytes (forall sbytes.
StaticBytes sbytes =>
Int -> (Int -> IO Word64) -> IO sbytes
usePeekS Int
0))

fromStatic
  :: forall dbytes sbytes.
     (DynamicBytes dbytes, StaticBytes sbytes)
  => sbytes
  -> dbytes
fromStatic :: forall dbytes sbytes.
(DynamicBytes dbytes, StaticBytes sbytes) =>
sbytes -> dbytes
fromStatic = forall dbytes. DynamicBytes dbytes => Int -> [Word64] -> dbytes
fromWordsD (forall sbytes (proxy :: * -> *).
StaticBytes sbytes =>
proxy sbytes -> Int
lengthS (forall a. Maybe a
Nothing :: Maybe sbytes)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> a -> b
$ []) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall sbytes. StaticBytes sbytes => sbytes -> [Word64] -> [Word64]
toWordsS