| Safe Haskell | Safe-Inferred |
|---|---|
| Language | GHC2021 |
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:
- byte magics e.g. Zstandard:
28 B5 2F FD - printable magics e.g. Ogg:
4F 67 67 53->OggS(in ASCII)
For byte magics, use type-level Natural lists.
For printable magics, use Symbols (type-level strings).
Documentation
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
| IsCBLen (Magic a :: Type) Source # | The byte length of a magic is known at compile time. |
| (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 (MagicBytes a)) => BLen (Magic a) Source # | The byte length of a magic is obtained via reifying. |
| (bs ~ MagicBytes a, ParseReifyBytesW64 bs, ReifyBytesW64 bs, KnownNat (Length bs)) => Get (Magic a) Source # | |
| (bs ~ MagicBytes a, ParseReifyBytesW64 bs, ReifyBytesW64 bs, KnownNat (Length bs)) => GetC (Magic a) Source # | |
| (bs ~ MagicBytes a, ReifyBytesW64 bs, KnownNat (Length bs)) => Put (Magic a) Source # | |
| (bs ~ MagicBytes a, ReifyBytesW64 bs) => PutC (Magic a) Source # | |
| Eq (Magic a) Source # | |
| Strengthen (Magic a) Source # | Strengthen the unit to some |
Defined in Binrep.Type.Magic | |
| Weaken (Magic a) Source # | Weaken a |
| type CBLen (Magic a :: Type) Source # | |
Defined in Binrep.Type.Magic | |
| type Rep (Magic a) Source # | |
| type Weak (Magic a) Source # | |
Defined in Binrep.Type.Magic | |
class Magical (a :: k) Source #
Types which define a magic value.
Instances
| Magical (sym :: Symbol) Source # | Type-level symbols are converted to UTF-8. |
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!) |
Defined in Binrep.Type.Magic Associated Types type MagicBytes ns :: [Natural] Source # | |