Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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 Symbol
s (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
Constructors
Magic |
Instances
(Typeable a, Typeable k) => Data (Magic a) Source # | |
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 # | |
Show (Magic a) Source # | |
KnownNat (Length (MagicVals a)) => BLen (Magic a) Source # | Assumes magic values are individual bytes. |
(bs ~ MagicVals a, ByteVals bs) => Get (Magic a) Source # | Forces magic values to be individual bytes. TODO improve show - maybe hexbytestring goes here? lol |
(bs ~ MagicVals a, ByteVals bs) => Put (Magic a) Source # | Forces magic values to be individual bytes. |
Eq (Magic a) Source # | |
type Rep (Magic a) Source # | |
type CBLen (Magic a) Source # | Assumes magic values are individual bytes. |
Defined in Binrep.Type.Magic |
type family MagicVals (a :: k) :: [Natural] Source #
Instances
type MagicVals (a :: Symbol) Source # | |
Defined in Binrep.Type.Magic | |
type MagicVals (a :: [Natural]) Source # | |
Defined in Binrep.Type.Magic |
type family SymbolUnicodeCodepoints (a :: Symbol) :: [Natural] where ... Source #
Equations
SymbolUnicodeCodepoints a = CharListUnicodeCodepoints (SymbolAsCharList a) |
type family CharListUnicodeCodepoints (a :: [Char]) :: [Natural] where ... Source #
Equations
CharListUnicodeCodepoints '[] = '[] | |
CharListUnicodeCodepoints (c ': cs) = CharToNat c ': CharListUnicodeCodepoints cs |
type family SymbolAsCharList (a :: Symbol) :: [Char] where ... Source #
Equations
SymbolAsCharList a = SymbolAsCharList' (UnconsSymbol a) |
type family SymbolAsCharList' (a :: Maybe (Char, Symbol)) :: [Char] where ... Source #
Equations
SymbolAsCharList' 'Nothing = '[] | |
SymbolAsCharList' ('Just '(c, s)) = c ': SymbolAsCharList' (UnconsSymbol s) |