zm-0.3.2: Language independent, reproducible, absolute types

Safe HaskellNone
LanguageHaskell2010

ZM.Types

Contents

Synopsis

Model

type AbsTypeModel = TypeModel Identifier Identifier (ADTRef AbsRef) AbsRef Source #

An absolute type model, an absolute type and its associated environment

type AbsType = Type AbsRef Source #

An absolute type, a type identifier that depends only on the definition of the type

data AbsRef Source #

A reference to an absolute data type definition, in the form of a hash of the data type definition itself data AbsRef = AbsRef (SHA3_256_6 AbsADT) deriving (Eq, Ord, Show, NFData, Generic, Flat)

Constructors

AbsRef (SHAKE128_48 AbsADT) 

Instances

Eq AbsRef Source # 

Methods

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

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

Ord AbsRef Source # 
Show AbsRef Source # 
Generic AbsRef Source # 

Associated Types

type Rep AbsRef :: * -> * #

Methods

from :: AbsRef -> Rep AbsRef x #

to :: Rep AbsRef x -> AbsRef #

NFData AbsRef Source # 

Methods

rnf :: AbsRef -> () #

Flat AbsRef Source # 
Model AbsRef Source # 
type Rep AbsRef Source # 
type Rep AbsRef = D1 (MetaData "AbsRef" "ZM.Types" "zm-0.3.2-9EffK4RA8nV74pYjwjqtDn" False) (C1 (MetaCons "AbsRef" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (SHAKE128_48 AbsADT))))

absRef :: Flat r => r -> AbsRef Source #

Return the absolute reference of the given value

type AbsADT = ADT Identifier Identifier (ADTRef AbsRef) Source #

An absolute data type definition, a definition that refers only to other absolute definitions

type AbsEnv = TypeEnv Identifier Identifier (ADTRef AbsRef) AbsRef Source #

An environments of absolute types

data ADTRef r Source #

A reference inside an ADT to another ADT

Constructors

Var Word8

Variable, standing for a type

Rec

Recursive reference to the ADT itself

Ext r

Reference to another ADT

Instances

Functor ADTRef Source # 

Methods

fmap :: (a -> b) -> ADTRef a -> ADTRef b #

(<$) :: a -> ADTRef b -> ADTRef a #

Foldable ADTRef Source # 

Methods

fold :: Monoid m => ADTRef m -> m #

foldMap :: Monoid m => (a -> m) -> ADTRef a -> m #

foldr :: (a -> b -> b) -> b -> ADTRef a -> b #

foldr' :: (a -> b -> b) -> b -> ADTRef a -> b #

foldl :: (b -> a -> b) -> b -> ADTRef a -> b #

foldl' :: (b -> a -> b) -> b -> ADTRef a -> b #

foldr1 :: (a -> a -> a) -> ADTRef a -> a #

foldl1 :: (a -> a -> a) -> ADTRef a -> a #

toList :: ADTRef a -> [a] #

null :: ADTRef a -> Bool #

length :: ADTRef a -> Int #

elem :: Eq a => a -> ADTRef a -> Bool #

maximum :: Ord a => ADTRef a -> a #

minimum :: Ord a => ADTRef a -> a #

sum :: Num a => ADTRef a -> a #

product :: Num a => ADTRef a -> a #

Traversable ADTRef Source # 

Methods

traverse :: Applicative f => (a -> f b) -> ADTRef a -> f (ADTRef b) #

sequenceA :: Applicative f => ADTRef (f a) -> f (ADTRef a) #

mapM :: Monad m => (a -> m b) -> ADTRef a -> m (ADTRef b) #

sequence :: Monad m => ADTRef (m a) -> m (ADTRef a) #

Eq r => Eq (ADTRef r) Source # 

Methods

(==) :: ADTRef r -> ADTRef r -> Bool #

(/=) :: ADTRef r -> ADTRef r -> Bool #

Ord r => Ord (ADTRef r) Source # 

Methods

compare :: ADTRef r -> ADTRef r -> Ordering #

(<) :: ADTRef r -> ADTRef r -> Bool #

(<=) :: ADTRef r -> ADTRef r -> Bool #

(>) :: ADTRef r -> ADTRef r -> Bool #

(>=) :: ADTRef r -> ADTRef r -> Bool #

max :: ADTRef r -> ADTRef r -> ADTRef r #

min :: ADTRef r -> ADTRef r -> ADTRef r #

Show r => Show (ADTRef r) Source # 

Methods

showsPrec :: Int -> ADTRef r -> ShowS #

show :: ADTRef r -> String #

showList :: [ADTRef r] -> ShowS #

Generic (ADTRef r) Source # 

Associated Types

type Rep (ADTRef r) :: * -> * #

Methods

from :: ADTRef r -> Rep (ADTRef r) x #

to :: Rep (ADTRef r) x -> ADTRef r #

NFData r => NFData (ADTRef r) Source # 

Methods

