haskus-binary-0.6.0.0: Haskus binary format manipulation

Safe HaskellNone
LanguageHaskell2010

Haskus.Format.Binary.Unum

Contents

Synopsis

Documentation

data Unum xs Source #

An Unum

0 (and its reciprocal) is always included. Numbers have to be >= 1 and sorted.

e.g., Unum '[] => 0 .. 0 .. 0 Unum '[I 1] => 0 .. -1 .. 0 .. 1 .. 0 Unum '[I 1, I 2] => 0 .. -2 .. -1 .. -2 .. 0 .. 2 .. 1 .. 2 .. 0 Unum '[I 1, PI] => 0 .. -PI .. -1 .. -PI .. 0 .. PI .. 1 .. PI .. 0

class UnumNum a where Source #

Minimal complete definition

unumLabel

Methods

unumLabel :: a -> String Source #

Instances

UnumNum x => UnumNum (Rcp x) Source # 

Methods

unumLabel :: Rcp x -> String Source #

UnumNum x => UnumNum (Neg x) Source # 

Methods

unumLabel :: Neg x -> String Source #

KnownNat n => UnumNum (I n) Source # 

Methods

unumLabel :: I n -> String Source #

data I n Source #

Instances

KnownNat n => UnumNum (I n) Source # 

Methods

unumLabel :: I n -> String Source #

newtype U u Source #

Constructors

U (BackingWord u) 

Instances

Eq (BackingWord u) => Eq (U u) Source # 

Methods

(==) :: U u -> U u -> Bool #

(/=) :: U u -> U u -> Bool #

