isobmff-builder-0.11.3.0: A (bytestring-) builder for the ISO-14496-12 base media file format

Safe HaskellNone
LanguageHaskell2010

Data.Type.BitRecords.Assert

Description

Type - level assertion utility leveraging custom TypeErrors

Synopsis

Documentation

type family Assert (cond :: Assertion a) (x :: a) :: a where ... Source #

Apply an Assertion to some value and return that value if the assertion holds, otherwise throw a TypeError.

Equations

Assert cond x = ProcessCheckResult (Check cond x) x 

type Assertion a = TyFun a (Maybe ErrorMessage) -> Type Source #

Make an assertion by creating a phantom data type which contains TyFun a (Maybe ErrorMessage) as last parameter. Check is used by Assert the apply the TyFuns which are specialized in this definition to have the return type Maybe ErrorMessage.

type family Check (f :: Assertion a) (x :: a) :: Maybe ErrorMessage Source #

Apply Assertions to the actual values.

Instances

type Check Nat (NatLE n) x Source # 
type Check Nat (NatLE n) x = If (Maybe ErrorMessage) ((<=?) x n) (Nothing ErrorMessage) (Just ErrorMessage ((:$$:) ((:<>:) (Text "Natural too big: ") (ShowType Nat x)) ((:<>:) (Text "Required: <=") (ShowType Nat n))))
type Check Nat (NatGE n) x Source # 
type Check Nat (NatGE n) x = If (Maybe ErrorMessage) ((<=?) n x) (Nothing ErrorMessage) (Just ErrorMessage ((:$$:) ((:<>:) (Text "Natural too small: ") (ShowType Nat x)) ((:<>:) (Text "Required: >=") (ShowType Nat n))))
type Check Nat (NatIn from to) n Source # 
type Check Nat (NatIn from to) n
type Check k (LengthIn k from to) xs Source # 
type Check k (LengthIn k from to) xs = Check Nat (NatIn from to) (CountElementsForLengthIn k xs)
type Check (Maybe ErrorMessage) ((@&&) (Maybe ErrorMessage) a1 a2) x Source # 

type (?::) x cond = Assert cond x infixr 0 Source #

Assert that a given type satisfies some condition defined via Check instances. This is only an alias for Assert

data (@&&) :: Assertion a -> Assertion a -> Assertion a Source #

Assert that two assertions both hold

data NatLE :: Nat -> Assertion Nat Source #

Assert that a Nat is less than or equal to an other Nat.

Instances

type Check Nat (NatLE n) x Source # 
type Check Nat (NatLE n) x = If (Maybe ErrorMessage) ((<=?) x n) (Nothing ErrorMessage) (Just ErrorMessage ((:$$:) ((:<>:) (Text "Natural too big: ") (ShowType Nat x)) ((:<>:) (Text "Required: <=") (ShowType Nat n))))

data NatGE :: Nat -> Assertion Nat Source #

Assert that a Nat is greater than or equal to an other Nat.

Instances

type Check Nat (NatGE n) x Source # 
type Check Nat (NatGE n) x = If (Maybe ErrorMessage) ((<=?) n x) (Nothing ErrorMessage) (Just ErrorMessage ((:$$:) ((:<>:) (Text "Natural too small: ") (ShowType Nat x)) ((:<>:) (Text "Required: >=") (ShowType Nat n))))

data NatIn :: Nat -> Nat -> Assertion Nat Source #

Assert that a Nat is in a specific range.

Instances

type Check Nat (NatIn from to) n Source # 
type Check Nat (NatIn from to) n

data LengthIn :: Nat -> Nat -> Assertion a Source #

Assert that a list's length falls into a given range. This is generalized from actual lists; everything with a CountElementsForLengthIn instance can be asserted.

Instances

type Check k (LengthIn k from to) xs Source # 
type Check k (LengthIn k from to) xs = Check Nat (NatIn from to) (CountElementsForLengthIn k xs)

type family CountElementsForLengthIn (xs :: k) :: Nat Source #

Instances

type CountElementsForLengthIn [k] ([] k) Source # 
type CountElementsForLengthIn [k] ([] k) = 0
type CountElementsForLengthIn [a] ((:) a x xs) Source # 
type CountElementsForLengthIn [a] ((:) a x xs) = (+) 1 (CountElementsForLengthIn [a] xs)