#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 702
#endif
#ifndef MIN_VERSION_hashable
#define MIN_VERSION_hashable(x,y,z) 1
#endif
module Linear.V1
( V1(..)
, R1(..)
, ex
) where
import Control.Applicative
import Control.DeepSeq (NFData)
import Control.Monad (liftM)
import Control.Monad.Fix
import Control.Monad.Zip
import Control.Lens
import Data.Data
import Data.Distributive
import Data.Foldable
import Data.Functor.Bind
import Data.Functor.Rep
import Data.Hashable
import Data.Semigroup.Foldable
import Foreign.Storable (Storable)
import GHC.Arr (Ix(..))
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 702
import GHC.Generics (Generic)
#endif
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 706
import GHC.Generics (Generic1)
#endif
import Linear.Metric
import Linear.Epsilon
import Linear.Vector
import Prelude hiding (sum)
import qualified Data.Vector.Generic.Mutable as M
import qualified Data.Vector.Generic as G
import qualified Data.Vector.Unboxed.Base as U
#ifdef HLINT
#endif
newtype V1 a = V1 a
deriving (Eq,Ord,Show,Read,Data,Typeable,
Functor,Foldable,Traversable,
Epsilon,Storable,NFData
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 702
,Generic
#endif
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 706
,Generic1
#endif
)
instance Foldable1 V1 where
foldMap1 f (V1 a) = f a
instance Traversable1 V1 where
traverse1 f (V1 a) = V1 <$> f a
instance Apply V1 where
V1 f <.> V1 x = V1 (f x)
instance Applicative V1 where
pure = V1
V1 f <*> V1 x = V1 (f x)
instance Additive V1 where
zero = pure 0
liftU2 = liftA2
liftI2 = liftA2
instance Bind V1 where
V1 a >>- f = f a
instance Monad V1 where
return = V1
V1 a >>= f = f a
instance Num a => Num (V1 a) where
(+) = liftA2 (+)
() = liftA2 ()
(*) = liftA2 (*)
negate = fmap negate
abs = fmap abs
signum = fmap signum
fromInteger = pure . fromInteger
instance Fractional a => Fractional (V1 a) where
recip = fmap recip
(/) = liftA2 (/)
fromRational = pure . fromRational
instance Hashable a => Hashable (V1 a) where
#if (MIN_VERSION_hashable(1,2,1)) || !(MIN_VERSION_hashable(1,2,0))
hash (V1 a) = hash a
#endif
hashWithSalt s (V1 a) = s `hashWithSalt` a
instance Metric V1 where
dot (V1 a) (V1 b) = a * b
class R1 t where
_x :: Lens' (t a) a
ex :: R1 t => E t
ex = E _x
instance R1 V1 where
_x f (V1 a) = V1 <$> f a
instance R1 Identity where
_x f (Identity a) = Identity <$> f a
instance Distributive V1 where
distribute f = V1 (fmap (\(V1 x) -> x) f)
instance Ix a => Ix (V1 a) where
range (V1 l1, V1 u1) =
[ V1 i1 | i1 <- range (l1,u1) ]
unsafeIndex (V1 l1,V1 u1) (V1 i1) = unsafeIndex (l1,u1) i1
inRange (V1 l1,V1 u1) (V1 i1) = inRange (l1,u1) i1
instance Representable V1 where
type Rep V1 = E V1
tabulate f = V1 (f ex)
index xs (E l) = view l xs
instance FunctorWithIndex (E V1) V1 where
imap f (V1 a) = V1 (f ex a)
instance FoldableWithIndex (E V1) V1 where
ifoldMap f (V1 a) = f ex a
instance TraversableWithIndex (E V1) V1 where
itraverse f (V1 a) = V1 <$> f ex a
type instance Index (V1 a) = E V1
type instance IxValue (V1 a) = a
instance Ixed (V1 a) where
ix = el
instance Each (V1 a) (V1 b) a b where
each f (V1 x) = V1 <$> f x
newtype instance U.Vector (V1 a) = V_V1 (U.Vector a)
newtype instance U.MVector s (V1 a) = MV_V1 (U.MVector s a)
instance U.Unbox a => U.Unbox (V1 a)
instance U.Unbox a => M.MVector U.MVector (V1 a) where
basicLength (MV_V1 v) = M.basicLength v
basicUnsafeSlice m n (MV_V1 v) = MV_V1 (M.basicUnsafeSlice m n v)
basicOverlaps (MV_V1 v) (MV_V1 u) = M.basicOverlaps v u
basicUnsafeNew n = liftM MV_V1 (M.basicUnsafeNew n)
basicUnsafeRead (MV_V1 v) i = liftM V1 (M.basicUnsafeRead v i)
basicUnsafeWrite (MV_V1 v) i (V1 x) = M.basicUnsafeWrite v i x
instance U.Unbox a => G.Vector U.Vector (V1 a) where
basicUnsafeFreeze (MV_V1 v) = liftM V_V1 (G.basicUnsafeFreeze v)
basicUnsafeThaw (V_V1 v) = liftM MV_V1 (G.basicUnsafeThaw v)
basicLength (V_V1 v) = G.basicLength v
basicUnsafeSlice m n (V_V1 v) = V_V1 (G.basicUnsafeSlice m n v)
basicUnsafeIndexM (V_V1 v) i = liftM V1 (G.basicUnsafeIndexM v i)
instance MonadZip V1 where
mzip (V1 a) (V1 b) = V1 (a, b)
mzipWith f (V1 a) (V1 b) = V1 (f a b)
munzip (V1 (a,b)) = (V1 a, V1 b)
instance MonadFix V1 where
mfix f = V1 (let V1 a = f a in a)
instance Bounded a => Bounded (V1 a) where
minBound = pure minBound
maxBound = pure maxBound