Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Magic numbers (also just magic): short constant bytestrings usually found at the top of a file, often used as an early sanity check.
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
.
Synopsis
- data Magic (a :: k) = Magic
- type family SymbolUnicodeCodepoints (a :: Symbol) :: [Natural] where ...
- type family CharListUnicodeCodepoints (a :: [Char]) :: [Natural] where ...
- type family SymbolAsCharList (a :: Symbol) :: [Char] where ...
- type family SymbolAsCharList' (a :: Maybe (Char, Symbol)) :: [Char] where ...
- class Magical (a :: k) where
- type MagicBytes a :: [Natural]
Documentation
An empty data type representing a magic number (a constant bytestring) via a phantom type.
The phantom type variable unambiguously defines a short, 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.
Instances
(Typeable a, Typeable k) => Data (Magic a) Source # | |
Defined in Binrep.Type.Magic 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 (MagicBytes a)) => BLen (Magic a) Source # | |
(bs ~ MagicBytes a, ReifyBytes bs) => Get (Magic a) Source # | |
(bs ~ MagicBytes a, ReifyBytes bs) => Put (Magic a) Source # | |
Eq (Magic a) Source # | |
Strengthen (Magic a) Source # | Strengthen the unit to some 'Magic a'. |
Defined in Binrep.Type.Magic strengthen :: Weak (Magic a) -> Validation (NonEmpty StrengthenFail) (Magic a) # | |
Weaken (Magic a) Source # | Weaken a 'Magic a' to the unit. Perhaps you prefer pattern matching on |
type Rep (Magic a) Source # | |
type CBLen (Magic a) Source # | |
Defined in Binrep.Type.Magic | |
type Weak (Magic a) Source # | |
Defined in Binrep.Type.Magic |
type family SymbolUnicodeCodepoints (a :: Symbol) :: [Natural] where ... Source #
type family CharListUnicodeCodepoints (a :: [Char]) :: [Natural] where ... Source #
CharListUnicodeCodepoints '[] = '[] | |
CharListUnicodeCodepoints (c ': cs) = CharToNat c ': CharListUnicodeCodepoints cs |
type family SymbolAsCharList (a :: Symbol) :: [Char] where ... Source #
type family SymbolAsCharList' (a :: Maybe (Char, Symbol)) :: [Char] where ... Source #
SymbolAsCharList' 'Nothing = '[] | |
SymbolAsCharList' ('Just '(c, s)) = c ': SymbolAsCharList' (UnconsSymbol s) |
class Magical (a :: k) Source #
Types which define a magic value.
type MagicBytes a :: [Natural] Source #
How to turn the type into a list of bytes.
Instances
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. |
Defined in Binrep.Type.Magic type MagicBytes sym :: [Natural] Source # | |
Magical (ns :: [Natural]) Source # | Type-level naturals go as-is. (Make sure you don't go over 255, though!) |
Defined in Binrep.Type.Magic type MagicBytes ns :: [Natural] Source # |