Copyright | 2014 Edward Kmett Charles Durham [2015..2020] Trevor L. McDonell |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Trevor L. McDonell <trevor.mcdonell@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Data.Array.Accelerate.Linear.V2
Contents
Description
2-D Vectors
Synopsis
- data V2 a = V2 !a !a
- pattern V2_ :: Elt a => Exp a -> Exp a -> Exp (V2 a)
- class R1 t => R1 t where
- class (R2 t, R1 t) => R2 t where
- _yx :: forall t a. (R2 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V2 a))
- ex :: R1 t => E t
- ey :: R2 t => E t
- perp :: forall a. Num a => Exp (V2 a) -> Exp (V2 a)
- angle :: Floating a => Exp a -> Exp (V2 a)
Documentation
A 2-dimensional vector
>>>
pure 1 :: V2 Int
V2 1 1
>>>
V2 1 2 + V2 3 4
V2 4 6
>>>
V2 1 2 * V2 3 4
V2 3 8
>>>
sum (V2 1 2)
3
Constructors
V2 !a !a |
Instances
class R1 t => R1 t where Source #
A space that has at least 1 basis vector _x
.
Minimal complete definition
Nothing
Methods
_x :: (Elt a, Box t a) => Lens' (Exp (t a)) (Exp a) Source #
>>>
test $ (V1_ 2 :: Exp (V1 Int)) ^. _x
2
>>>
test $ (V1_ 2 :: Exp (V1 Int)) & _x .~ 3
V1 3
class (R2 t, R1 t) => R2 t where Source #
Minimal complete definition
Nothing
Methods
_y :: (Elt a, Box t a) => Lens' (Exp (t a)) (Exp a) Source #
>>>
test $ (V2_ 1 2 :: Exp (V2 Int)) ^. _y
2
>>>
test $ (V2_ 1 2 :: Exp (V2 Int)) & _y .~ 3
V2 1 3
_xy :: (Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V2 a)) Source #
_yx :: forall t a. (R2 t, Elt a, Box t a) => Lens' (Exp (t a)) (Exp (V2 a)) Source #
>>>
test $ (V2_ 1 2 :: Exp (V2 Int)) ^. _yx
V2 2 1
perp :: forall a. Num a => Exp (V2 a) -> Exp (V2 a) Source #
the counter-clockwise perpendicular vector
>>>
test $ perp $ (V2_ 10 20 :: Exp (V2 Int))
V2 (-20) 10
Orphan instances
Functor V2 Source # | |
Additive V2 Source # | |
Metric V2 Source # | |
Methods dot :: (Num a, Box V2 a) => Exp (V2 a) -> Exp (V2 a) -> Exp a Source # quadrance :: (Num a, Box V2 a) => Exp (V2 a) -> Exp a Source # qd :: (Num a, Box V2 a) => Exp (V2 a) -> Exp (V2 a) -> Exp a Source # distance :: (Floating a, Box V2 a) => Exp (V2 a) -> Exp (V2 a) -> Exp a Source # norm :: (Floating a, Box V2 a) => Exp (V2 a) -> Exp a Source # signorm :: (Floating a, Box V2 a) => Exp (V2 a) -> Exp (V2 a) Source # | |
R1 V2 Source # | |
(Lift Exp a, Elt (Plain a)) => Lift Exp (V2 a) Source # | |
Elt a => Unlift Exp (V2 (Exp a)) Source # | |
Bounded a => Bounded (Exp (V2 a)) Source # | |
Floating a => Floating (Exp (V2 a)) Source # | |
Methods exp :: Exp (V2 a) -> Exp (V2 a) # log :: Exp (V2 a) -> Exp (V2 a) # sqrt :: Exp (V2 a) -> Exp (V2 a) # (**) :: Exp (V2 a) -> Exp (V2 a) -> Exp (V2 a) # logBase :: Exp (V2 a) -> Exp (V2 a) -> Exp (V2 a) # sin :: Exp (V2 a) -> Exp (V2 a) # cos :: Exp (V2 a) -> Exp (V2 a) # tan :: Exp (V2 a) -> Exp (V2 a) # asin :: Exp (V2 a) -> Exp (V2 a) # acos :: Exp (V2 a) -> Exp (V2 a) # atan :: Exp (V2 a) -> Exp (V2 a) # sinh :: Exp (V2 a) -> Exp (V2 a) # cosh :: Exp (V2 a) -> Exp (V2 a) # tanh :: Exp (V2 a) -> Exp (V2 a) # asinh :: Exp (V2 a) -> Exp (V2 a) # acosh :: Exp (V2 a) -> Exp (V2 a) # atanh :: Exp (V2 a) -> Exp (V2 a) # log1p :: Exp (V2 a) -> Exp (V2 a) # expm1 :: Exp (V2 a) -> Exp (V2 a) # | |
Floating a => Fractional (Exp (V2 a)) Source # | |
Num a => Num (Exp (V2 a)) Source # | |
Ord a => Ord (V2 a) Source # | |
Eq a => Eq (V2 a) Source # | |
Elt a => Elt (V2 a) Source # | |
Epsilon a => Epsilon (V2 a) Source # | |
(Elt a, Elt b) => Each (Exp (V2 a)) (Exp (V2 b)) (Exp a) (Exp b) Source # | |