rnf :: ADTRef r -> () #

Flat r => Flat (ADTRef r) Source # 

Methods

encode :: ADTRef r -> Encoding #

decode :: Get (ADTRef r) #

size :: ADTRef r -> NumBits -> NumBits #

Model a => Model (ADTRef a) Source # 

Methods

envType :: Proxy * (ADTRef a) -> State Env HType #

type Rep (ADTRef r) Source # 

getADTRef :: ADTRef a -> Maybe a Source #

Return an external reference, if present

asIdentifier :: String -> Validation Errors Identifier Source #

Validate a string as an Identifier

>>> asIdentifier ""
Failure ["identifier cannot be empty"]
>>> asIdentifier "Id_1"
Success (Name (UnicodeLetter 'I') [UnicodeLetterOrNumberOrLine 'd',UnicodeLetterOrNumberOrLine '_',UnicodeLetterOrNumberOrLine '1'])
>>> asIdentifier "a*^"
Failure ["In a*^: '*' is not an Unicode Letter or Number or a _","In a*^: '^' is not an Unicode Letter or Number or a _"]
>>> asIdentifier "<>"
Success (Symbol (Cons (UnicodeSymbol '<') (Elem (UnicodeSymbol '>'))))

data Identifier Source #

An Identifier, the name of an ADT

Instances

Eq Identifier Source # 
Ord Identifier Source # 
Show Identifier Source # 
Generic Identifier Source # 

Associated Types

type Rep Identifier :: * -> * #

NFData Identifier Source # 

Methods

rnf :: Identifier -> () #

Flat Identifier Source # 
Model Identifier Source # 
Convertible String Identifier Source # 
Convertible Identifier String Source # 
type Rep Identifier Source # 

data UnicodeLetter Source #

A character that is included in one of the following Unicode classes: UppercaseLetter LowercaseLetter TitlecaseLetter ModifierLetter OtherLetter

Constructors

UnicodeLetter Char 

data UnicodeLetterOrNumberOrLine Source #

A character that is either a UnicodeLetter, a UnicodeNumber or the special character '_'

Instances

Eq UnicodeLetterOrNumberOrLine Source # 
Ord UnicodeLetterOrNumberOrLine Source # 
Show UnicodeLetterOrNumberOrLine Source # 
Generic UnicodeLetterOrNumberOrLine Source # 
NFData UnicodeLetterOrNumberOrLine Source # 
Flat UnicodeLetterOrNumberOrLine Source # 
Model UnicodeLetterOrNumberOrLine Source # 
Flat [UnicodeLetterOrNumberOrLine] Source # 
type Rep UnicodeLetterOrNumberOrLine Source # 
type Rep UnicodeLetterOrNumberOrLine = D1 (MetaData "UnicodeLetterOrNumberOrLine" "ZM.Types" "zm-0.3.2-9EffK4RA8nV74pYjwjqtDn" False) (C1 (MetaCons "UnicodeLetterOrNumberOrLine" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char)))

data UnicodeSymbol Source #

A character that is included in one of the following Unicode classes: MathSymbol CurrencySymbol ModifierSymbol OtherSymbol

Constructors

UnicodeSymbol Char 

data SHA3_256_6 a Source #

A hash of a value, the first 6 bytes of the value's SHA3-256 hash

Instances

Eq (SHA3_256_6 a) Source # 

Methods

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

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

Ord (SHA3_256_6 a) Source # 
Show (SHA3_256_6 a) Source # 
Generic (SHA3_256_6 a) Source # 

Associated Types

type Rep (SHA3_256_6 a) :: * -> * #

Methods

from :: SHA3_256_6 a -> Rep (SHA3_256_6 a) x #

to :: Rep (SHA3_256_6 a) x -> SHA3_256_6 a #

NFData (SHA3_256_6 a) Source # 

Methods

rnf :: SHA3_256_6 a -> () #

Flat (SHA3_256_6 a) Source # 
Model a => Model (SHA3_256_6 a) Source # 
type Rep (SHA3_256_6 a) Source # 

data SHAKE128_48 a Source #

A hash of a value, the first 48 bits (6 bytes) of the value's SHAKE128 hash

Instances

Eq (SHAKE128_48 a) Source # 
Ord (SHAKE128_48 a) Source # 
Show (SHAKE128_48 a) Source # 
Generic (SHAKE128_48 a) Source # 

Associated Types

type Rep (SHAKE128_48 a) :: * -> * #

Methods

from :: SHAKE128_48 a -> Rep (SHAKE128_48 a) x #

to :: Rep (SHAKE128_48 a) x -> SHAKE128_48 a #

NFData (SHAKE128_48 a) Source # 

Methods

rnf :: SHAKE128_48 a -> () #

Flat (SHAKE128_48 a) Source # 
Model a => Model (SHAKE128_48 a) Source # 
type Rep (SHAKE128_48 a) Source # 

data NonEmptyList a Source #

