finitary-derive-2.1.0.0: Flexible and easy deriving of type classes for finitary types.
Copyright(C) Koz Ross 2019
LicenseGPL version 3.0 or later
Maintainerkoz.ross@retro-freedom.nz
StabilityExperimental
PortabilityGHC only
Safe HaskellNone
LanguageHaskell2010

Data.Finitary.PackInto

Description

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.

Synopsis

Documentation

data PackInto (a :: Type) (b :: Type) Source #

An opaque wrapper, representing values of type a as 'corresponding' values of type b.

Instances

Instances details
Unbox b => Vector Vector (PackInto a b) Source # 
Instance details

Defined in Data.Finitary.PackInto

Unbox b => MVector MVector (PackInto a b) Source # 
Instance details

Defined in Data.Finitary.PackInto

(Finitary a, Finitary b, 1 <= Cardinality a, Cardinality a <= Cardinality b) => Bounded (PackInto a b) Source # 
Instance details

Defined in Data.Finitary.PackInto

Methods

minBound :: PackInto a b #

maxBound :: PackInto a b #

Eq b => Eq (PackInto a b) Source # 
Instance details

Defined in Data.Finitary.PackInto

Methods

(==) :: PackInto a b -> PackInto a b -> Bool #

(/=) :: PackInto a b -> PackInto a b -> Bool #

(Ord a, Finitary a, Finitary b, Cardinality a <= Cardinality b) => Ord (PackInto a b) Source # 
Instance details

Defined in Data.Finitary.PackInto

Methods

compare :: PackInto a b -> PackInto a b -> Ordering #

(<) :: PackInto a b -> PackInto a b -> Bool #

(<=) :: PackInto a b -> PackInto a b -> Bool #

(>) :: PackInto a b -> PackInto a b -> Bool #

(>=) :: PackInto a b -> PackInto a b -> Bool #

max :: PackInto a b -> PackInto a b -> PackInto a b #

min :: PackInto a b -> PackInto a b -> PackInto a b #

Show b => Show (PackInto a b) Source # 
Instance details

Defined in Data.Finitary.PackInto

Methods

showsPrec :: Int -> PackInto a b -> ShowS #

show :: PackInto a b -> String #

showList :: [PackInto a b] -> ShowS #

Storable b => Storable (PackInto a b) Source # 
Instance details

Defined in Data.Finitary.PackInto

Methods

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 () #

peek :: Ptr (PackInto a b) -> IO (PackInto a b) #

poke :: Ptr (PackInto a b) -> PackInto a b -> IO () #

NFData b => NFData (PackInto a b) Source # 
Instance details

Defined in Data.Finitary.PackInto

Methods

rnf :: PackInto a b -> () #

(Finitary a, Finitary b, Cardinality a <= Cardinality b) => Finitary (PackInto a b) Source # 
Instance details

Defined in Data.Finitary.PackInto

Associated Types

type Cardinality (PackInto a b) :: Nat #

Methods

fromFinite :: Finite (Cardinality (PackInto a b)) -> PackInto a b #

toFinite :: PackInto a b -> Finite (Cardinality (PackInto a b)) #

start :: PackInto a b #

end :: PackInto a b #

previous :: Alternative f => PackInto a b -> f (PackInto a b) #

next :: Alternative f => PackInto a b -> f (PackInto a b) #

Hashable b => Hashable (PackInto a b) Source # 
Instance details

Defined in Data.Finitary.PackInto

Methods

hashWithSalt :: Int -> PackInto a b -> Int #

hash :: PackInto a b -> Int #

Unbox b => Unbox (PackInto a b) Source # 
Instance details

Defined in Data.Finitary.PackInto

newtype MVector s (PackInto a b) Source # 
Instance details

Defined in Data.Finitary.PackInto

newtype MVector s (PackInto a b) = MV_PackInto (MVector s b)
newtype Vector (PackInto a b) Source # 
Instance details

Defined in Data.Finitary.PackInto

newtype Vector (PackInto a b) = V_PackInto (Vector b)
type Cardinality (PackInto a b) Source # 
Instance details

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.