haskus-binary-1.5: Haskus binary format manipulation

Safe HaskellNone
LanguageHaskell2010

Haskus.Binary.Union

Description

Union (as in C)

Unions are storable and can contain any storable data.

Use fromUnion to read an alternative:

{--}

getUnion :: IO (Union '[Word16, Word32, Word64])
getUnion = ...

test = do
   u <- getUnion

   -- to get one of the member
   let v = fromUnion u :: Word16
   let v = fromUnion u :: Word32
   let v = fromUnion u :: Word64

   -- This won't compile (Word8 is not a member of the union)
   let v = fromUnion u :: Word8

Use toUnion to create a new union:

let
   u2 :: Union '[Word32, Vector 4 Word8]
   u2 = toUnion (0x12345678 :: Word32)
Synopsis

Documentation

data Union (x :: [*]) Source #

An union

We use a list of types as a parameter.

The union is just a pointer to a buffer containing the value(s). The size of the buffer is implicitly known from the types in the list.

Instances
Show (Union x) Source # 
Instance details

Defined in Haskus.Binary.Union

Methods

showsPrec :: Int -> Union x -> ShowS #

show :: Union x -> String #

showList :: [Union x] -> ShowS #

(HFoldr' FoldSizeOf Word l Word, HFoldr' FoldAlignment Word l Word) => Storable (Union l) Source # 
Instance details

Defined in Haskus.Binary.Union

Methods

sizeOf :: Union l -> Int #

alignment :: Union l -> Int #

peekElemOff :: Ptr (Union l) -> Int -> IO (Union l) #

pokeElemOff :: Ptr (Union l) -> Int -> Union l -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Union l) #

pokeByteOff :: Ptr b -> Int -> Union l -> IO () #

peek :: Ptr (Union l) -> IO (Union l) #

poke :: Ptr (Union l) -> Union l -> IO () #

(HFoldr' FoldSizeOf Word l Word, HFoldr' FoldAlignment Word l Word) => Storable (Union l) Source # 
Instance details

Defined in Haskus.Binary.Union

Methods

peekIO :: Ptr (Union l) -> IO (Union l) Source #

pokeIO :: Ptr (Union l) -> Union l -> IO () Source #

alignment :: Union l -> Word Source #

sizeOf :: Union l -> Word Source #

(KnownNat (ListMax (MapSizeOf fs)), KnownNat (ListMax (MapAlignment fs))) => StaticStorable (Union fs) Source # 
Instance details

Defined in Haskus.Binary.Union

Associated Types

type SizeOf (Union fs) :: Nat Source #

type Alignment (Union fs) :: Nat Source #

Methods

staticPeekIO :: Ptr (Union fs) -> IO (Union fs) Source #

staticPokeIO :: Ptr (Union fs) -> Union fs -> IO () Source #

type SizeOf (Union fs) Source # 
Instance details

Defined in Haskus.Binary.Union

type SizeOf (Union fs)
type Alignment (Union fs) Source # 
Instance details

Defined in Haskus.Binary.Union

type Alignment (Union fs)

fromUnion :: (Storable a, Member a l) => Union l -> a Source #

Retrieve a union member from its type

toUnion :: forall a l. (Storable (Union l), Storable a, Member a l) => a -> Union l Source #

Create a new union from one of the union types

toUnionZero :: forall a l. (Storable (Union l), Storable a, Member a l) => a -> Union l Source #

Like toUnion but set the remaining bytes to 0