binrep-0.7.0: Encode precise binary representations directly in types
Safe HaskellSafe-Inferred
LanguageGHC2021

Binrep.Type.Magic

Description

Magic numbers (also just magic): short constant bytestrings usually found at the top of a file, often used as an early sanity check.

There are two main flavors of magics:

  • "random" bytes e.g. Zstandard: 28 B5 2F FD
  • printable ASCII bytes e.g. Ogg: 4F 67 67 53 -> OggS

For bytewise magics, use type-level Natural lists. For ASCII magics, use Symbols (type-level strings).

Previously, I squashed these into a representationally-safe type. Now the check only occurs during reification. So you are able to define invalid magics now (bytes over 255, non-ASCII characters), and potentially use them, but you'll get a clear type error like "no instance for ByteVal 256" when attempting to reify.

String magics are restricted to ASCII, and will type error during reification otherwise. If you really want UTF-8, please read UTF8.

Synopsis

Documentation

data Magic (a :: k) Source #

A singleton data type representing a "magic number" via a phantom type.

The phantom type variable unambiguously defines a constant bytestring. A handful of types are supported for using magics conveniently, e.g. for pure ASCII magics, you may use a Symbol type-level string.

Constructors

Magic 

Instances

Instances details
IsCBLen (Magic a :: Type) Source #

The byte length of a magic is known at compile time.

Instance details

Defined in Binrep.Type.Magic

Associated Types

type CBLen (Magic a) :: Natural Source #

(Typeable a, Typeable k) => Data (Magic a) Source # 
Instance details

Defined in Binrep.Type.Magic

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Magic a -> c (Magic a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Magic a) #

toConstr :: Magic a -> Constr #

dataTypeOf :: Magic a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Magic a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Magic a)) #

gmapT :: (forall b. Data b => b -> b) -> Magic a -> Magic a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Magic a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Magic a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Magic a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Magic a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Magic a -> m (Magic a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Magic a -> m (Magic a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Magic a -> m (Magic a) #

Generic (Magic a) Source # 
Instance details

Defined in Binrep.Type.Magic

Associated Types

type Rep (Magic a) :: Type -> Type #

Methods

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

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

Show (Magic a) Source # 
Instance details

Defined in Binrep.Type.Magic

Methods

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

show :: Magic a -> String #

showList :: [Magic a] -> ShowS #

KnownNat (Length (MagicBytes a)) => BLen (Magic a) Source #

The byte length of a magic is obtained via reifying.

Instance details

Defined in Binrep.Type.Magic

Methods

blen :: Magic a -> Int Source #

(bs ~ MagicBytes a, ParseReifyBytesW64 bs, ReifyBytesW64 bs, KnownNat (Length bs)) => Get (Magic a) Source # 
Instance details

Defined in Binrep.Type.Magic

Methods

get :: Getter (Magic a) Source #

(bs ~ MagicBytes a, ParseReifyBytesW64 bs, ReifyBytesW64 bs, KnownNat (Length bs)) => GetC (Magic a) Source # 
Instance details

Defined in Binrep.Type.Magic

Methods

getC :: GetterC (Magic a) Source #

(bs ~ MagicBytes a, ReifyBytesW64 bs, KnownNat (Length bs)) => Put (Magic a) Source # 
Instance details

Defined in Binrep.Type.Magic

Methods

put :: Magic a -> Putter Source #

(bs ~ MagicBytes a, ReifyBytesW64 bs) => PutC (Magic a) Source # 
Instance details

Defined in Binrep.Type.Magic

Methods

putC :: Magic a -> PutterC Source #

Eq (Magic a) Source # 
Instance details

Defined in Binrep.Type.Magic

Methods

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

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

Strengthen (Magic a) Source #

Strengthen the unit to some Magic a.

Instance details

Defined in Binrep.Type.Magic

Methods

strengthen :: Weak (Magic a) -> Result (Magic a) #

Weaken (Magic a) Source #

Weaken a Magic a to the unit.

Instance details

Defined in Binrep.Type.Magic

Associated Types

type Weak (Magic a) #

Methods

weaken :: Magic a -> Weak (Magic a) #

type CBLen (Magic a :: Type) Source # 
Instance details

Defined in Binrep.Type.Magic

type CBLen (Magic a :: Type) = Length (MagicBytes a)
type Rep (Magic a) Source # 
Instance details

Defined in Binrep.Type.Magic

type Rep (Magic a) = D1 ('MetaData "Magic" "Binrep.Type.Magic" "binrep-0.7.0-inplace" 'False) (C1 ('MetaCons "Magic" 'PrefixI 'False) (U1 :: Type -> Type))
type Weak (Magic a) Source # 
Instance details

Defined in Binrep.Type.Magic

type Weak (Magic a) = ()

type family Length (a :: [k]) :: Natural where ... Source #

The length of a type-level list.

Equations

Length '[] = 0 
Length (a ': as) = 1 + Length as 

type family CharListUnicodeCodepoints (a :: [Char]) :: [Natural] where ... Source #

type family SymbolAsCharList (a :: Symbol) :: [Char] where ... Source #

type family SymbolAsCharList' (a :: Maybe (Char, Symbol)) :: [Char] where ... Source #

class Magical (a :: k) Source #

Types which define a magic value.

Associated Types

type MagicBytes a :: [Natural] Source #

How to turn the type into a list of bytes.

Instances

Instances details
Magical (sym :: Symbol) Source #

Type-level symbols are turned into their Unicode codepoints - but multibyte characters aren't handled, so they'll simply be overlarge bytes, which will fail further down.

Instance details

Defined in Binrep.Type.Magic

Associated Types

type MagicBytes sym :: [Natural] Source #

Magical (ns :: [Natural]) Source #

Type-level naturals go as-is. (Make sure you don't go over 255, though!)

Instance details

Defined in Binrep.Type.Magic

Associated Types

type MagicBytes ns :: [Natural] Source #