A list that contains at least one element

Constructors

Elem a 
Cons a (NonEmptyList a) 

Instances

Functor NonEmptyList Source # 

Methods

fmap :: (a -> b) -> NonEmptyList a -> NonEmptyList b #

(<$) :: a -> NonEmptyList b -> NonEmptyList a #

Foldable NonEmptyList Source # 

Methods

fold :: Monoid m => NonEmptyList m -> m #

foldMap :: Monoid m => (a -> m) -> NonEmptyList a -> m #

foldr :: (a -> b -> b) -> b -> NonEmptyList a -> b #

foldr' :: (a -> b -> b) -> b -> NonEmptyList a -> b #

foldl :: (b -> a -> b) -> b -> NonEmptyList a -> b #

foldl' :: (b -> a -> b) -> b -> NonEmptyList a -> b #

foldr1 :: (a -> a -> a) -> NonEmptyList a -> a #

foldl1 :: (a -> a -> a) -> NonEmptyList a -> a #

toList :: NonEmptyList a -> [a] #

null :: NonEmptyList a -> Bool #

length :: NonEmptyList a -> Int #

elem :: Eq a => a -> NonEmptyList a -> Bool #

maximum :: Ord a => NonEmptyList a -> a #

minimum :: Ord a => NonEmptyList a -> a #

sum :: Num a => NonEmptyList a -> a #

product :: Num a => NonEmptyList a -> a #

Traversable NonEmptyList Source # 

Methods

traverse :: Applicative f => (a -> f b) -> NonEmptyList a -> f (NonEmptyList b) #

sequenceA :: Applicative f => NonEmptyList (f a) -> f (NonEmptyList a) #

mapM :: Monad m => (a -> m b) -> NonEmptyList a -> m (NonEmptyList b) #

sequence :: Monad m => NonEmptyList (m a) -> m (NonEmptyList a) #

Eq a => Eq (NonEmptyList a) Source # 
Ord a => Ord (NonEmptyList a) Source # 
Show a => Show (NonEmptyList a) Source # 
Generic (NonEmptyList a) Source # 

Associated Types

type Rep (NonEmptyList a) :: * -> * #

Methods

from :: NonEmptyList a -> Rep (NonEmptyList a) x #

to :: Rep (NonEmptyList a) x -> NonEmptyList a #

NFData a => NFData (NonEmptyList a) Source # 

Methods

rnf :: NonEmptyList a -> () #

Flat a => Flat (NonEmptyList a) Source # 
Model a => Model (NonEmptyList a) Source # 
type Rep (NonEmptyList a) Source # 

nonEmptyList :: [a] -> NonEmptyList a Source #

Convert a list to a NonEmptyList, returns an error if the list is empty

data Word7 Source #

A 7 bits unsigned integer data Word7 = V0 .. V127

Instances

Eq Word7 Source # 

Methods

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

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

Ord Word7 Source # 

Methods

compare :: Word7 -> Word7 -> Ordering #

(<) :: Word7 -> Word7 -> Bool #

(<=) :: Word7 -> Word7 -> Bool #

(>) :: Word7 -> Word7 -> Bool #

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

max :: Word7 -> Word7 -> Word7 #

min :: Word7 -> Word7 -> Word7 #

Show Word7 Source # 

Methods

showsPrec :: Int -> Word7 -> ShowS #

show :: Word7 -> String #

showList :: [Word7] -> ShowS #

Generic Word7 Source # 

Associated Types

type Rep Word7 :: * -> * #

Methods

from :: Word7 -> Rep Word7 x #

to :: Rep Word7 x -> Word7 #

Model Word7 Source # 
type Rep Word7 Source # 
type Rep Word7 = D1 (MetaData "Word7" "ZM.Type.Words" "zm-0.3.2-9EffK4RA8nV74pYjwjqtDn" False) (C1 (MetaCons "Word7" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word8)))

Encodings

data UTF16LEEncoding Source #

UTF-16 Little Endian Encoding

Constructors

UTF16LEEncoding 

Exceptions

Other Re-exports

class NFData a #

A class of types that can be fully evaluated.

Since: 1.1.0.0

Instances

NFData Bool 

Methods

rnf :: Bool -> () #

NFData Char 

Methods

rnf :: Char -> () #

NFData Double 

Methods

rnf :: Double -> () #

NFData Float 

Methods

rnf :: Float -> () #

NFData Int 

Methods

rnf :: Int -> () #

NFData Int8 

Methods

rnf :: Int8 -> () #

NFData Int16 

Methods

rnf :: Int16 -> () #

NFData Int32 

Methods

rnf :: Int32 -> () #

NFData Int64 

Methods

rnf :: Int64 -> () #

NFData Integer 

Methods

rnf :: Integer -> () #

NFData Word 

Methods

rnf :: Word -> () #

NFData Word8 

Methods

rnf :: Word8 -> () #

NFData Word16 

