binrep-0.2.0: Encode precise binary representations directly in types
Safe HaskellSafe-Inferred
LanguageHaskell2010

Binrep.Type.Magic

Description

Magic numbers (also just magic): short constant bytestrings usually found at the top of a file, included as a safety check for parsing.

TODO rename: MagicBytes -> MagicVals, and have ByteVal be a "consumer" of MagicVals where each value must be a byte. (It's conceivable that we have another consumer which makes each value into a non-empty list of bytes, LE/BE.)

TODO unassociated type fams bad (maybe). turn into class -- and turn the reifier into a default method! (TODO think about this)

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.

Documentation

data Magic (a :: k) Source #

Constructors

Magic 

Instances

Instances details
(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 (MagicVals a)) => BLen (Magic a) Source #

Assumes magic values are individual bytes.

Instance details

Defined in Binrep.Type.Magic

Methods

blen :: Magic a -> BLenT Source #

(bs ~ MagicVals a, ByteVals bs) => Get (Magic a) Source #

Forces magic values to be individual bytes.

TODO improve show - maybe hexbytestring goes here? lol

Instance details

Defined in Binrep.Type.Magic

Methods

get :: Getter (Magic a) Source #

(bs ~ MagicVals a, ByteVals bs) => Put (Magic a) Source #

Forces magic values to be individual bytes.

Instance details

Defined in Binrep.Type.Magic

Methods

put :: Magic a -> Builder Source #

Eq (Magic a) Source # 
Instance details

Defined in Binrep.Type.Magic

Methods

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

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

type Rep (Magic a) Source # 
Instance details

Defined in Binrep.Type.Magic

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

Assumes magic values are individual bytes.

Instance details

Defined in Binrep.Type.Magic

type CBLen (Magic a) = Length (MagicVals a)

type family MagicVals (a :: k) :: [Natural] Source #

Instances

Instances details
type MagicVals (a :: Symbol) Source # 
Instance details

Defined in Binrep.Type.Magic

type MagicVals (a :: [Natural]) Source # 
Instance details

Defined in Binrep.Type.Magic

type MagicVals (a :: [Natural]) = a

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 #