haskus-binary-0.6.0.0: Haskus binary format manipulation

Safe HaskellNone
LanguageHaskell2010

Haskus.Format.Binary.Enum

Description

Store an Enum in the given backing word type

Synopsis

Documentation

data EnumField b a Source #

Store enum a as a b

Instances

Eq a => Eq (EnumField b a) Source # 

Methods

(==) :: EnumField b a -> EnumField b a -> Bool #

(/=) :: EnumField b a -> EnumField b a -> Bool #

Show a => Show (EnumField b a) Source # 

Methods

showsPrec :: Int -> EnumField b a -> ShowS #

show :: EnumField b a -> String #

showList :: [EnumField b a] -> ShowS #

(Storable b, Integral b, CEnum a) => Storable (EnumField b a) Source # 

Methods

peekIO :: Ptr (EnumField b a) -> IO (EnumField b a) Source #

pokeIO :: Ptr (EnumField b a) -> EnumField b a -> IO () Source #

alignment :: EnumField b a -> Word Source #

sizeOf :: EnumField b a -> Word Source #

(Integral b, StaticStorable b, CEnum a) => StaticStorable (EnumField b a) Source # 

Associated Types

type SizeOf (EnumField b a) :: Nat Source #

type Alignment (EnumField b a) :: Nat Source #

Methods

staticPeekIO :: Ptr (EnumField b a) -> IO (EnumField b a) Source #

staticPokeIO :: Ptr (EnumField b a) -> EnumField b a -> IO () Source #

CEnum a => Field (EnumField b a) Source # 

Methods

fromField :: Integral b => EnumField b a -> b

toField :: Integral b => b -> EnumField b a

type SizeOf (EnumField b a) Source # 
type SizeOf (EnumField b a) = SizeOf b
type Alignment (EnumField b a) Source # 

class CEnum a where Source #

By default, use fromEnumtoEnum to convert fromto an Integral.

But it can be overloaded to perform transformation before using fromEnum/toEnum. E.g. if values are shifted by 1 compared to Enum values, define fromCEnum = (+1) . fromIntegral . fromEnum

Methods

fromCEnum :: Integral b => a -> b Source #

fromCEnum :: (Enum a, Integral b) => a -> b Source #

toCEnum :: Integral b => b -> a Source #

toCEnum :: (Enum a, Integral b) => b -> a Source #

fromEnumField :: EnumField b a -> a Source #

Read an enum field

toEnumField :: a -> EnumField b a Source #

Create an enum field

makeEnum :: forall a i. (Data a, Integral i) => i -> a Source #

Make an enum from a number (0 indexed)

makeEnumMaybe :: forall a i. (Data a, Integral i) => i -> Maybe a Source #

Make an enum with the last constructor taking a parameter for the rest of the range, but don't build the last constructor

E.g., data T = A | B | C | D Word8 makeEnumMaybe :: Int -> T makeEnumMaybe x = case x of 0 -> Just A 1 -> Just B 2 -> Just C n -> Nothing

makeEnumWithCustom :: forall a i. (Data a, Integral i) => i -> a Source #

Make an enum with the last constructor taking a parameter for the rest of the range

E.g., data T = A | B | C | D Word8 makeEnumWithCustom :: Int -> T makeEnumWithCustom x = case x of 0 -> A 1 -> B 2 -> C n -> D (n - 3)