describe-0.4.0.5: Combinators for describing binary data structures

Safe HaskellNone
LanguageHaskell2010

Data.Serialize.Describe.Combinators.LE

Description

Little endian combinators.

All combinators take a function that takes the structure leing described (a) and produces the specified data type from it. Most of the time, this will le one of the structure's fields, which are all functions from the structure to the field type.

Documentation

newtype LE a Source #

Constructors

LE 

Fields

Instances
Enum a => Enum (LE a) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

Methods

succ :: LE a -> LE a #

pred :: LE a -> LE a #

toEnum :: Int -> LE a #

fromEnum :: LE a -> Int #

enumFrom :: LE a -> [LE a] #

enumFromThen :: LE a -> LE a -> [LE a] #

enumFromTo :: LE a -> LE a -> [LE a] #

enumFromThenTo :: LE a -> LE a -> LE a -> [LE a] #

Eq a => Eq (LE a) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

Methods

(==) :: LE a -> LE a -> Bool #

(/=) :: LE a -> LE a -> Bool #

Fractional a => Fractional (LE a) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

Methods

(/) :: LE a -> LE a -> LE a #

recip :: LE a -> LE a #

fromRational :: Rational -> LE a #

Integral a => Integral (LE a) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

Methods

quot :: LE a -> LE a -> LE a #

rem :: LE a -> LE a -> LE a #

div :: LE a -> LE a -> LE a #

mod :: LE a -> LE a -> LE a #

quotRem :: LE a -> LE a -> (LE a, LE a) #

divMod :: LE a -> LE a -> (LE a, LE a) #

toInteger :: LE a -> Integer #

Num a => Num (LE a) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

Methods

(+) :: LE a -> LE a -> LE a #

(-) :: LE a -> LE a -> LE a #

(*) :: LE a -> LE a -> LE a #

negate :: LE a -> LE a #

abs :: LE a -> LE a #

signum :: LE a -> LE a #

fromInteger :: Integer -> LE a #

Ord a => Ord (LE a) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

Methods

compare :: LE a -> LE a -> Ordering #

(<) :: LE a -> LE a -> Bool #

(<=) :: LE a -> LE a -> Bool #

(>) :: LE a -> LE a -> Bool #

(>=) :: LE a -> LE a -> Bool #

max :: LE a -> LE a -> LE a #

min :: LE a -> LE a -> LE a #

Read a => Read (LE a) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

Real a => Real (LE a) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

Methods

toRational :: LE a -> Rational #

Show a => Show (LE a) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

Methods

showsPrec :: Int -> LE a -> ShowS #

show :: LE a -> String #

showList :: [LE a] -> ShowS #

Describe (LE Double) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

Associated Types

type Context m (LE Double) :: Constraint Source #

Methods

describe :: (MonadTrans m, forall (x :: Type -> Type). Monad x => Monad (m x), Context m (LE Double)) => DescriptorM m (LE Double) (LE Double) Source #

Describe (LE Float) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

Associated Types

type Context m (LE Float) :: Constraint Source #

Methods

describe :: (MonadTrans m, forall (x :: Type -> Type). Monad x => Monad (m x), Context m (LE Float)) => DescriptorM m (LE Float) (LE Float) Source #

Describe (LE Int16) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

Associated Types

type Context m (LE Int16) :: Constraint Source #

Methods

describe :: (MonadTrans m, forall (x :: Type -> Type). Monad x => Monad (m x), Context m (LE Int16)) => DescriptorM m (LE Int16) (LE Int16) Source #

Describe (LE Int32) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

Associated Types

type Context m (LE Int32) :: Constraint Source #

Methods

describe :: (MonadTrans m, forall (x :: Type -> Type). Monad x => Monad (m x), Context m (LE Int32)) => DescriptorM m (LE Int32) (LE Int32) Source #

Describe (LE Int64) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

Associated Types

type Context m (LE Int64) :: Constraint Source #

Methods

describe :: (MonadTrans m, forall (x :: Type -> Type). Monad x => Monad (m x), Context m (LE Int64)) => DescriptorM m (LE Int64) (LE Int64) Source #

Describe (LE Word16) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

Associated Types

type Context m (LE Word16) :: Constraint Source #

Methods

describe :: (MonadTrans m, forall (x :: Type -> Type). Monad x => Monad (m x), Context m (LE Word16)) => DescriptorM m (LE Word16) (LE Word16) Source #

Describe (LE Word32) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

Associated Types

type Context m (LE Word32) :: Constraint Source #

Methods

describe :: (MonadTrans m, forall (x :: Type -> Type). Monad x => Monad (m x), Context m (LE Word32)) => DescriptorM m (LE Word32) (LE Word32) Source #

Describe (LE Word64) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

Associated Types

type Context m (LE Word64) :: Constraint Source #

Methods

describe :: (MonadTrans m, forall (x :: Type -> Type). Monad x => Monad (m x), Context m (LE Word64)) => DescriptorM m (LE Word64) (LE Word64) Source #

Num n => Nullable (LE n) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.FList

Methods

nullVal :: LE n Source #

type Context m (LE Double) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

type Context m (LE Double) = ()
type Context m (LE Float) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

type Context m (LE Float) = ()
type Context m (LE Int64) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

type Context m (LE Int64) = ()
type Context m (LE Int32) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

type Context m (LE Int32) = ()
type Context m (LE Int16) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

type Context m (LE Int16) = ()
type Context m (LE Word64) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

type Context m (LE Word64) = ()
type Context m (LE Word32) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

type Context m (LE Word32) = ()
type Context m (LE Word16) Source # 
Instance details

Defined in Data.Serialize.Describe.Combinators.LE

type Context m (LE Word16) = ()

w16 :: Integral i => (s -> i) -> Descriptor s i Source #

w32 :: Integral i => (s -> i) -> Descriptor s i Source #

w64 :: Integral i => (s -> i) -> Descriptor s i Source #

i16 :: Integral i => (s -> i) -> Descriptor s i Source #

i32 :: Integral i => (s -> i) -> Descriptor s i Source #

i64 :: Integral i => (s -> i) -> Descriptor s i Source #

f32 :: (Real f, Fractional f) => (s -> f) -> Descriptor s f Source #

f64 :: (Real f, Fractional f) => (s -> f) -> Descriptor s f Source #