Safe Haskell | None |
---|---|
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 e.g.
For printable (UTF-8) magics, use Magic
@'[0xFF, 0x01]Symbol
s e.g.
.Magic
@"hello"
Documentation
data Magic (a :: k) where Source #
A unit data type representing a "magic number" via a phantom type.
The phantom type unambiguously defines a bytestring at compile time. This
depends on the type's kind. See MagicBytes
for details.
This is defined using GADT syntax to permit labelling the phantom type kind as inferred, which effectively means hidden (not available for visible type applications). That kind is always evident from the type, so it's just nicer.
Instances
IsCBLen (Magic a :: Type) Source # | The byte length of a magic is known at compile time. | ||||
Defined in Binrep.Type.Magic Associated Types
| |||||
(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 # | |||||
Defined in Binrep.Type.Magic | |||||
Show (Magic a) Source # | |||||
KnownNat (Length (MagicBytes a)) => BLen (Magic a) Source # | |||||
(bs ~ MagicBytes a, ParseReifyBytesW64 0 bs, ReifyBytesW64 bs, KnownNat (Length bs)) => Get (Magic a) Source # | |||||
(bs ~ MagicBytes a, ParseReifyBytesW64 0 bs) => GetC (Magic a) Source # | Efficiently parse a | ||||
(bs ~ MagicBytes a, ReifyBytesW64 bs, KnownNat (Length bs)) => Put (Magic a) Source # | |||||
(bs ~ MagicBytes a, ReifyBytesW64 bs) => PutC (Magic a) Source # | Efficiently serialize a | ||||
Eq (Magic a) Source # | |||||
type CBLen (Magic a :: Type) Source # | |||||
Defined in Binrep.Type.Magic | |||||
type Rep (Magic a) Source # | |||||
class Magical (a :: k) Source #
Types which define a magic value.
Associated Types
type MagicBytes (a :: k) :: [Natural] Source #
How to turn the type into a list of bytes (stored using Natural
s).
Instances
Magical (sym :: Symbol) Source # | Type-level symbols are converted to UTF-8. | ||||
Defined in Binrep.Type.Magic Associated Types
| |||||
Magical (bs :: [Natural]) Source # | Type-level naturals go as-is. (Make sure you don't go over 255, though!) | ||||
Defined in Binrep.Type.Magic Associated Types
|