Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension


Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 2 additions & 2 deletions .github/workflows/ci.yml
Original file line number Diff line number Diff line change
Expand Up @@ -24,11 +24,11 @@ jobs:
include:
# Linux
- { cabal: "3.14", os: ubuntu-latest, ghc: "8.10.7" }
- { cabal: "3.14", os: ubuntu-latest, ghc: "9.0.1" }
- { cabal: "3.14", os: ubuntu-latest, ghc: "9.0.2" }
- { cabal: "3.14", os: ubuntu-latest, ghc: "9.2.8" }
- { cabal: "3.14", os: ubuntu-latest, ghc: "9.4.8" }
- { cabal: "3.14", os: ubuntu-latest, ghc: "9.6.7" }
- { cabal: "3.14", os: ubuntu-latest, ghc: "9.8.2" }
- { cabal: "3.14", os: ubuntu-latest, ghc: "9.8.4" }
- { cabal: "3.14", os: ubuntu-latest, ghc: "9.10.2" }
- { cabal: "3.14", os: ubuntu-latest, ghc: "9.12.2" }
fail-fast: false
Expand Down
6 changes: 6 additions & 0 deletions fixed-vector/ChangeLog.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,9 @@
2.0.1.0 [XXX]
-------------
* All data types defined in library now has `Prim` instance.
* `Prim` could be derived using `ViaFixed` by deriving via mechanism.


2.0.0.0 [2025.07.10]
------------------
* Type family `Dim` returns Peano numbers instead of standard type level
Expand Down
88 changes: 79 additions & 9 deletions fixed-vector/Data/Vector/Fixed.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UndecidableInstances #-}
-- |
-- @fixed-vector@ library provides general API for working with short
Expand Down Expand Up @@ -188,23 +190,27 @@ module Data.Vector.Fixed (
, sequenceA
) where

import Control.Applicative (Applicative(..))
import Control.DeepSeq (NFData(..))
import Control.Applicative (Applicative(..))
import Control.DeepSeq (NFData(..))
import Control.Monad.Primitive (PrimBase(..))
import Data.Coerce
import Data.Data (Data)
import Data.Monoid (Monoid(..))
import Data.Semigroup (Semigroup(..))
import Data.Foldable qualified as F
import Data.Traversable qualified as T
import Foreign.Storable (Storable(..))
import Data.Data (Data)
import Data.Monoid (Monoid(..))
import Data.Semigroup (Semigroup(..))
import Data.Foldable qualified as F
import Data.Traversable qualified as T
import Data.Primitive.Types (Prim(..))
import Foreign.Storable (Storable(..))
import GHC.TypeLits
import GHC.Exts (Proxy#,proxy#,(*#),(+#),Int(..),Int#)
import GHC.ST (ST(..))

import Data.Vector.Fixed.Cont (Vector(..),Dim,length,ContVec,PeanoNum(..),
vector,cvec,empty,Arity,ArityPeano,Fun(..),accum,apply)
import Data.Vector.Fixed.Cont qualified as C
import Data.Vector.Fixed.Internal as I

import Prelude (Show(..),Eq(..),Ord(..),Num(..),Functor(..),id,(.),($),(<$>))
import Prelude (Show(..),Eq(..),Ord(..),Num(..),Functor(..),id,(.),($),(<$>),undefined,flip)


-- $construction
Expand Down Expand Up @@ -302,6 +308,8 @@ deriving via ViaFixed (VecList n) a instance (Arity n, NFData a) => NFData
deriving via ViaFixed (VecList n) a instance (Arity n, Semigroup a) => Semigroup (VecList n a)
deriving via ViaFixed (VecList n) a instance (Arity n, Monoid a) => Monoid (VecList n a)
deriving via ViaFixed (VecList n) a instance (Arity n, Storable a) => Storable (VecList n a)
-- | @since 2.0.1.0
deriving via ViaFixed (VecList n) a instance (Arity n, Prim a) => Prim (VecList n a)



Expand All @@ -326,6 +334,8 @@ deriving via ViaFixed (VecPeano n) a instance (ArityPeano n, NFData a) => NFD
deriving via ViaFixed (VecPeano n) a instance (ArityPeano n, Semigroup a) => Semigroup (VecPeano n a)
deriving via ViaFixed (VecPeano n) a instance (ArityPeano n, Monoid a) => Monoid (VecPeano n a)
deriving via ViaFixed (VecPeano n) a instance (ArityPeano n, Storable a) => Storable (VecPeano n a)
-- | @since 2.0.1.0
deriving via ViaFixed (VecPeano n) a instance (ArityPeano n, Prim a) => Prim (VecPeano n a)



Expand Down Expand Up @@ -430,6 +440,66 @@ instance (Vector v a, Storable a) => Storable (ViaFixed v a) where
{-# INLINE peek #-}
{-# INLINE poke #-}

-- | @since 2.0.1.0
instance (Vector v a, Prim a) => Prim (ViaFixed v a) where
sizeOf# _ = sizeOf# (undefined :: a) *# dim where
dim = case C.peanoToInt (proxy# @(Dim v)) of I# i -> i
alignment# _ = alignment# (undefined :: a)
{-# INLINE sizeOf# #-}
{-# INLINE alignment# #-}
-- Bytearray
indexByteArray# ba k
= generate $ \(I# i) -> indexByteArray# ba (off +# i)
where
off = vectorOff (proxy# @(Dim v)) k
readByteArray# ba k
= internal
$ generateM
$ \(I# i) -> ST (\s -> readByteArray# ba (off +# i) s)
where
off = vectorOff (proxy# @(Dim v)) k
writeByteArray# ba k (ViaFixed vec) =
case loop of
ST st -> \s -> case st s of
(# s', () #) -> s'
where
off = vectorOff (proxy# @(Dim v)) k
loop = flip imapM_ vec $ \(I# i) a -> ST $ \s ->
(# writeByteArray# ba (off +# i) a s, () #)
{-# INLINE indexByteArray# #-}
{-# INLINE readByteArray# #-}
{-# INLINE writeByteArray# #-}
-- Addr
indexOffAddr# addr k
= generate $ \(I# i) -> indexOffAddr# addr (off +# i)
where
off = vectorOff (proxy# @(Dim v)) k
readOffAddr# ba k
= internal
$ generateM
$ \(I# i) -> ST (\s -> readOffAddr# ba (off +# i) s)
where
off = vectorOff (proxy# @(Dim v)) k
writeOffAddr# addr k (ViaFixed vec) =
case loop of
ST st -> \s -> case st s of
(# s', () #) -> s'
where
off = vectorOff (proxy# @(Dim v)) k
loop = flip imapM_ vec $ \(I# i) a -> ST $ \s ->
(# writeOffAddr# addr (off +# i) a s, () #)
{-# INLINE indexOffAddr# #-}
{-# INLINE readOffAddr# #-}
{-# INLINE writeOffAddr# #-}


vectorOff :: (ArityPeano n) => Proxy# n -> Int# -> Int#
{-# INLINE vectorOff #-}
vectorOff n k =
case C.peanoToInt n of
I# dim -> dim *# k


instance (forall a. Vector v a) => Functor (ViaFixed v) where
fmap = map
{-# INLINE fmap #-}
Expand Down
6 changes: 5 additions & 1 deletion fixed-vector/Data/Vector/Fixed/Boxed.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UndecidableInstances #-}
-- |
-- Lazy vector which could hold any value. For strict variant see
Expand All @@ -21,9 +22,10 @@ import Data.Primitive.SmallArray
import Data.Monoid (Monoid(..))
import Data.Semigroup (Semigroup(..))
import Data.Data
import Data.Primitive.Types (Prim)
import qualified Data.Foldable as F
import qualified Data.Traversable as T
import Foreign.Storable (Storable(..))
import Foreign.Storable (Storable)
import GHC.TypeLits
import GHC.Exts (proxy#)
import Prelude ( Show(..),Eq(..),Ord(..),Functor(..),Monad(..)
Expand Down Expand Up @@ -82,6 +84,8 @@ deriving via ViaFixed (Vec n) a instance (Arity n, NFData a) => NFData (Ve
deriving via ViaFixed (Vec n) a instance (Arity n, Semigroup a) => Semigroup (Vec n a)
deriving via ViaFixed (Vec n) a instance (Arity n, Monoid a) => Monoid (Vec n a)
deriving via ViaFixed (Vec n) a instance (Arity n, Storable a) => Storable (Vec n a)
-- | @since 2.0.1.0
deriving via ViaFixed (Vec n) a instance (Arity n, Prim a) => Prim (Vec n a)

instance (Arity n) => MVector (MVec n) a where
basicNew =
Expand Down
3 changes: 3 additions & 0 deletions fixed-vector/Data/Vector/Fixed/Primitive.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UndecidableInstances #-}
-- |
-- Unboxed vectors with fixed length. Vectors from
Expand Down Expand Up @@ -73,6 +74,8 @@ deriving via ViaFixed (Vec n) a instance (Arity n, Prim a, Ord a) => Ord
deriving via ViaFixed (Vec n) a instance (Arity n, Prim a, Semigroup a) => Semigroup (Vec n a)
deriving via ViaFixed (Vec n) a instance (Arity n, Prim a, Monoid a) => Monoid (Vec n a)
deriving via ViaFixed (Vec n) a instance (Arity n, Prim a, Storable a) => Storable (Vec n a)
-- | @since 2.0.1.0
deriving via ViaFixed (Vec n) a instance (Arity n, Prim a) => Prim (Vec n a)

instance (Arity n, Prim a) => MVector (MVec n) a where
basicNew = do
Expand Down
5 changes: 5 additions & 0 deletions fixed-vector/Data/Vector/Fixed/Storable.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UndecidableInstances #-}
-- |
-- Storable-based unboxed vectors.
Expand All @@ -26,6 +27,7 @@ import Control.DeepSeq (NFData(..))
import Data.Monoid (Monoid(..))
import Data.Semigroup (Semigroup(..))
import Data.Data
import Data.Primitive.Types (Prim)
import Foreign.Ptr (castPtr)
import Foreign.Storable
import Foreign.Marshal.Array ( copyArray, moveArray )
Expand Down Expand Up @@ -156,6 +158,9 @@ instance (Arity n, Storable a) => Storable (Vec n a) where
= unsafeWithForeignPtr fp $ \p ->
moveArray (castPtr ptr) p (peanoToInt (proxy# @(Peano n)))

-- | @since 2.0.1.0
deriving via ViaFixed (Vec n) a instance (Arity n, Storable a, Prim a) => Prim (Vec n a)

instance (Typeable n, Arity n, Storable a, Data a) => Data (Vec n a) where
gfoldl = C.gfoldl
gunfold = C.gunfold
Expand Down
6 changes: 5 additions & 1 deletion fixed-vector/Data/Vector/Fixed/Strict.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UndecidableInstances #-}
-- |
-- Strict boxed vector which could hold any value. For lazy variant see
Expand All @@ -11,9 +12,10 @@ import Data.Primitive.SmallArray
import Data.Monoid (Monoid(..))
import Data.Semigroup (Semigroup(..))
import Data.Data
import Data.Primitive.Types (Prim)
import qualified Data.Foldable as F
import qualified Data.Traversable as T
import Foreign.Storable (Storable(..))
import Foreign.Storable (Storable)
import GHC.TypeLits
import GHC.Exts (proxy#)
import Prelude ( Show(..),Eq(..),Ord(..),Functor(..),Monad(..)
Expand Down Expand Up @@ -72,6 +74,8 @@ deriving via ViaFixed (Vec n) a instance (Arity n, NFData a) => NFData (Ve
deriving via ViaFixed (Vec n) a instance (Arity n, Semigroup a) => Semigroup (Vec n a)
deriving via ViaFixed (Vec n) a instance (Arity n, Monoid a) => Monoid (Vec n a)
deriving via ViaFixed (Vec n) a instance (Arity n, Storable a) => Storable (Vec n a)
-- | @since 2.0.1.0
deriving via ViaFixed (Vec n) a instance (Arity n, Prim a) => Prim (Vec n a)

instance (Arity n) => MVector (MVec n) a where
basicNew =
Expand Down
5 changes: 4 additions & 1 deletion fixed-vector/Data/Vector/Fixed/Unboxed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,8 @@ import Data.Monoid (Monoid(..),Dual(..),Sum(..),Product(..),All(..),An
import Data.Semigroup (Semigroup(..))
import Data.Ord (Down(..))
import Data.Word (Word,Word8,Word16,Word32,Word64)
import Foreign.Storable (Storable(..))
import Data.Primitive.Types (Prim)
import Foreign.Storable (Storable)
import GHC.TypeLits
import GHC.Exts (Proxy#, proxy#)
import Prelude ( Show(..),Eq(..),Ord(..),Num(..),Applicative(..)
Expand Down Expand Up @@ -110,6 +111,8 @@ deriving via ViaFixed (Vec n) a instance (Unbox n a, NFData a) => NFData (
deriving via ViaFixed (Vec n) a instance (Unbox n a, Semigroup a) => Semigroup (Vec n a)
deriving via ViaFixed (Vec n) a instance (Unbox n a, Monoid a) => Monoid (Vec n a)
deriving via ViaFixed (Vec n) a instance (Unbox n a, Storable a) => Storable (Vec n a)
-- | @since 2.0.1.0
deriving via ViaFixed (Vec n) a instance (Unbox n a, Prim a) => Prim (Vec n a)

instance (Typeable n, Unbox n a, Data a) => Data (Vec n a) where
gfoldl = C.gfoldl
Expand Down
61 changes: 33 additions & 28 deletions fixed-vector/fixed-vector.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -2,48 +2,52 @@ Cabal-Version: 3.0
Build-Type: Simple

Name: fixed-vector
Version: 2.0.0.0
Version: 2.0.1.0
Synopsis: Generic vectors with statically known size.
Description:
Generic library for vectors with statically known
size. Implementation is based on
<http://unlines.wordpress.com/2010/11/15/generics-for-small-fixed-size-vectors/>
Same functions could be used to work with both ADT based vector like
.

> data Vec3 a = a a a
.

Tuples are vectors too:
.

>>> sum (1,2,3)
6
.

Vectors which are represented internally by arrays are provided by
library. Both boxed and unboxed arrays are supported.
.

Library is structured as follows:
.
* Data.Vector.Fixed

* __Data.Vector.Fixed__:
Generic API. It's suitable for both ADT-based vector like Complex
and array-based ones.
.
* Data.Vector.Fixed.Cont

* __Data.Vector.Fixed.Cont__:
Continuation based vectors. Internally all functions use them.
.
* Data.Vector.Fixed.Mutable

* __Data.Vector.Fixed.Unboxed__:
Unboxed vectors which select best representation using types.

* __Data.Vector.Fixed.Strict__:
Strict boxed vector which can hold elements of any type.

* __Data.Vector.Fixed.Boxed__:
Lazy boxed vector which can hold elements of any type.

* __Data.Vector.Fixed.Storable__:
Unboxed vectors of Storable types.

* __Data.Vector.Fixed.Primitive__:
Unboxed vectors backed by single @ByteArray@

* __Data.Vector.Fixed.Mutable__:
Type classes for array-based implementation and API for working with
mutable state.
.
* Data.Vector.Fixed.Unboxed
Unboxed vectors.
.
* Data.Vector.Fixed.Boxed
Boxed vector which can hold elements of any type.
.
* Data.Vector.Fixed.Storable
Unboxed vectors of Storable types.
.
* Data.Vector.Fixed.Primitive
Unboxed vectors based on pritimive package.


License: BSD-3-Clause
License-File: LICENSE
Expand All @@ -56,12 +60,13 @@ extra-doc-files:

tested-with:
GHC ==8.10.7
|| ==9.0.1
|| ==9.0.2
|| ==9.2.8
|| ==9.4.7
|| ==9.6.6
|| ==9.8.2
|| ==9.10.1
|| ==9.6.7
|| ==9.8.4
|| ==9.10.2
|| ==9.12.2

source-repository head
type: git
Expand Down
Loading