Copyright | (C) Koz Ross 2019 |
---|---|
License | GPL version 3.0 or later |
Maintainer | koz.ross@retro-freedom.nz |
Stability | Experimental |
Portability | GHC only |
Safe Haskell | None |
Language | Haskell2010 |
This allows us to 'borrow' implementations of certain type classes from
'larger' finitary types for 'smaller' finitary types. Essentially, for
any types a
and b
, if both a
and b
are Finitary
and Cardinality a
<= Cardinality b
, the set of indexes for a
is a subset (strictly speaking,
a prefix) of the set of indexes for b
. Therefore, we have an injective
mapping from a
to b
, whose
preimage
is also injective, witnessed by the function fromFinite . toFinite
in both
directions. When combined with the monotonicity of toFinite
and
fromFinite
, we can operate on inhabitants of b
in certain ways while
always being able to recover the 'equivalent' inhabitant of a
.
On this basis, we can 'borrow' both Unbox
and Storable
instances
from b
. This is done by way of the PackInto a b
type; here, a
is the
type to which instances are being 'lent' and b
is the type from which
instances are being 'borrowed'. PackInto a b
does not store any values of
type a
- construction and deconstruction of PackInto
performs a
conversion as described above.
If an existing Finitary
type exists with desired instances, this encoding
is the most flexible and efficient. Unless you have good reasons to consider
something else (such as space use), use this encoding. However, its
usefulness is conditional on a suitable 'packing' type existing of
appropriate cardinality. Additionally, if Cardinality a < Cardinality b
,
any PackInto a b
will waste some space, with larger cardinality differences
creating proportionately more waste.
Documentation
data PackInto (a :: Type) (b :: Type) Source #
An opaque wrapper, representing values of type a
as 'corresponding'
values of type b
.
Instances
Unbox b => MVector MVector (PackInto a b) Source # | |
Defined in Data.Finitary.PackInto basicLength :: MVector s (PackInto a b) -> Int basicUnsafeSlice :: Int -> Int -> MVector s (PackInto a b) -> MVector s (PackInto a b) basicOverlaps :: MVector s (PackInto a b) -> MVector s (PackInto a b) -> Bool basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (PackInto a b)) basicInitialize :: PrimMonad m => MVector (PrimState m) (PackInto a b) -> m () basicUnsafeReplicate :: PrimMonad m => Int -> PackInto a b -> m (MVector (PrimState m) (PackInto a b)) basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (PackInto a b) -> Int -> m (PackInto a b) basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (PackInto a b) -> Int -> PackInto a b -> m () basicClear :: PrimMonad m => MVector (PrimState m) (PackInto a b) -> m () basicSet :: PrimMonad m => MVector (PrimState m) (PackInto a b) -> PackInto a b -> m () basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (PackInto a b) -> MVector (PrimState m) (PackInto a b) -> m () basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (PackInto a b) -> MVector (PrimState m) (PackInto a b) -> m () basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (PackInto a b) -> Int -> m (MVector (PrimState m) (PackInto a b)) | |
Unbox b => Vector Vector (PackInto a b) Source # | |
Defined in Data.Finitary.PackInto basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (PackInto a b) -> m (Vector (PackInto a b)) basicUnsafeThaw :: PrimMonad m => Vector (PackInto a b) -> m (Mutable Vector (PrimState m) (PackInto a b)) basicLength :: Vector (PackInto a b) -> Int basicUnsafeSlice :: Int -> Int -> Vector (PackInto a b) -> Vector (PackInto a b) basicUnsafeIndexM :: Monad m => Vector (PackInto a b) -> Int -> m (PackInto a b) basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (PackInto a b) -> Vector (PackInto a b) -> m () elemseq :: Vector (PackInto a b) -> PackInto a b -> b0 -> b0 | |
(Finitary a, Finitary b, 1 <= Cardinality a, Cardinality a <= Cardinality b) => Bounded (PackInto a b) Source # | |
Eq b => Eq (PackInto a b) Source # | |
(Finitary a, Finitary b, Cardinality a <= Cardinality b) => Ord (PackInto a b) Source # | |
Defined in Data.Finitary.PackInto | |
Show b => Show (PackInto a b) Source # | |
Storable b => Storable (PackInto a b) Source # | |
Defined in Data.Finitary.PackInto sizeOf :: PackInto a b -> Int # alignment :: PackInto a b -> Int # peekElemOff :: Ptr (PackInto a b) -> Int -> IO (PackInto a b) # pokeElemOff :: Ptr (PackInto a b) -> Int -> PackInto a b -> IO () # peekByteOff :: Ptr b0 -> Int -> IO (PackInto a b) # pokeByteOff :: Ptr b0 -> Int -> PackInto a b -> IO () # | |
NFData b => NFData (PackInto a b) Source # | |
Defined in Data.Finitary.PackInto | |
(Finitary a, Finitary b, Cardinality a <= Cardinality b) => Finitary (PackInto a b) Source # | |
Defined in Data.Finitary.PackInto | |
Unbox b => Unbox (PackInto a b) Source # | |
Defined in Data.Finitary.PackInto | |
Hashable b => Hashable (PackInto a b) Source # | |
Defined in Data.Finitary.PackInto | |
newtype MVector s (PackInto a b) Source # | |
Defined in Data.Finitary.PackInto | |
type Cardinality (PackInto a b) Source # | |
Defined in Data.Finitary.PackInto type Cardinality (PackInto a b) = Cardinality a | |
newtype Vector (PackInto a b) Source # | |
Defined in Data.Finitary.PackInto |
pattern Packed :: forall (b :: Type) (a :: Type). (Finitary a, Finitary b, Cardinality a <= Cardinality b) => PackInto a b -> a Source #
To provide (something that resembles a) data constructor for PackInto
, we
provide the following pattern. It can be used like any other data
constructor:
import Data.Finitary.PackInt anInt :: PackInto Int Word anInt = Packed 10 isPackedEven :: PackInto Int Word -> Bool isPackedEven (Packed x) = even x
Every pattern match, and data constructor call, performs a re-encoding by
way of fromFinite . toFinite
on b
and a
respectively. Use with this in
mind.