{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Data.Array.Accelerate.Linear.Vector
where
import Data.Array.Accelerate as A hiding ( pattern V2 )
import Data.Array.Accelerate.Linear.Type
import Control.Lens
import Prelude as P
import qualified Linear.Vector as L
infixl 6 ^+^, ^+, +^, ^-^, ^-, -^
infixl 7 ^*, *^, ^/, /^
class L.Additive f => Additive f where
zero :: (Elt (f a), P.Num a) => Exp (f a)
zero = constant (L.zero)
(^+^) :: forall a. (A.Num a, Box f a)
=> Exp (f a)
-> Exp (f a)
-> Exp (f a)
(^+^) = lift2 ((L.^+^) :: f (Exp a) -> f (Exp a) -> f (Exp a))
(^-^) :: forall a. (A.Num a, Box f a)
=> Exp (f a)
-> Exp (f a)
-> Exp (f a)
(^-^) = lift2 ((L.^-^) :: f (Exp a) -> f (Exp a) -> f (Exp a))
lerp :: forall a. (A.Num a, Box f a)
=> Exp a
-> Exp (f a)
-> Exp (f a)
-> Exp (f a)
lerp = lift3 (L.lerp :: Exp a -> f (Exp a) -> f (Exp a) -> f (Exp a))
newtype E t = E {
el :: forall a. (Elt a, Box t a) => Lens' (Exp (t a)) (Exp a)
}
negated
:: forall f a. (Functor f, A.Num a, Box f a)
=> Exp (f a)
-> Exp (f a)
negated = lift1 (L.negated :: f (Exp a) -> f (Exp a))
(*^) :: forall f a. (Functor f, A.Num a, Box f a)
=> Exp a
-> Exp (f a)
-> Exp (f a)
(*^) = lift2 ((L.*^) :: Exp a -> f (Exp a) -> f (Exp a))
(^*) :: forall f a. (Functor f, A.Num a, Box f a)
=> Exp (f a)
-> Exp a
-> Exp (f a)
(^*) = lift2 ((L.^*) :: f (Exp a) -> Exp a -> f (Exp a))
(^/) :: forall f a. (Functor f, A.Fractional a, Box f a)
=> Exp (f a)
-> Exp a
-> Exp (f a)
(^/) = lift2 ((L.^/) :: f (Exp a) -> Exp a -> f (Exp a))
(/^) :: forall f a. (Functor f, A.Fractional a, Box f a)
=> Exp a
-> Exp (f a)
-> Exp (f a)
(/^) = lift2 ((\a f -> fmap (a/) f) :: Exp a -> f (Exp a) -> f (Exp a))
(+^) :: forall f a. (Functor f, A.Num a, Box f a)
=> Exp a
-> Exp (f a)
-> Exp (f a)
(+^) = lift2 ((\a f -> fmap (a+) f) :: Exp a -> f (Exp a) -> f (Exp a))
(^+) :: forall f a. (Functor f, A.Num a, Box f a)
=> Exp (f a)
-> Exp a
-> Exp (f a)
(^+) = lift2 ((\f a -> fmap (+a) f) :: f (Exp a) -> Exp a -> f (Exp a))
(-^) :: forall f a. (Functor f, A.Num a, Box f a)
=> Exp a
-> Exp (f a)
-> Exp (f a)
(-^) = lift2 ((\a f -> fmap (a-) f) :: Exp a -> f (Exp a) -> f (Exp a))
(^-) :: forall f a. (Functor f, A.Num a, Box f a)
=> Exp (f a)
-> Exp a
-> Exp (f a)
(^-) = lift2 ((\f a -> fmap (A.subtract a) f) :: f (Exp a) -> Exp a -> f (Exp a))