----------------------------------------------------------- -- | -- Module : Control.Imperative.Vector.Base -- Copyright : (C) 2015, Yu Fukuzawa -- License : BSD3 -- Maintainer : minpou.primer@email.com -- Stability : experimental -- Portability : portable -- ----------------------------------------------------------- {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} module Control.Imperative.Vector.Base ( VectorEntity , MonadVector , VectorElem , NestedList , Dim(..) , dim1 , dim2 , dim3 , Size(..) ) where import Control.Imperative.Internal import Control.Monad.Base import Control.Monad.Primitive (PrimMonad) import Data.Int import Data.Nat import qualified Data.Vector.Generic.Mutable as GMV import qualified Data.Vector.Mutable as MV import qualified Data.Vector.Unboxed as UV import Data.Word -- | Useful constraint synonym for vector operations. type MonadVector m = (MonadBase (BaseEff m) m, PrimMonad (BaseEff m)) -- | Specialized 'Proxy' type. data Dim (n :: Nat) = Dim dim1 :: Dim (S Z) dim1 = Dim dim2 :: Dim (S (S Z)) dim2 = Dim dim3 :: Dim (S (S (S Z))) dim3 = Dim type VectorElem a = GMV.MVector (VectorEntity a) a type family NestedList (n :: Nat) a where NestedList Z a = a NestedList (S n) a = [NestedList n a] type family VectorEntity a :: * -> * -> * where VectorEntity Bool = UV.MVector VectorEntity Char = UV.MVector VectorEntity Double = UV.MVector VectorEntity Float = UV.MVector VectorEntity Int = UV.MVector VectorEntity Int8 = UV.MVector VectorEntity Int16 = UV.MVector VectorEntity Int32 = UV.MVector VectorEntity Int64 = UV.MVector VectorEntity Word = UV.MVector VectorEntity Word8 = UV.MVector VectorEntity Word16 = UV.MVector VectorEntity Word32 = UV.MVector VectorEntity Word64 = UV.MVector VectorEntity () = UV.MVector VectorEntity a = MV.MVector -- | A sized-list type for specify the size of array. data Size (n :: Nat) where One :: Size Z (:*:) :: {-# UNPACK #-} !Int -> Size n -> Size (S n) infixr 5 :*: