In August 2017, Jason Le identified the vector-sized
package as the canonical source for efficient fixed-size vectors.
Module Data.Vector.Generic.Sized.Internal
of the package exports a new type Vector
defined as:
1 2 3 4 5 |
newtype Vector v (n :: Nat) a = Vector (v a) deriving ( Show, Eq, Ord, Functor, Foldable, Traversable, NFData, Generic , Show1, Eq1, Ord1 , Data, Typeable ) |
and module Data.Vector.Sized
defines the type synonym Vector
(where Data.Vector
is a module of the vector
package):
1 2 3 4 |
import qualified Data.Vector.Generic.Sized as V import qualified Data.Vector as VU type Vector = V.Vector VU.Vector |
As shown above, instances of Vector v (n :: Nat) a
are derived for a number of classes, but (as of version 1.0.4.0 of the package) there is no instance for the Ix
class exported by module Data.Ix
of the base
package. I wanted to create one.
Data.Vector.Generic.Sized.Internal
The module makes use of a number of extensions to the Haskell 2010 language provided by GHC. Four of them are related to deriving but two are related to types:
1 2 |
{-# LANGUAGE DataKinds #-} {-# LANGUAGE KindSignatures #-} |
The DataKinds
extension enables numeric type literals of kind Nat
, exported by the GHC.TypeLits
module. The KindSignatures
extension enables kind signatures to be added to type variables, such as n :: Nat
.
instance (Ix a, Ord (v a), VG.Vector v a) => Ix (Vector v n a)
The class Ix
exported by module Data.Ix
is a re-export from module GHC.Arr
. The original class definition includes signatures for range
,rangeSize
,inRange
, and index
but also unsafeRangeSize
and unsafeIndex
. The latter are not re-exported by Data.Ix
. Default implementations of index
and unsafeIndex
refer to each other. Default implementations of rangeSize
and unsafeRangeSize
refer to unsafeIndex
.
Module GHC.Arr
defines instances of class Ix
for ()
(the unit type) and tuples of various sizes whose elements are of types that are instances of Ix
.
1 2 3 4 5 6 7 8 9 10 11 12 13 |
instance Ix () where range ((), ()) = [()] unsafeIndex ((), ()) () = 0 inRange ((), ()) () = True index b i = unsafeIndex b i instance (Ix a, Ix b) => Ix (a, b) where range ((l1, l2), (u1, u2)) = [ (i1, i2) | i1 <- range (l1, u1), i2 <- range (l2, u2) ] unsafeIndex ((l1, l2), (u1, u2)) (i1, i2) = unsafeIndex (l1, u1) i1 * unsafeRangeSize (l2, u2) + unsafeIndex (l2, u2) i2 inRange ((l1, l2), (u1, u2)) (i1, i2) = inRange (l1, u1) i1 && inRange (l2, u2) i2 |
I took a similar approach to instance (Ix a, Ord (v a), Data.Vector.Generic.Vector v a) => Ix (Vector v n a)
, as shown below:
1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 |
import Data.Vector as V (and, foldl', null, zipWith, zipWith3) import qualified Data.Vector.Generic as VG (Vector, convert, empty, fromList, toList) instance (Ix a, Ord (v a), VG.Vector v a) => Ix (Vector v n a) where range (Vector l, Vector u) = Vector <$> enumerate ranges where ranges = V.zipWith (curry range) lc uc lc = VG.convert l uc = VG.convert u enumerate v | V.null v = [VG.empty] | otherwise = map VG.fromList $ enumerate' (VG.toList v) enumerate' [] = [[]] enumerate' (xs:xss) = [ x : xs' | x <- xs, xs' <- enumerate' xss ] unsafeIndex (Vector l, Vector u) (Vector i) = V.foldl' f 0 v where f acc (index', rangeSize') = acc * rangeSize' + index' v = V.zipWith3 indexAndRangeSize lc uc ic lc = VG.convert l uc = VG.convert u ic = VG.convert i indexAndRangeSize l' u' i' = let b' = (l', u') in (unsafeIndex b' i', unsafeRangeSize b') inRange (Vector l, Vector u) (Vector i) = V.and $ V.zipWith3 (curry inRange) lc uc ic where lc = VG.convert l uc = VG.convert u ic = VG.convert i |
The class Ix
is defined as class Ord a => Ix a where ...
, with the constraint Ord a
. Vector v n a
is an instance of class Ord
, but only if v a
is an instance of Ord
; that must be specified expressly.
instance (Ix a, …) => Ix (Vector v n a)
Can the instance be made more general than the Data.Vector.Generic.Vector v a
constraint allows? The answer is ‘yes’.
Class Foldable
, exported by module Data.Foldable
, promises functions null
and foldl'
. The former is exported by the Prelude
. Data.Vector.and
is just a specialised form of a fold.
Class Monoid
, exported by the Prelude
, promises function mempty
.
Class MonadZip
, exported by module Control.Monad.Zip
, promises functions mzip
and mzipWith
. There is no mzipWith3
, but:
1 2 |
mzipWith3 :: (a -> b -> c -> d) -> m a -> m b -> m c -> m d mzipWith3 f a b c = mzipWith (uncurry f) (mzip a b) c |
Class IsList
, exported by module GHC.Exts
, is defined as:
1 2 3 4 5 6 |
class IsList l where type Item l fromList :: [Item l] -> l fromListN :: Int -> [Item l] -> l fromListN _ = fromList toList :: l -> [Item l] |
It promises functions toList
and fromList
and an associated type synonym family Item l
(of kind *
). The extension TypeFamilies
enables the use of associated type synonym families.
To translate:
1 |
map V.fromList $ enumerate' (V.toList v) |
v [a]
must be an instance of IsList
(for toList
), v a
must also be an instance of IsList
(for fromList
) and types [Item (v a)]
and Item (v [a])
must be equivalent (the constraint [Item (v a)] ~ Item (v [a])
).
1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 |
{-# LANGUAGE TypeFamilies #-} import Control.Monad.Zip (MonadZip (mzip, mzipWith)) import qualified Data.Foldable as F (Foldable (foldl')) import GHC.Exts as E (IsList (Item, fromList, toList)) instance {-# OVERLAPPABLE #-} ([Item (v a)] ~ Item (v [a]), Foldable v, IsList (v a), IsList (v [a]), Ix a, MonadZip v, Monoid (v a), Ord (v a)) => Ix (Vector v n a) where range (Vector l, Vector u) = Vector <$> enumerate ranges where ranges = mzipWith (curry range) l u enumerate v | null v = [mempty] | otherwise = map E.fromList $ enumerate' (E.toList v) enumerate' [] = [[]] enumerate' (xs:xss) = [ x : xs' | x <- xs, xs' <- enumerate' xss ] unsafeIndex (Vector l, Vector u) (Vector i) = F.foldl' f 0 v where f acc (index', rangeSize') = acc * rangeSize' + index' v = mzipWith indexAndRangeSize (mzip l u) i indexAndRangeSize b' i' = (unsafeIndex b' i', unsafeRangeSize b') inRange (Vector l, Vector u) (Vector i) = F.foldl' (&&) True $ mzipWith inRange (mzip l u) i |