Methods

rnf :: Word16 -> () #

NFData Word32 

Methods

rnf :: Word32 -> () #

NFData Word64 

Methods

rnf :: Word64 -> () #

NFData CallStack

Since: 1.4.2.0

Methods

rnf :: CallStack -> () #

NFData TypeRep

NOTE: Only defined for base-4.8.0.0 and later

Since: 1.4.0.0

Methods

rnf :: TypeRep -> () #

NFData () 

Methods

rnf :: () -> () #

NFData TyCon

NOTE: Only defined for base-4.8.0.0 and later

Since: 1.4.0.0

Methods

rnf :: TyCon -> () #

NFData Natural

Since: 1.4.0.0

Methods

rnf :: Natural -> () #

NFData Void

Defined as rnf = absurd.

Since: 1.4.0.0

Methods

rnf :: Void -> () #

NFData Version

Since: 1.3.0.0

Methods

rnf :: Version -> () #

NFData Unique

Since: 1.4.0.0

Methods

rnf :: Unique -> () #

NFData ThreadId

Since: 1.4.0.0

Methods

rnf :: ThreadId -> () #

NFData ExitCode

Since: 1.4.2.0

Methods

rnf :: ExitCode -> () #

NFData CChar

Since: 1.4.0.0

Methods

rnf :: CChar -> () #

NFData CSChar

Since: 1.4.0.0

Methods

rnf :: CSChar -> () #

NFData CUChar

Since: 1.4.0.0

Methods

rnf :: CUChar -> () #

NFData CShort

Since: 1.4.0.0

Methods

rnf :: CShort -> () #

NFData CUShort

Since: 1.4.0.0

Methods

rnf :: CUShort -> () #

NFData CInt

Since: 1.4.0.0

Methods

rnf :: CInt -> () #

NFData CUInt

Since: 1.4.0.0

Methods

rnf :: CUInt -> () #

NFData CLong

Since: 1.4.0.0

Methods

rnf :: CLong -> () #

NFData CULong

Since: 1.4.0.0

Methods

rnf :: CULong -> () #

NFData CLLong

Since: 1.4.0.0

Methods

rnf :: CLLong -> () #

NFData CULLong

Since: 1.4.0.0

Methods

rnf :: CULLong -> () #

NFData CFloat

Since: 1.4.0.0

Methods

rnf :: CFloat -> () #

NFData CDouble

Since: 1.4.0.0

Methods

rnf :: CDouble -> () #

NFData CPtrdiff

Since: 1.4.0.0

Methods

rnf :: CPtrdiff -> () #

NFData CSize

Since: 1.4.0.0

Methods

rnf :: CSize -> () #

NFData CWchar

Since: 1.4.0.0

Methods

rnf :: CWchar -> () #

NFData CSigAtomic

Since: 1.4.0.0

Methods

rnf :: CSigAtomic -> () #

NFData CClock

Since: 1.4.0.0

Methods

rnf :: CClock -> () #

NFData CTime

Since: 1.4.0.0

Methods

rnf :: CTime -> () #

NFData CUSeconds

Since: 1.4.0.0

Methods

rnf :: CUSeconds -> () #

NFData CSUSeconds

Since: 1.4.0.0

Methods

rnf :: CSUSeconds -> () #

NFData CFile

Since: 1.4.0.0

Methods

rnf :: CFile -> () #

NFData CFpos

Since: 1.4.0.0

Methods

rnf :: CFpos -> () #

NFData CJmpBuf

Since: 1.4.0.0

Methods

rnf :: CJmpBuf -> () #

NFData CIntPtr

Since: 1.4.0.0

Methods

rnf :: CIntPtr -> () #

NFData CUIntPtr

Since: 1.4.0.0

Methods

rnf :: CUIntPtr -> () #

NFData CIntMax

Since: 1.4.0.0

Methods

rnf :: CIntMax -> () #

NFData CUIntMax

Since: 1.4.0.0

Methods

rnf :: CUIntMax -> () #

NFData All

Since: 1.4.0.0

Methods

rnf :: All -> () #

NFData Any

Since: 1.4.0.0

Methods

rnf :: Any -> () #

NFData Fingerprint

Since: 1.4.0.0

Methods

rnf :: Fingerprint -> () #

NFData SrcLoc

Since: 1.4.2.0

Methods

rnf :: SrcLoc -> () #

NFData ShortByteString 

Methods

rnf :: ShortByteString -> () #

NFData ByteString 

Methods

rnf :: ByteString -> () #

NFData ByteString 

Methods

rnf :: ByteString -> () #

NFData IntSet 

Methods

rnf :: IntSet -> () #

NFData Filler 

Methods

rnf :: Filler -> () #

NFData QualName 

Methods

rnf :: QualName -> () #

NFData Name 

Methods

rnf :: Name -> () #

NFData Doc 

Methods

rnf :: Doc -> () #

NFData TextDetails 

Methods

