{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
module Data.Vector.Static (
Vector
, VectorConstructor
, IsVector
, vector
, normalize
, NormalizedVector
, Normalize
, unNormalizedVector
, norm
, vectorLenSquare
, VectorLenSquare
, vectorLen
, VectorLen
, dot
, Dot
, cross
, toHomogenous
, fromHomogenous
, genVectorInstance
) where
import Data.Containers (MonoZip(..))
import Data.MonoTraversable (omap, osum)
import Data.Tensor.Static ( IsTensor(..), scale, Scale, TensorConstructor, withTensor
, MonoFunctorCtx, MonoFoldableCtx, MonoZipCtx)
import Data.Tensor.Static.TH (genTensorInstance)
import GHC.Generics (Generic)
import GHC.TypeLits (Nat)
import Language.Haskell.TH (Q, Name, Dec)
import qualified Data.List.NonEmpty as N
type Vector n e = Tensor '[n] e
type VectorConstructor n e = TensorConstructor '[n] e
type IsVector n e = IsTensor '[n] e
newtype NormalizedVector n e =
NormalizedVector
{ unNormalizedVector :: Vector n e
}
deriving (Generic)
deriving instance (Eq (Vector n e)) => Eq (NormalizedVector n e)
deriving instance (Show (Vector n e)) => Show (NormalizedVector n e)
vector :: forall n e. (IsVector n e) => VectorConstructor n e
vector = tensor @'[n] @e
{-# INLINE vector #-}
vectorLenSquare :: (VectorLenSquare n e) => Vector n e -> e
vectorLenSquare = osum . omap (\x -> x * x)
{-# INLINE vectorLenSquare #-}
type VectorLenSquare (n :: Nat) e =
( Num e
, IsVector n e
, MonoFunctorCtx '[n] e
, MonoFoldableCtx '[n] e
)
vectorLen :: (VectorLen n e) => Vector n e -> e
vectorLen = sqrt . vectorLenSquare
{-# INLINE vectorLen #-}
type VectorLen (n :: Nat) e =
( Floating e
, VectorLenSquare n e
)
normalize :: (Normalize n e) => Vector n e -> NormalizedVector n e
normalize v = NormalizedVector $ scale v (1 / vectorLen v)
{-# INLINE normalize #-}
type Normalize (n :: Nat) e =
( VectorLen n e
, Scale '[n] e
)
norm :: (Normalize n e) => Vector n e -> Vector n e
norm = unNormalizedVector . normalize
{-# INLINE norm #-}
dot :: (Dot n e) => Vector n e -> Vector n e -> e
dot v1 v2 = osum $ ozipWith (*) v1 v2
{-# INLINE dot #-}
type Dot (n :: Nat) e =
( Num e
, IsVector n e
, MonoFunctorCtx '[n] e
, MonoFoldableCtx '[n] e
, MonoZipCtx '[n] e
)
cross :: (Num e, IsVector 3 e) => Vector 3 e -> Vector 3 e -> Vector 3 e
cross v0 v1 =
withTensor v0 $ \x0 y0 z0 ->
withTensor v1 $ \x1 y1 z1 ->
vector @3 (y0 * z1 - z0 * y1) (z0 * x1 - x0 * z1) (x0 * y1 - y0 * x1)
{-# INLINE cross #-}
toHomogenous :: (Num e, IsVector 3 e, IsVector 4 e) => Vector 3 e -> Vector 4 e
toHomogenous v = withTensor v $ \x y z -> vector @4 x y z 1
{-# INLINE toHomogenous #-}
fromHomogenous :: (Fractional e, IsVector 3 e, IsVector 4 e) => Vector 4 e -> Vector 3 e
fromHomogenous v = withTensor v $ \x y z w -> scale (vector @3 x y z) (1 / w)
{-# INLINE fromHomogenous #-}
genVectorInstance :: Int
-> Name
-> Q [Dec]
genVectorInstance size elemTypeName = genTensorInstance (N.fromList [size]) elemTypeName