module Data.Vector.Fixed (
Dim
, Vector(..)
, VectorN
, Arity
, Fun(..)
, length
, mk0
, mk1
, mk2
, mk3
, mk4
, mk5
, mkN
, ContVec
, empty
, vector
, C.cvec
, replicate
, replicateM
, generate
, generateM
, unfoldr
, basis
, head
, tail
, cons
, snoc
, concat
, reverse
, (!)
, index
, set
, element
, elementTy
, eq
, ord
, map
, mapM
, mapM_
, imap
, imapM
, imapM_
, scanl
, scanl1
, sequence
, sequence_
, sequenceA
, traverse
, distribute
, collect
, foldl
, foldr
, foldl1
, fold
, foldMap
, ifoldl
, ifoldr
, foldM
, ifoldM
, sum
, maximum
, minimum
, and
, or
, all
, any
, find
, zipWith
, zipWith3
, zipWithM
, zipWithM_
, izipWith
, izipWith3
, izipWithM
, izipWithM_
, defaultAlignemnt
, defaultSizeOf
, defaultPeek
, defaultPoke
, defaultRnf
, convert
, toList
, fromList
, fromList'
, fromListM
, fromFoldable
, VecList(..)
, VecPeano(..)
, Only(..)
, Empty(..)
, Tuple2
, Tuple3
, Tuple4
, Tuple5
) where
import Control.Applicative (Applicative(..),(<$>))
import Control.DeepSeq (NFData(..))
import Data.Data (Typeable,Data)
import Data.Monoid (Monoid(..))
import Data.Semigroup (Semigroup(..))
import qualified Data.Foldable as F
import qualified Data.Traversable as T
import Foreign.Storable (Storable(..))
import Foreign.Ptr (castPtr)
import GHC.TypeLits
import Data.Vector.Fixed.Cont (Vector(..),VectorN,Dim,length,ContVec,PeanoNum(..),
vector,empty,Arity,Fun(..),accum,apply,vector)
import qualified Data.Vector.Fixed.Cont as C
import Data.Vector.Fixed.Internal
import Prelude (Show(..),Eq(..),Ord(..),Functor(..),id,(.),($),undefined)
import Prelude (Char)
newtype VecList (n :: Nat) a = VecList (VecPeano (C.Peano n) a)
data VecPeano (n :: PeanoNum) a where
Nil :: VecPeano 'Z a
Cons :: a -> VecPeano n a -> VecPeano ('S n) a
deriving (Typeable)
instance (Arity n, NFData a) => NFData (VecList n a) where
rnf = defaultRnf
type instance Dim (VecList n) = n
instance Arity n => Vector (VecList n) a where
construct = fmap VecList $ accum
(\(T_List f) a -> T_List (f . Cons a))
(\(T_List f) -> f Nil)
(T_List id :: T_List a (C.Peano n) (C.Peano n))
inspect (VecList v)
= inspect (apply step (Flip v) :: C.ContVec n a)
where
step :: Flip VecPeano a ('S k) -> (a, Flip VecPeano a k)
step (Flip (Cons a xs)) = (a, Flip xs)
instance Arity n => VectorN VecList n a
newtype Flip f a n = Flip (f n a)
newtype T_List a n k = T_List (VecPeano k a -> VecPeano n a)
instance (Show a, Arity n) => Show (VecList n a) where
show = show . foldr (:) []
instance (Eq a, Arity n) => Eq (VecList n a) where
(==) = eq
instance (Ord a, Arity n) => Ord (VecList n a) where
compare = ord
instance Arity n => Functor (VecList n) where
fmap = map
instance Arity n => Applicative (VecList n) where
pure = replicate
(<*>) = zipWith ($)
instance Arity n => F.Foldable (VecList n) where
foldr = foldr
instance Arity n => T.Traversable (VecList n) where
sequenceA = sequenceA
traverse = traverse
instance (Arity n, Monoid a) => Monoid (VecList n a) where
mempty = replicate mempty
mappend = zipWith mappend
instance (Arity n, Semigroup a) => Semigroup (VecList n a) where
(<>) = zipWith (<>)
instance (Storable a, Arity n) => Storable (VecList n a) where
alignment = defaultAlignemnt
sizeOf = defaultSizeOf
peek = defaultPeek
poke = defaultPoke
newtype Only a = Only a
deriving (Show,Eq,Ord,Typeable,Data)
instance Functor Only where
fmap f (Only a) = Only (f a)
instance F.Foldable Only where
foldr = foldr
instance T.Traversable Only where
sequenceA (Only f) = Only <$> f
traverse f (Only a) = Only <$> f a
instance Monoid a => Monoid (Only a) where
mempty = Only mempty
Only a `mappend` Only b = Only $ mappend a b
instance (Semigroup a) => Semigroup (Only a) where
Only a <> Only b = Only (a <> b)
instance NFData a => NFData (Only a) where
rnf (Only a) = rnf a
type instance Dim Only = 1
instance Vector Only a where
construct = Fun Only
inspect (Only a) (Fun f) = f a
instance (Storable a) => Storable (Only a) where
alignment _ = alignment (undefined :: a)
sizeOf _ = sizeOf (undefined :: a)
peek p = Only <$> peek (castPtr p)
poke p (Only a) = poke (castPtr p) a
data Empty a = Empty
deriving (Show,Eq,Ord)
deriving instance Typeable a => Typeable (Empty a)
deriving instance Data a => Data (Empty a)
instance Functor Empty where
fmap _ Empty = Empty
instance F.Foldable Empty where
foldr = foldr
instance T.Traversable Empty where
sequenceA Empty = pure Empty
traverse _ Empty = pure Empty
instance NFData (Empty a) where
rnf Empty = ()
type instance Dim Empty = 0
instance Vector Empty a where
construct = Fun Empty
inspect _ (Fun b) = b
type Tuple2 a = (a,a)
type Tuple3 a = (a,a,a)
type Tuple4 a = (a,a,a,a)
type Tuple5 a = (a,a,a,a,a)