rnf :: TextDetails -> () #

NFData LocalTime 

Methods

rnf :: LocalTime -> () #

NFData ZonedTime 

Methods

rnf :: ZonedTime -> () #

NFData UTCTime 

Methods

rnf :: UTCTime -> () #

NFData NominalDiffTime 

Methods

rnf :: NominalDiffTime -> () #

NFData Day 

Methods

rnf :: Day -> () #

NFData UniversalTime 

Methods

rnf :: UniversalTime -> () #

NFData DiffTime 

Methods

rnf :: DiffTime -> () #

NFData NoEncoding # 

Methods

rnf :: NoEncoding -> () #

NFData FlatEncoding # 

Methods

rnf :: FlatEncoding -> () #

NFData UTF16LEEncoding # 

Methods

rnf :: UTF16LEEncoding -> () #

NFData UTF8Encoding # 

Methods

rnf :: UTF8Encoding -> () #

NFData Value # 

Methods

rnf :: Value -> () #

NFData UnicodeSymbol # 

Methods

rnf :: UnicodeSymbol -> () #

NFData UnicodeLetter # 

Methods

rnf :: UnicodeLetter -> () #

NFData UnicodeLetterOrNumberOrLine # 
NFData Identifier # 

Methods

rnf :: Identifier -> () #

NFData AbsRef # 

Methods

rnf :: AbsRef -> () #

NFData TypedBLOB # 

Methods

rnf :: TypedBLOB -> () #

NFData a => NFData [a] 

Methods

rnf :: [a] -> () #

NFData a => NFData (Maybe a) 

Methods

rnf :: Maybe a -> () #

NFData a => NFData (Ratio a) 

Methods

rnf :: Ratio a -> () #

NFData (Ptr a)

Since: 1.4.2.0

Methods

rnf :: Ptr a -> () #

NFData (FunPtr a)

Since: 1.4.2.0

Methods

rnf :: FunPtr a -> () #

NFData a => NFData (Identity a)

Since: 1.4.0.0

Methods

rnf :: Identity a -> () #

NFData a => NFData (Min a)

Since: 1.4.2.0

Methods

rnf :: Min a -> () #

NFData a => NFData (Max a)

Since: 1.4.2.0

Methods

rnf :: Max a -> () #

NFData a => NFData (First a)

Since: 1.4.2.0

Methods

rnf :: First a -> () #

NFData a => NFData (Last a)

Since: 1.4.2.0

Methods

rnf :: Last a -> () #

NFData m => NFData (WrappedMonoid m)

Since: 1.4.2.0

Methods

rnf :: WrappedMonoid m -> () #

NFData a => NFData (Option a)

Since: 1.4.2.0

Methods

rnf :: Option a -> () #

NFData a => NFData (NonEmpty a)

Since: 1.4.2.0

Methods

rnf :: NonEmpty a -> () #

NFData (Fixed a)

Since: 1.3.0.0

Methods

rnf :: Fixed a -> () #

NFData a => NFData (Complex a) 

Methods

rnf :: Complex a -> () #

NFData (StableName a)

Since: 1.4.0.0

Methods

rnf :: StableName a -> () #

NFData a => NFData (ZipList a)

Since: 1.4.0.0

Methods

rnf :: ZipList a -> () #

NFData a => NFData (Dual a)

Since: 1.4.0.0

Methods

rnf :: Dual a -> () #

NFData a => NFData (Sum a)

Since: 1.4.0.0

Methods

rnf :: Sum a -> () #

NFData a => NFData (Product a)

Since: 1.4.0.0

Methods

rnf :: Product a -> () #

NFData a => NFData (First a)

Since: 1.4.0.0

Methods

rnf :: First a -> () #

NFData a => NFData (Last a)

Since: 1.4.0.0

Methods

rnf :: Last a -> () #

NFData (IORef a)

NOTE: Only strict in the reference and not the referenced value.

Since: 1.4.2.0

Methods

rnf :: IORef a -> () #

NFData a => NFData (Down a)

Since: 1.4.0.0

Methods

rnf :: Down a -> () #

NFData (MVar a)

NOTE: Only strict in the reference and not the referenced value.

Since: 1.4.2.0

Methods

rnf :: MVar a -> () #

NFData a => NFData (Digit a) 

Methods

rnf :: Digit a -> () #

NFData a => NFData (Node a) 

Methods

rnf :: Node a -> () #

NFData a => NFData (Elem a) 

Methods

rnf :: Elem a -> () #

NFData a => NFData (FingerTree a) 

Methods

rnf :: FingerTree a -> () #

NFData a => NFData (IntMap a) 

Methods

rnf :: IntMap a -> () #

NFData a => NFData (Tree a) 

Methods

rnf :: Tree a -> () #

NFData a => NFData (Seq a) 

Methods

rnf :: Seq a -> () #

NFData a => NFData (Set a) 

Methods

rnf :: Set a -> () #