(HFoldr' GetLabel [String] v [String], (~) [*] v (UnumMembers u), Integral (BackingWord u)) => Show (U u) Source # 

Methods

showsPrec :: Int -> U u -> ShowS #

show :: U u -> String #

showList :: [U u] -> ShowS #

data Neg a Source #

Instances

UnumNum x => UnumNum (Neg x) Source # 

Methods

unumLabel :: Neg x -> String Source #

data Rcp a Source #

Instances

UnumNum x => UnumNum (Rcp x) Source # 

Methods

unumLabel :: Rcp x -> String Source #

type Infinite = Rcp (I 0) Source #

type family Log2 n where ... Source #

Equations

Log2 0 = 0 
Log2 1 = 0 
Log2 n = Log2 (Div2 n) + 1 

type family UnumNumbers x where ... Source #

Compute the precise numbers set

Equations

UnumNumbers (Unum xs) = Nub (AddNeg (AddRcp (Snoc xs Infinite))) 

type family UnumSize x where ... Source #

Compute the number of bits required

Equations

UnumSize x = 1 + Log2 (Length (UnumNumbers x)) 

type family BackingWord x where ... Source #

Backing word for the unum

Equations

BackingWord x = WordAtLeast (UnumSize x) 

data UBit Source #

Uncertainty bit

Constructors

ExactNumber

Exact number

OpenInterval

OpenInterval above the exact number

Instances

Eq UBit Source # 

Methods

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

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

Show UBit Source # 

Methods

showsPrec :: Int -> UBit -> ShowS #

show :: UBit -> String #

showList :: [UBit] -> ShowS #

unumSize :: forall u. KnownNat (UnumSize u) => Word Source #

Size of an unum in bits

unumZero :: forall u. (Num (BackingWord u), Bits (BackingWord u), Encodable (I 0) u) => U u Source #

Zero

unumInfinite :: forall u. (Num (BackingWord u), Bits (BackingWord u), Encodable Infinite u) => U u Source #

Infinite

unumEncode :: forall u x i. (i ~ IndexOf (Simplify x) (UnumIndexables u), KnownNat i, Num (BackingWord u), Bits (BackingWord u)) => UBit -> U u Source #

Encode a number

unumBits :: forall u. (FiniteBits (BackingWord u), KnownNat (UnumSize u)) => U u -> String Source #

unumNegate :: forall u. (FiniteBits (BackingWord u), Num (BackingWord u), KnownNat (UnumSize u)) => U u -> U u Source #

Negate a number

unumReciprocate :: forall u. (FiniteBits (BackingWord u), Num (BackingWord u), KnownNat (UnumSize u)) => U u -> U u Source #

Reciprocate a number

unumLabels :: forall u v. (HFoldr' GetLabel [String] v [String], v ~ UnumMembers u) => [String] Source #

Unum labels

data Sign Source #

Constructors

Positive 
Negative 
NoSign 

Instances

Eq Sign Source # 

Methods

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

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

Show Sign Source # 

Methods

showsPrec :: Int -> Sign -> ShowS #

show :: Sign -> String #

showList :: [Sign] -> ShowS #

unumSign :: forall u. (Bits (BackingWord u), KnownNat (UnumSize u)) => U u -> Sign Source #

Get unum sign

SORN (bit-sets)

data SORN u Source #

Instances

(KnownNat (SORNSize u), Bits (SORNBackingWord u), Num (BackingWord u), Integral (BackingWord u), HFoldr' GetLabel [String] v [String], (~) [*] v (UnumMembers u)) => Show (SORN u) Source # 

Methods

showsPrec :: Int -> SORN u -> ShowS #

show :: SORN u -> String #

showList :: [SORN u] -> ShowS #

type family SORNBackingWord u where ... Source #

Equations

SORNBackingWord u = WordAtLeast (SORNSize u) 

sornBits :: forall u s. (FiniteBits (SORNBackingWord u), KnownNat (UnumSize u), s ~ SORNSize u, KnownNat s) => SORN u -> String Source #

Show SORN bits

sornSize :: forall u s. (s ~ SORNSize u, KnownNat s) => Word Source #

Size of a SORN in bits

sornEmpty :: Bits (SORNBackingWord u) => SORN u Source #

Empty SORN

sornFull :: forall u. (FiniteBits (SORNBackingWord u), KnownNat (SORNSize u)) => SORN u Source #

Full SORN

sornNonInfinite :: forall u. (Bits (SORNBackingWord u), Integral (BackingWord u), Bits (BackingWord u), Encodable Infinite u) => SORN u Source #

Full SORN without infinite

sornNonZero :: (Bits (SORNBackingWord u), Integral (BackingWord u), Bits (BackingWord u), Encodable (I 0) u) => SORN u Source #

Full SORN without infinite

sornSingle :: (Integral (BackingWord u), Bits (SORNBackingWord u)) => U u -> SORN u Source #

SORN singleton

sornInsert :: forall u. (Bits (SORNBackingWord u), Integral (BackingWord u)) => SORN u -> U u -> SORN u Source #

Insert in a SORN

sornMember :: forall u. (Bits (SORNBackingWord u), Integral (BackingWord u)) => SORN u -> U u -> Bool Source #

Test membership in a SORN

sornRemove :: forall u. (Bits (SORNBackingWord u), Integral (BackingWord u)) => SORN u -> U u -> SORN u Source #

Remove in a SORN

sornUnion :: forall u. Bits (SORNBackingWord u) => SORN u -> SORN u -> SORN u Source #

Union of two SORNs

sornIntersect :: forall u. Bits (SORNBackingWord u) => SORN u -> SORN u -> SORN u Source #

Intersection of two SORNs

sornComplement :: Bits (SORNBackingWord u) => SORN u -> SORN u Source #

Complement the SORN

sornNegate :: forall u. (FiniteBits (SORNBackingWord u), FiniteBits (BackingWord u), Integral (BackingWord u), KnownNat (SORNSize u), KnownNat (UnumSize u)) => SORN u -> SORN u Source #

Negate a SORN

sornElems :: forall u s. (s ~ SORNSize u, KnownNat s, Bits (SORNBackingWord u), Num (BackingWord u)) => SORN u -> [U u] Source #

Elements in the SORN

sornFromElems :: (Integral (BackingWord u), Bits (SORNBackingWord u)) => [U u] -> SORN u Source #

Create a SORN from its elements

sornFromTo :: forall u. (Integral (BackingWord u), Bits (SORNBackingWord u), FiniteBits (BackingWord u), KnownNat (UnumSize u)) => U u -> U u -> SORN u Source #

Create a contiguous SORN from two elements

class SornAdd u where Source #

Minimal complete definition

sornAddU

Methods

sornAddU :: U u -> U u -> SORN u Source #

Add two Unums

sornAdd :: (KnownNat (SORNSize u), Bits (SORNBackingWord u), Num (BackingWord u)) => SORN u -> SORN u -> SORN u Source #

Add two SORNs

sornAddDep :: (KnownNat (SORNSize u), Bits (SORNBackingWord u), Num (BackingWord u)) => SORN u -> SORN u Source #

Add a SORN with itself

sornSubU :: (FiniteBits (BackingWord u), Num (BackingWord u), KnownNat (UnumSize u)) => U u -> U u -> SORN u Source #

Subtract two Unums

sornSub :: (KnownNat (SORNSize u), Bits (SORNBackingWord u), FiniteBits (BackingWord u), Num (BackingWord u), KnownNat (UnumSize u)) => SORN u -> SORN u -> SORN u Source #

Subtract two SORNS

sornSubDep :: (KnownNat (SORNSize u), Bits (SORNBackingWord u), FiniteBits (BackingWord u), Num (BackingWord u), KnownNat (UnumSize u)) => SORN u -> SORN u Source #

Subtract a SORN with itself

Contiguous SORN

newtype CSORN u Source #

Constructors

CSORN (BitFields (CSORNBackingWord u) '[BitField (UnumSize u) "start" (BackingWord u), BitField (UnumSize u) "count" (BackingWord u)]) 

Instances

(KnownNat (SORNSize u), KnownNat (UnumSize u), FiniteBits (BackingWord u), Bits (CSORNBackingWord u), Integral (CSORNBackingWord u), Num (BackingWord u), Integral (BackingWord u), HFoldr' GetLabel [String] v [String], Field (BackingWord u), Bits (SORNBackingWord u), FiniteBits (SORNBackingWord u), (~) [*] v (UnumMembers u)) => Show (CSORN u) Source # 

Methods

showsPrec :: Int -> CSORN u -> ShowS #

show :: CSORN u -> String #

showList :: [CSORN u] -> ShowS #

csornSize :: forall u s. (s ~ CSORNSize u, KnownNat s) => Word Source #

Size of a contiguous SORN in bits

csornBits :: forall u s. (FiniteBits (CSORNBackingWord u), KnownNat (UnumSize u), s ~ CSORNSize u, KnownNat s) => CSORN u -> String Source #

Show contiguous SORN bits

csornToSorn :: forall u. (KnownNat (UnumSize u), Num (BackingWord u), Integral (BackingWord u), Integral (CSORNBackingWord u), Bits (CSORNBackingWord u), FiniteBits (BackingWord u), Bits (SORNBackingWord u), Field (BackingWord u), KnownNat (SORNSize u), FiniteBits (SORNBackingWord u)) => CSORN u -> SORN u Source #

Convert a contiguous SORN into a SORN

csornEmpty :: forall u. Bits (CSORNBackingWord u) => CSORN u Source #

Empty contigiuous SORN

csornIsEmpty :: forall u. Bits (CSORNBackingWord u) => CSORN u -> Bool Source #

Test if a contigiuous SORN is empty

csornFromTo :: forall u. (Num (BackingWord u), Bits (BackingWord u), KnownNat (UnumSize u), KnownNat (SORNSize u), FiniteBits (BackingWord u), Integral (CSORNBackingWord u), Bits (CSORNBackingWord u), Field (BackingWord u), Integral (BackingWord u)) => U u -> U u -> CSORN u Source #

Contiguous SORN build

csornFull :: forall u. (Bits (CSORNBackingWord u), Integral (CSORNBackingWord u), Integral (BackingWord u), KnownNat (UnumSize u), Field (BackingWord u)) => CSORN u Source #

Full contiguous SORN

csornSingle :: forall u. (Bits (CSORNBackingWord u), Integral (CSORNBackingWord u), Integral (BackingWord u), KnownNat (UnumSize u), Field (BackingWord u)) => U u -> CSORN u Source #

Contiguous SORN singleton