binrep-0.3.1: Encode precise binary representations directly in types
Safe HaskellSafe-Inferred
LanguageHaskell2010

Binrep.Type.ByteString

Description

Machine bytestrings.

I mix string and bytestring terminology here due to bad C influences, but this module is specifically interested in bytestrings and their encoding. String/text encoding is handled in another module.

Note that the length prefix predicate is also defined here... because that's just Pascal-style bytestrings, extended to other types. I can't easily put it in an orphan module, because we define byte length for *all length-prefixed types* in one fell swoop.

Synopsis

Documentation

data Rep Source #

Bytestring representation.

Constructors

C

C-style bytestring. Arbitrary length, terminated with a null byte. Permits no null bytes inside the bytestring.

Pascal ISize Endianness

Pascal-style bytestring. Length defined in a prefixing integer of given size and endianness.

Instances

Instances details
Data Rep Source # 
Instance details

Defined in Binrep.Type.ByteString

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rep -> c Rep #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Rep #

toConstr :: Rep -> Constr #

dataTypeOf :: Rep -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Rep) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rep) #

gmapT :: (forall b. Data b => b -> b) -> Rep -> Rep #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rep -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rep -> r #

gmapQ :: (forall d. Data d => d -> u) -> Rep -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Rep -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rep -> m Rep #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rep -> m Rep #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rep -> m Rep #

Generic Rep Source # 
Instance details

Defined in Binrep.Type.ByteString

Associated Types

type Rep Rep :: Type -> Type #

Methods

from :: Rep -> Rep0 Rep x #

to :: Rep0 Rep x -> Rep #

Show Rep Source # 
Instance details

Defined in Binrep.Type.ByteString

Methods

showsPrec :: Int -> Rep -> ShowS #

show :: Rep -> String #

showList :: [Rep] -> ShowS #

Eq Rep Source # 
Instance details

Defined in Binrep.Type.ByteString

Methods

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

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

Predicate 'C ByteString Source #

A C-style bytestring must not contain any null bytes.

Instance details

Defined in Binrep.Type.ByteString

(irep ~ IRep 'U size, Bounded irep, Integral irep, Show irep, Typeable size, Typeable e) => Predicate ('Pascal size e :: Rep) ByteString Source # 
Instance details

Defined in Binrep.Type.ByteString

BLen (AsByteString 'C) Source # 
Instance details

Defined in Binrep.Type.ByteString

Associated Types

type CBLen (AsByteString 'C) :: Natural Source #

(itype ~ I 'U size end, irep ~ IRep 'U size, KnownNat (CBLen irep)) => BLen (AsByteString ('Pascal size end)) Source # 
Instance details

Defined in Binrep.Type.ByteString

Associated Types

type CBLen (AsByteString ('Pascal size end)) :: Natural Source #

Methods

blen :: AsByteString ('Pascal size end) -> BLenT Source #

Get (AsByteString 'C) Source # 
Instance details

Defined in Binrep.Type.ByteString

(itype ~ I 'U size end, irep ~ IRep 'U size, Integral irep, Get itype) => Get (AsByteString ('Pascal size end)) Source # 
Instance details

Defined in Binrep.Type.ByteString

Methods

get :: Getter (AsByteString ('Pascal size end)) Source #

Put (AsByteString 'C) Source # 
Instance details

Defined in Binrep.Type.ByteString

(itype ~ I 'U size end, irep ~ IRep 'U size, Put itype, Num irep) => Put (AsByteString ('Pascal size end)) Source # 
Instance details

Defined in Binrep.Type.ByteString

Methods

put :: AsByteString ('Pascal size end) -> Builder Source #

type Rep Rep Source # 
Instance details

Defined in Binrep.Type.ByteString

type CBLen (AsByteString 'C) Source # 
Instance details

Defined in Binrep.Type.ByteString

type CBLen (AsByteString 'C) = TypeError ('Text "No CBLen associated family instance defined for " :<>: 'ShowType (AsByteString 'C)) :: Natural
type CBLen (AsByteString ('Pascal size end)) Source # 
Instance details

Defined in Binrep.Type.ByteString

type CBLen (AsByteString ('Pascal size end)) = TypeError ('Text "No CBLen associated family instance defined for " :<>: 'ShowType (AsByteString ('Pascal size end))) :: Natural

type AsByteString (rep :: Rep) = Refined rep ByteString Source #

A bytestring using the given representation, stored in the Text type.