NFData (Context a) 

Methods

rnf :: Context a -> () #

NFData (Digest a) 

Methods

rnf :: Digest a -> () #

NFData a => NFData (DList a) 

Methods

rnf :: DList a -> () #

NFData a => NFData (PostAligned a) 

Methods

rnf :: PostAligned a -> () #

NFData a => NFData (PreAligned a) 

Methods

rnf :: PreAligned a -> () #

NFData (Get a) 

Methods

rnf :: Get a -> () #

NFData a => NFData (Hashed a) 

Methods

rnf :: Hashed a -> () #

NFData ref => NFData (Type ref) 

Methods

rnf :: Type ref -> () #

NFData r => NFData (TypeN r) 

Methods

rnf :: TypeN r -> () #

NFData name => NFData (TypeRef name) 

Methods

rnf :: TypeRef name -> () #

NFData a => NFData (Doc a) 

Methods

rnf :: Doc a -> () #

NFData a => NFData (AnnotDetails a) 

Methods

rnf :: AnnotDetails a -> () #

NFData a => NFData (HashSet a) 

Methods

rnf :: HashSet a -> () #

NFData a => NFData (Vector a) 

Methods

rnf :: Vector a -> () #

NFData (Vector a) 

Methods

rnf :: Vector a -> () #

NFData (Vector a) 

Methods

rnf :: Vector a -> () #

NFData (Vector a) 

Methods

rnf :: Vector a -> () #

NFData a => NFData (NonEmptyList a) # 

Methods

rnf :: NonEmptyList a -> () #

NFData a => NFData (List a) # 

Methods

rnf :: List a -> () #

NFData r => NFData (ADTRef r) # 

Methods

rnf :: ADTRef r -> () #

NFData (SHAKE128_48 a) # 

Methods

rnf :: SHAKE128_48 a -> () #

NFData (SHA3_256_6 a) # 

Methods

rnf :: SHA3_256_6 a -> () #

NFData a => NFData (TypedValue a) # 

Methods

rnf :: TypedValue a -> () #

NFData encoding => NFData (BLOB encoding) # 

Methods

rnf :: BLOB encoding -> () #

NFData (a -> b)

This instance is for convenience and consistency with seq. This assumes that WHNF is equivalent to NF for functions.

Since: 1.3.0.0

Methods

rnf :: (a -> b) -> () #

(NFData a, NFData b) => NFData (Either a b) 

Methods

rnf :: Either a b -> () #

(NFData a, NFData b) => NFData (a, b) 

Methods

rnf :: (a, b) -> () #

(NFData a, NFData b) => NFData (Array a b) 

Methods

rnf :: Array a b -> () #

(NFData a, NFData b) => NFData (Arg a b)

Since: 1.4.2.0

Methods

rnf :: Arg a b -> () #

NFData (Proxy k a)

Since: 1.4.0.0

Methods

rnf :: Proxy k a -> () #

NFData (STRef s a)

NOTE: Only strict in the reference and not the referenced value.

Since: 1.4.2.0

Methods

rnf :: STRef s a -> () #

(NFData k, NFData a) => NFData (Map k a) 

Methods

rnf :: Map k a -> () #

(NFData ref, NFData name) => NFData (ConTree name ref) 

Methods

rnf :: ConTree name ref -> () #

(NFData k, NFData v) => NFData (HashMap k v) 

Methods

rnf :: HashMap k v -> () #

(NFData k, NFData v) => NFData (Leaf k v) 

Methods

rnf :: Leaf k v -> () #

NFData (MVector s a) 

Methods

rnf :: MVector s a -> () #

NFData (MVector s a) 

Methods

rnf :: MVector s a -> () #

NFData (MVector s a) 

Methods

rnf :: MVector s a -> () #

(NFData label, NFData a) => NFData (Label a label) # 

Methods

rnf :: Label a label -> () #

(NFData a, NFData b, NFData c) => NFData (a, b, c) 

Methods

rnf :: (a, b, c) -> () #

NFData a => NFData (Const k a b)

Since: 1.4.0.0

Methods

rnf :: Const k a b -> () #

(NFData consName, NFData ref, NFData name) => NFData (ADT name consName ref) 

Methods

rnf :: ADT name consName ref -> () #

NFData b => NFData (Tagged k s b) 

Methods

rnf :: Tagged k s b -> () #

(NFData a, NFData b, NFData c, NFData d) => NFData (a, b, c, d) 

Methods

rnf :: (a, b, c, d) -> () #

(NFData adtName, NFData inRef, NFData consName, NFData exRef) => NFData (TypeModel adtName consName inRef exRef) 

Methods

rnf :: TypeModel adtName consName inRef exRef -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => NFData (a1, a2, a3, a4, a5) 

Methods

