#if __GLASGOW_HASKELL__ >= 707
#define USE_TYPE_LITS 1
#endif
#ifndef MIN_VERSION_reflection
#define MIN_VERSION_reflection(x,y,z) 1
#endif
module Linear.V
( V(V,toVector)
, int
, dim
, Dim(..)
, reifyDim
, reifyVector
, fromVector
) where
import Control.Applicative
import Control.DeepSeq (NFData)
import Control.Monad.Fix
import Control.Monad.Zip
import Control.Lens as Lens
import Data.Data
import Data.Distributive
import Data.Foldable as Foldable
import Data.Functor.Bind
import Data.Functor.Rep as Rep
#if __GLASGOW_HASKELL__ < 708
import Data.Proxy
#endif
import Data.Reflection as R
import Data.Vector as V
import Foreign.Ptr
import Foreign.Storable
#ifdef USE_TYPE_LITS
import GHC.TypeLits
#endif
#if __GLASGOW_HASKELL__ >= 702
import GHC.Generics (Generic)
#endif
#if __GLASGOW_HASKELL__ >= 707
import GHC.Generics (Generic1)
#endif
#if !(MIN_VERSION_reflection(1,3,0))
import Language.Haskell.TH
#endif
import Linear.Epsilon
import Linear.Metric
import Linear.Vector
#ifdef HLINT
#endif
class Dim n where
reflectDim :: p n -> Int
#if __GLASGOW_HASKELL__ >= 707
type role V nominal representational
#endif
newtype V n a = V { toVector :: V.Vector a } deriving (Eq,Ord,Show,Read,Typeable,NFData
, Generic
#if __GLASGOW_HASKELL__ >= 707
,Generic1
#endif
)
dim :: forall n a. Dim n => V n a -> Int
dim _ = reflectDim (Proxy :: Proxy n)
#ifdef USE_TYPE_LITS
instance KnownNat n => Dim (n :: Nat) where
reflectDim = fromInteger . natVal
#endif
data ReifiedDim (s :: *)
retagDim :: (Proxy s -> a) -> proxy (ReifiedDim s) -> a
retagDim f _ = f Proxy
instance Reifies s Int => Dim (ReifiedDim s) where
reflectDim = retagDim reflect
reifyDim :: Int -> (forall (n :: *). Dim n => Proxy n -> r) -> r
reifyDim i f = R.reify i (go f) where
go :: Reifies n Int => (Proxy (ReifiedDim n) -> a) -> proxy n -> a
go g _ = g Proxy
reifyVector :: forall a r. Vector a -> (forall (n :: *). Dim n => V n a -> r) -> r
reifyVector v f = reifyDim (V.length v) $ \(Proxy :: Proxy n) -> f (V v :: V n a)
instance Dim n => Dim (V n a) where
reflectDim _ = reflectDim (Proxy :: Proxy n)
instance Functor (V n) where
fmap f (V as) = V (fmap f as)
instance FunctorWithIndex Int (V n) where
imap f (V as) = V (Lens.imap f as)
instance Foldable (V n) where
foldMap f (V as) = foldMap f as
instance FoldableWithIndex Int (V n) where
ifoldMap f (V as) = ifoldMap f as
instance Traversable (V n) where
traverse f (V as) = V <$> traverse f as
instance TraversableWithIndex Int (V n) where
itraverse f (V as) = V <$> itraverse f as
instance Apply (V n) where
V as <.> V bs = V (V.zipWith id as bs)
instance Dim n => Applicative (V n) where
pure = V . V.replicate (reflectDim (Proxy :: Proxy n))
V as <*> V bs = V (V.zipWith id as bs)
instance Bind (V n) where
V as >>- f = V $ generate (V.length as) $ \i ->
toVector (f (as `unsafeIndex` i)) `unsafeIndex` i
instance Dim n => Monad (V n) where
return = V . V.replicate (reflectDim (Proxy :: Proxy n))
V as >>= f = V $ generate (reflectDim (Proxy :: Proxy n)) $ \i ->
toVector (f (as `unsafeIndex` i)) `unsafeIndex` i
instance Dim n => Additive (V n) where
zero = pure 0
liftU2 f (V as) (V bs) = V (V.zipWith f as bs)
liftI2 f (V as) (V bs) = V (V.zipWith f as bs)
instance (Dim n, Num a) => Num (V n a) where
V as + V bs = V $ V.zipWith (+) as bs
V as V bs = V $ V.zipWith () as bs
V as * V bs = V $ V.zipWith (*) as bs
negate = fmap negate
abs = fmap abs
signum = fmap signum
fromInteger = pure . fromInteger
instance (Dim n, Fractional a) => Fractional (V n a) where
recip = fmap recip
V as / V bs = V $ V.zipWith (/) as bs
fromRational = pure . fromRational
instance Dim n => Distributive (V n) where
distribute f = V $ V.generate (reflectDim (Proxy :: Proxy n)) $ \i -> fmap (\(V v) -> unsafeIndex v i) f
instance (Dim n, Storable a) => Storable (V n a) where
sizeOf _ = reflectDim (Proxy :: Proxy n) * sizeOf (undefined:: a)
alignment _ = alignment (undefined :: a)
poke ptr (V xs) = Foldable.forM_ [0..reflectDim (Proxy :: Proxy n)1] $ \i ->
pokeElemOff ptr' i (unsafeIndex xs i)
where ptr' = castPtr ptr
peek ptr = V <$> generateM (reflectDim (Proxy :: Proxy n)) (peekElemOff ptr')
where ptr' = castPtr ptr
instance (Dim n, Epsilon a) => Epsilon (V n a) where
nearZero = nearZero . quadrance
instance Dim n => Metric (V n) where
dot (V a) (V b) = V.sum $ V.zipWith (*) a b
fromVector :: forall n a. Dim n => Vector a -> Maybe (V n a)
fromVector v
| V.length v == reflectDim (Proxy :: Proxy n) = Just (V v)
| otherwise = Nothing
#if !(MIN_VERSION_reflection(1,3,0))
data Z
data D (n :: *)
data SD (n :: *)
data PD (n :: *)
instance Reifies Z Int where
reflect _ = 0
retagD :: (Proxy n -> a) -> proxy (D n) -> a
retagD f _ = f Proxy
retagSD :: (Proxy n -> a) -> proxy (SD n) -> a
retagSD f _ = f Proxy
retagPD :: (Proxy n -> a) -> proxy (PD n) -> a
retagPD f _ = f Proxy
instance Reifies n Int => Reifies (D n) Int where
reflect = (\n -> n+n) <$> retagD reflect
instance Reifies n Int => Reifies (SD n) Int where
reflect = (\n -> n+n+1) <$> retagSD reflect
instance Reifies n Int => Reifies (PD n) Int where
reflect = (\n -> n+n1) <$> retagPD reflect
int :: Int -> TypeQ
int n = case quotRem n 2 of
(0, 0) -> conT ''Z
(q,1) -> conT ''PD `appT` int q
(q, 0) -> conT ''D `appT` int q
(q, 1) -> conT ''SD `appT` int q
_ -> error "ghc is bad at math"
#endif
instance Dim n => Representable (V n) where
type Rep (V n) = Int
tabulate = V . generate (reflectDim (Proxy :: Proxy n))
index (V xs) i = xs V.! i
type instance Index (V n a) = E (V n)
type instance IxValue (V n a) = a
instance Ixed (V n a) where
ix = el
instance Dim n => MonadZip (V n) where
mzip (V as) (V bs) = V $ V.zip as bs
mzipWith f (V as) (V bs) = V $ V.zipWith f as bs
instance Dim n => MonadFix (V n) where
mfix f = tabulate $ \r -> let a = Rep.index (f a) r in a
instance Each (V n a) (V n b) a b where
each = traverse
instance (Bounded a, Dim n) => Bounded (V n a) where
minBound = pure minBound
maxBound = pure maxBound
vConstr :: Constr
vConstr = mkConstr vDataType "variadic" [] Prefix
vDataType :: DataType
vDataType = mkDataType "Linear.V.V" [vConstr]
instance (Dim n, Typeable n, Data a) => Data (V n a) where
gfoldl f z (V as) = z (V . fromList) `f` V.toList as
toConstr _ = vConstr
gunfold k z c = case constrIndex c of
1 -> k (z (V . fromList))
_ -> error "gunfold"
dataTypeOf _ = vDataType
dataCast1 f = gcast1 f