zm-0.3.2: Language independent, reproducible, absolute types

Safe HaskellNone
LanguageHaskell2010

ZM.BLOB

Synopsis

Documentation

data BLOB encoding Source #

A BLOB is binary value encoded according to a specified encoding (e.g. UTF8)

Constructors

BLOB 

Fields

Instances

Eq encoding => Eq (BLOB encoding) Source # 

Methods

(==) :: BLOB encoding -> BLOB encoding -> Bool #

(/=) :: BLOB encoding -> BLOB encoding -> Bool #

Ord encoding => Ord (BLOB encoding) Source # 

Methods

compare :: BLOB encoding -> BLOB encoding -> Ordering #

(<) :: BLOB encoding -> BLOB encoding -> Bool #

(<=) :: BLOB encoding -> BLOB encoding -> Bool #

(>) :: BLOB encoding -> BLOB encoding -> Bool #

(>=) :: BLOB encoding -> BLOB encoding -> Bool #

max :: BLOB encoding -> BLOB encoding -> BLOB encoding #

min :: BLOB encoding -> BLOB encoding -> BLOB encoding #

Show encoding => Show (BLOB encoding) Source # 

Methods

showsPrec :: Int -> BLOB encoding -> ShowS #

show :: BLOB encoding -> String #

showList :: [BLOB encoding] -> ShowS #

Generic (BLOB encoding) Source # 

Associated Types

type Rep (BLOB encoding) :: * -> * #

Methods

from :: BLOB encoding -> Rep (BLOB encoding) x #

to :: Rep (BLOB encoding) x -> BLOB encoding #

NFData encoding => NFData (BLOB encoding) Source # 

Methods

rnf :: BLOB encoding -> () #

Flat encoding => Flat (BLOB encoding) Source # 

Methods

encode :: BLOB encoding -> Encoding #

decode :: Get (BLOB encoding) #

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

Model encoding => Model (BLOB encoding) Source # 

Methods

envType :: Proxy * (BLOB encoding) -> State Env HType #

type Rep (BLOB encoding) Source # 
type Rep (BLOB encoding) = D1 (MetaData "BLOB" "ZM.BLOB" "zm-0.3.2-9EffK4RA8nV74pYjwjqtDn" False) (C1 (MetaCons "BLOB" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "encoding") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 encoding)) (S1 (MetaSel (Just Symbol "content") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))))

blob :: AsByteString a => encoding -> a -> BLOB encoding Source #

Build a BLOB from an encoding and a ByteString-like value

unblob :: BLOB t -> ByteString Source #

Extract the binary content of a BLOB

data TypedBLOB Source #

A typed value, a Flat encoded value and its absolute type

typedBLOB :: forall a. (Model a, Flat a) => a -> TypedBLOB Source #

Build a TypedBLOB out of a value

typedBLOB_ :: Flat a => AbsType -> a -> TypedBLOB Source #

Build a TypedBLOB out of a type and a value

untypedBLOB :: forall a. (Flat a, Model a) => Decoded TypedBLOB -> TypedDecoded a Source #

Type-checked extraction of a value of a known type from a decoded TypedBLOB

data TypedValue a Source #

A typed value, a value and its absolute type

Constructors

TypedValue AbsType a 

Instances

Functor TypedValue Source # 

Methods

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

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

Eq a => Eq (TypedValue a) Source # 

Methods

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

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

Ord a => Ord (TypedValue a) Source # 
Show a => Show (TypedValue a) Source # 
Generic (TypedValue a) Source # 

Associated Types

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

Methods

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

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

NFData a => NFData (TypedValue a) Source # 

Methods

rnf :: TypedValue a -> () #

Flat a => Flat (TypedValue a) Source # 
type Rep (TypedValue a) Source # 

typedValue :: forall a. Model a => a -> TypedValue a Source #

Build a TypedValue out of a value

untypedValue :: Model a => Decoded (TypedValue a) -> TypedDecoded a Source #

Type-checked extraction of a value of a known type from a decoded TypedValue

typeErr :: AbsType -> AbsType -> TypedDecoded a Source #

Return a WrongType error