rnf :: (a1, a2, a3, a4, a5) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => NFData (a1, a2, a3, a4, a5, a6) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => NFData (a1, a2, a3, a4, a5, a6, a7) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6, a7) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8) => NFData (a1, a2, a3, a4, a5, a6, a7, a8) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6, a7, a8) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8, NFData a9) => NFData (a1, a2, a3, a4, a5, a6, a7, a8, a9) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6, a7, a8, a9) -> () #

class Flat a #

Class of types that can be encoded/decoded

Instances

Flat Filler

Use a special encoding for the filler

Flat Sign # 
Flat Bit # 
Flat Bits11 # 
Flat Bits23 # 
Flat Bits52 # 
Flat Bits8 # 
Flat NoEncoding # 
Flat FlatEncoding # 
Flat UTF16LEEncoding # 
Flat UTF8Encoding # 
Flat Value # 
Flat UnicodeSymbol # 
Flat UnicodeLetter # 
Flat UnicodeLetterOrNumberOrLine # 
Flat Identifier # 
Flat AbsRef # 
Flat TypedBLOB # 
Flat [UnicodeLetterOrNumberOrLine] # 
Flat a => Flat (PostAligned a) 
Flat a => Flat (PreAligned a) 
Flat a => Flat (NonEmptyList a) # 
Flat a => Flat (List a) # 

Methods

encode :: List a -> Encoding #

decode :: Get (List a) #

size :: List a -> NumBits -> NumBits #

Flat a => Flat (MostSignificantFirst a) # 
Flat a => Flat (LeastSignificantFirst a) # 
Flat a => Flat (ZigZag a) # 

Methods

encode :: ZigZag a -> Encoding #

decode :: Get (ZigZag a) #

size :: ZigZag a -> NumBits -> NumBits #

Flat r => Flat (ADTRef r) # 

Methods

encode :: ADTRef r -> Encoding #

decode :: Get (ADTRef r) #

size :: ADTRef r -> NumBits -> NumBits #

Flat (SHAKE128_48 a) # 
Flat (SHA3_256_6 a) # 
Flat a => Flat (TypedValue a) # 
Flat encoding => Flat (BLOB encoding) # 

Methods

encode :: BLOB encoding -> Encoding #

decode :: Get (BLOB encoding) #

size :: BLOB encoding -> NumBits -> NumBits #

(Flat label, Flat a) => Flat (Label a label) # 

Methods

encode :: Label a label -> Encoding #

decode :: Get (Label a label) #

size :: Label a label -> NumBits -> NumBits #

data ZigZag a Source #

ZigZag encoding, map signed integers to unsigned integers Positive integers are mapped to even unsigned values, negative integers to odd values: 0 -> 0, -1 -> 1, 1 -> 2, -2 -> 3, 2 -> 4 ...

Constructors

ZigZag a 

Instances

Eq a => Eq (ZigZag a) Source # 

Methods

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

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

Ord a => Ord (ZigZag a) Source # 

Methods

compare :: ZigZag a -> ZigZag a -> Ordering #

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

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

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

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

max :: ZigZag a -> ZigZag a -> ZigZag a #

min :: ZigZag a -> ZigZag a -> ZigZag a #

Show a => Show (ZigZag a) Source # 

Methods

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

show :: ZigZag a -> String #

showList :: [ZigZag a] -> ShowS #

Generic (ZigZag a) Source # 

Associated Types

type Rep (ZigZag a) :: * -> * #

Methods

from :: ZigZag a -> Rep (ZigZag a) x #

to :: Rep (ZigZag a) x -> ZigZag a #

Flat a => Flat (ZigZag a) Source # 

Methods

encode :: ZigZag a -> Encoding #

decode :: Get (ZigZag a) #

size :: ZigZag a -> NumBits -> NumBits #

Model a => Model (ZigZag a) Source # 

Methods

envType :: Proxy * (ZigZag a) -> State Env HType #

type Rep (ZigZag a) Source # 
type Rep (ZigZag a) = D1 (MetaData "ZigZag" "ZM.Type.Words" "zm-0.3.2-9EffK4RA8nV74pYjwjqtDn" False) (C1 (MetaCons "ZigZag" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

data LeastSignificantFirst a Source #

Constructors

LeastSignificantFirst a 

Instances

Eq a => Eq (LeastSignificantFirst a) Source # 
Ord a => Ord (LeastSignificantFirst a) Source # 
Show a => Show (LeastSignificantFirst a) Source # 
Generic (LeastSignificantFirst a) Source # 
Flat a => Flat (LeastSignificantFirst a) Source # 
Model a => Model (LeastSignificantFirst a) Source # 
type Rep (LeastSignificantFirst a) Source # 
type Rep (LeastSignificantFirst a) = D1 (MetaData "LeastSignificantFirst" "ZM.Type.Words" "zm-0.3.2-9EffK4RA8nV74pYjwjqtDn" False) (C1 (MetaCons "LeastSignificantFirst" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

data MostSignificantFirst a Source #

Constructors

MostSignificantFirst a 

Instances

Eq a => Eq (MostSignificantFirst a) Source # 
Ord a => Ord (MostSignificantFirst a) Source # 
Show a => Show (MostSignificantFirst a) Source # 
Generic (MostSignificantFirst a) Source # 
Flat a => Flat (MostSignificantFirst a) Source # 
Model a => Model (MostSignificantFirst a) Source # 
type Rep (MostSignificantFirst a) Source # 
type Rep (MostSignificantFirst a) = D1 (MetaData "MostSignificantFirst" "ZM.Type.Words" "zm-0.3.2-9EffK4RA8nV74pYjwjqtDn" False) (C1 (MetaCons "MostSignificantFirst" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

data Value Source #

A generic value (used for dynamic decoding)

Constructors

Value 

Fields

data Label a label Source #

An optionally labeled value

Constructors

Label a (Maybe label) 

Instances

(Eq label, Eq a) => Eq (Label a label) Source # 

Methods

(==) :: Label a label -> Label a label -> Bool #

(/=) :: Label a label -> Label a label -> Bool #

(Ord label, Ord a) => Ord (Label a label) Source # 

Methods

compare :: Label a label -> Label a label -> Ordering #

(<) :: Label a label -> Label a label -> Bool #

(<=) :: Label a label -> Label a label -> Bool #

(>) :: Label a label -> Label a label -> Bool #

(>=) :: Label a label -> Label a label -> Bool #

max :: Label a label -> Label a label -> Label a label #

min :: Label a label -> Label a label -> Label a label #

(Show label, Show a) => Show (Label a label) Source # 

Methods

showsPrec :: Int -> Label a label -> ShowS #

show :: Label a label -> String #

showList :: [Label a label] -> ShowS #

Generic (Label a label) Source # 

Associated Types

type Rep (Label a label) :: * -> * #

Methods

from :: Label a label -> Rep (Label a label) x #

to :: Rep (Label a label) x -> Label a label #

(NFData label, NFData a) => NFData (Label a label) Source # 

Methods

rnf :: Label a label -> () #

(Flat label, Flat a) => Flat (Label a label) Source # 

Methods

encode :: Label a label -> Encoding #

decode :: Get (Label a label) #

size :: Label a label -> NumBits -> NumBits #

type Rep (Label a label) Source # 
type Rep (Label a label) = D1 (MetaData "Label" "ZM.Types" "zm-0.3.2-9EffK4RA8nV74pYjwjqtDn" False) (C1 (MetaCons "Label" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe label)))))

label :: (Functor f, Ord k) => Map k a -> (a -> l) -> f k -> f (Label k l) Source #

Orphan instances

(Flat a, Flat b) => Flat [(a, Type b)] Source # 

Methods

encode :: [(a, Type b)] -> Encoding #

decode :: Get [(a, Type b)] #

size :: [(a, Type b)] -> NumBits -> NumBits #

Flat a => Flat [Type a] Source # 

Methods

encode :: [Type a] -> Encoding #

decode :: Get [Type a] #

size :: [Type a] -> NumBits -> NumBits #

Flat a => Flat (Type a) Source # 

Methods

encode :: Type a -> Encoding #

decode :: Get (Type a) #

size :: Type a -> NumBits -> NumBits #

Flat a => Flat (TypeRef a) Source # 
Model a => Model (PostAligned a) Source # 
Model a => Model (Type a) Source # 

Methods

envType :: Proxy * (Type a) -> State Env HType #

Model a => Model (TypeRef a) Source # 

Methods

envType :: Proxy * (TypeRef a) -> State Env HType #

(Flat a, Flat b) => Flat (ConTree a b) Source # 

Methods

encode :: ConTree a b -> Encoding #

decode :: Get (ConTree a b) #

size :: ConTree a b -> NumBits -> NumBits #

(Model a, Model b) => Model (ConTree a b) Source # 

Methods

envType :: Proxy * (ConTree a b) -> State Env HType #

(Flat a, Flat b, Flat c) => Flat (ADT a b c) Source # 

Methods

encode :: ADT a b c -> Encoding #

decode :: Get (ADT a b c) #

size :: ADT a b c -> NumBits -> NumBits #

(Model a, Model b, Model c) => Model (ADT a b c) Source # 

Methods

envType :: Proxy * (ADT a b c) -> State Env HType #

(Flat adtName, Flat consName, Flat inRef, Flat exRef, Ord exRef) => Flat (TypeModel adtName consName inRef exRef) Source # 

Methods

encode :: TypeModel adtName consName inRef exRef -> Encoding #

decode :: Get (TypeModel adtName consName inRef exRef) #

size :: TypeModel adtName consName inRef exRef -> NumBits -> NumBits #

(Model adtName, Model consName, Model inRef, Model exRef) => Model (TypeModel adtName consName inRef exRef) Source # 

Methods

envType :: Proxy * (TypeModel adtName consName inRef exRef) -> State Env HType #