hgeometry-combinatorial
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageGHC2021

HGeometry.Cyclic

Description

Representing Cyclic Sequences

Synopsis

Documentation

newtype Cyclic (v :: k -> Type) (a :: k) Source #

A cyclic sequence type

Constructors

Cyclic (v a) 

Instances

Instances details
FoldableWithIndex i v => FoldableWithIndex i (Cyclic v) Source # 
Instance details

Defined in HGeometry.Cyclic

Methods

ifoldMap :: Monoid m => (i -> a -> m) -> Cyclic v a -> m Source #

ifoldMap' :: Monoid m => (i -> a -> m) -> Cyclic v a -> m Source #

ifoldr :: (i -> a -> b -> b) -> b -> Cyclic v a -> b Source #

ifoldl :: (i -> b -> a -> b) -> b -> Cyclic v a -> b Source #

ifoldr' :: (i -> a -> b -> b) -> b -> Cyclic v a -> b Source #

ifoldl' :: (i -> b -> a -> b) -> b -> Cyclic v a -> b Source #

FunctorWithIndex i v => FunctorWithIndex i (Cyclic v) Source # 
Instance details

Defined in HGeometry.Cyclic

Methods

imap :: (i -> a -> b) -> Cyclic v a -> Cyclic v b Source #

TraversableWithIndex i v => TraversableWithIndex i (Cyclic v) Source # 
Instance details

Defined in HGeometry.Cyclic

Methods

itraverse :: Applicative f => (i -> a -> f b) -> Cyclic v a -> f (Cyclic v b) Source #

Foldable1 v => Foldable1 (Cyclic v) Source # 
Instance details

Defined in HGeometry.Cyclic

Methods

fold1 :: Semigroup m => Cyclic v m -> m #

foldMap1 :: Semigroup m => (a -> m) -> Cyclic v a -> m #

foldMap1' :: Semigroup m => (a -> m) -> Cyclic v a -> m #

toNonEmpty :: Cyclic v a -> NonEmpty a #

maximum :: Ord a => Cyclic v a -> a #

minimum :: Ord a => Cyclic v a -> a #

head :: Cyclic v a -> a #

last :: Cyclic v a -> a #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> Cyclic v a -> b #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> Cyclic v a -> b #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> Cyclic v a -> b #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> Cyclic v a -> b #

Functor v => Functor (Cyclic v) Source # 
Instance details

Defined in HGeometry.Cyclic

Methods

fmap :: (a -> b) -> Cyclic v a -> Cyclic v b #

(<$) :: a -> Cyclic v b -> Cyclic v a #

Foldable v => Foldable (Cyclic v) Source # 
Instance details

Defined in HGeometry.Cyclic

Methods

fold :: Monoid m => Cyclic v m -> m #

foldMap :: Monoid m => (a -> m) -> Cyclic v a -> m #

foldMap' :: Monoid m => (a -> m) -> Cyclic v a -> m #

foldr :: (a -> b -> b) -> b -> Cyclic v a -> b #

foldr' :: (a -> b -> b) -> b -> Cyclic v a -> b #

foldl :: (b -> a -> b) -> b -> Cyclic v a -> b #

foldl' :: (b -> a -> b) -> b -> Cyclic v a -> b #

foldr1 :: (a -> a -> a) -> Cyclic v a -> a #

foldl1 :: (a -> a -> a) -> Cyclic v a -> a #

toList :: Cyclic v a -> [a] #

null :: Cyclic v a -> Bool #

length :: Cyclic v a -> Int #

elem :: Eq a => a -> Cyclic v a -> Bool #

maximum :: Ord a => Cyclic v a -> a #

minimum :: Ord a => Cyclic v a -> a #

sum :: Num a => Cyclic v a -> a #

product :: Num a => Cyclic v a -> a #

Traversable v => Traversable (Cyclic v) Source # 
Instance details

Defined in HGeometry.Cyclic

Methods

traverse :: Applicative f => (a -> f b) -> Cyclic v a -> f (Cyclic v b) #

sequenceA :: Applicative f => Cyclic v (f a) -> f (Cyclic v a) #

mapM :: Monad m => (a -> m b) -> Cyclic v a -> m (Cyclic v b) #

sequence :: Monad m => Cyclic v (m a) -> m (Cyclic v a) #

HasDirectedTraversals v => HasDirectedTraversals (Cyclic v) Source # 
Instance details

Defined in HGeometry.Cyclic

HasFromFoldable v => HasFromFoldable (Cyclic v) Source # 
Instance details

Defined in HGeometry.Cyclic

Methods

fromFoldable :: Foldable g => g a -> Cyclic v a Source #

fromList :: [a] -> Cyclic v a Source #

HasFromFoldable1 v => HasFromFoldable1 (Cyclic v) Source # 
Instance details

Defined in HGeometry.Cyclic

Methods

fromFoldable1 :: Foldable1 g => g a -> Cyclic v a Source #

fromNonEmpty :: NonEmpty a -> Cyclic v a Source #

Traversable1 v => Traversable1 (Cyclic v) Source # 
Instance details

Defined in HGeometry.Cyclic

Methods

traverse1 :: Apply f => (a -> f b) -> Cyclic v a -> f (Cyclic v b) Source #

sequence1 :: Apply f => Cyclic v (f b) -> f (Cyclic v b) Source #

FromJSON (v a) => FromJSON (Cyclic v a) Source # 
Instance details

Defined in HGeometry.Cyclic

ToJSON (v a) => ToJSON (Cyclic v a) Source # 
Instance details

Defined in HGeometry.Cyclic

NFData (v a) => NFData (Cyclic v a) Source # 
Instance details

Defined in HGeometry.Cyclic

Methods

rnf :: Cyclic v a -> () #

Generic (Cyclic v a) Source # 
Instance details

Defined in HGeometry.Cyclic

Associated Types

type Rep (Cyclic v a) 
Instance details

Defined in HGeometry.Cyclic

type Rep (Cyclic v a) = D1 ('MetaData "Cyclic" "HGeometry.Cyclic" "hgeometry-combinatorial-1.0.0.0-inplace" 'True) (C1 ('MetaCons "Cyclic" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (v a))))

Methods

from :: Cyclic v a -> Rep (Cyclic v a) x #

to :: Rep (Cyclic v a) x -> Cyclic v a #

Show (v a) => Show (Cyclic v a) Source # 
Instance details

Defined in HGeometry.Cyclic

Methods

showsPrec :: Int -> Cyclic v a -> ShowS #

show :: Cyclic v a -> String #

showList :: [Cyclic v a] -> ShowS #

Eq (v a) => Eq (Cyclic v a) Source # 
Instance details

Defined in HGeometry.Cyclic

Methods

(==) :: Cyclic v a -> Cyclic v a -> Bool #

(/=) :: Cyclic v a -> Cyclic v a -> Bool #

Foldable1 v => ShiftedEq (Cyclic v a) Source # 
Instance details

Defined in HGeometry.Cyclic

Associated Types

type ElemCyclic (Cyclic v a) 
Instance details

Defined in HGeometry.Cyclic

type ElemCyclic (Cyclic v a) = a

Methods

isShiftOf :: Cyclic v a -> Cyclic v a -> Bool Source #

(Index (v a) ~ Int, Foldable v, Ixed (v a)) => Ixed (Cyclic v a) Source # 
Instance details

Defined in HGeometry.Cyclic

Methods

ix :: Index (Cyclic v a) -> Traversal' (Cyclic v a) (IxValue (Cyclic v a)) Source #

Reversing (v a) => Reversing (Cyclic v a) Source # 
Instance details

Defined in HGeometry.Cyclic

Methods

reversing :: Cyclic v a -> Cyclic v a Source #

type Rep (Cyclic v a) Source # 
Instance details

Defined in HGeometry.Cyclic

type Rep (Cyclic v a) = D1 ('MetaData "Cyclic" "HGeometry.Cyclic" "hgeometry-combinatorial-1.0.0.0-inplace" 'True) (C1 ('MetaCons "Cyclic" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (v a))))
type ElemCyclic (Cyclic v a) Source # 
Instance details

Defined in HGeometry.Cyclic

type ElemCyclic (Cyclic v a) = a
type Index (Cyclic v a) Source # 
Instance details

Defined in HGeometry.Cyclic

type Index (Cyclic v a) = Index (v a)
type IxValue (Cyclic v a) Source # 
Instance details

Defined in HGeometry.Cyclic

type IxValue (Cyclic v a) = IxValue (v a)

class HasDirectedTraversals (v :: Type -> Type) where Source #

Class that models that some type has a cyclic traversal starting from a particular index.

Methods

traverseRightFrom :: Index (v a) -> IndexedTraversal1' (Index (v a)) (v a) a Source #

A rightward-traversal over all elements starting from the given one. Indices are taken modulo the length.

running time : \(O(n)\)

traverseLeftFrom :: Index (v a) -> IndexedTraversal1' (Index (v a)) (v a) a Source #

A rightward-traversal over all elements starting from the given one. Indices are taken modulo the length.

running time : \(O(n)\)

class ShiftedEq t where Source #

Class for types that have an Equality test up to cyclic shifts

Associated Types

type ElemCyclic t Source #

The type of the elements stored in this cyclic container.

Methods

isShiftOf :: t -> t -> Bool Source #

Given a and b, test if a is a shifted version of the other.

Instances

Instances details
Foldable1 v => ShiftedEq (Cyclic v a) Source # 
Instance details

Defined in HGeometry.Cyclic

Associated Types

type ElemCyclic (Cyclic v a) 
Instance details

Defined in HGeometry.Cyclic

type ElemCyclic (Cyclic v a) = a

Methods

isShiftOf :: Cyclic v a -> Cyclic v a -> Bool Source #

groupWith :: (Foldable1 cyclic, Eq b) => (a -> b) -> cyclic a -> Cyclic NonEmpty (b, NonEmpty a) Source #

Groups the elements of a cyclic. Note in particular that this may join the first and last group, thereby changing the indices of the individual elements.

the items are reported in the same order as before.

withCyclicSuccessor :: forall (cyclic :: Type -> Type) a b. Traversable1 cyclic => Traversal1 (cyclic a) (cyclic b) (a, a) b Source #

A traversal that associates every elemnt with its successor

withCyclicPredecessor :: forall (cyclic :: Type -> Type) a b. Traversable1 cyclic => Traversal1 (cyclic a) (cyclic b) (a, a) b Source #

A traversal that associates every elemnt with its predecessor

withCyclicNeighbours :: forall (cyclic :: Type -> Type) a b. Traversable1 cyclic => Traversal1 (cyclic a) (cyclic b) (a, V2 a) b Source #

Traverse a cyclic structure together with both its neighbors

iWithCyclicSuccessor :: forall (cyclic :: Type -> Type) i a b. (Traversable1 cyclic, TraversableWithIndex i cyclic) => IndexedTraversal1 (i, i) (cyclic a) (cyclic b) (a, a) b Source #

An indexed version of withCyclicSuccessor

iWithCyclicPredecessor :: forall (cyclic :: Type -> Type) i a b. (Traversable1 cyclic, TraversableWithIndex i cyclic) => IndexedTraversal1 (i, i) (cyclic a) (cyclic b) (a, a) b Source #

An indexed traversal that associates every elemnt with its predecessor

iWithCyclicNeighbours :: forall (cyclic :: Type -> Type) i a b. (Traversable1 cyclic, TraversableWithIndex i cyclic) => IndexedTraversal1 (i, V2 i) (cyclic a) (cyclic b) (a, V2 a) b Source #

An indexed traversal that associates every elemnt with its neighbours

data V2 a Source #

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

Instances details
Representable V2 
Instance details

Defined in Linear.V2

Associated Types

type Rep V2 
Instance details

Defined in Linear.V2

type Rep V2 = E V2

Methods

tabulate :: (Rep V2 -> a) -> V2 a Source #

index :: V2 a -> Rep V2 -> a Source #

MonadZip V2 
Instance details

Defined in Linear.V2

Methods

mzip :: V2 a -> V2 b -> V2 (a, b) #

mzipWith :: (a -> b -> c) -> V2 a -> V2 b -> V2 c #

munzip :: V2 (a, b) -> (V2 a, V2 b) #

Foldable1 V2 
Instance details

Defined in Linear.V2

Methods

fold1 :: Semigroup m => V2 m -> m #

foldMap1 :: Semigroup m => (a -> m) -> V2 a -> m #

foldMap1' :: Semigroup m => (a -> m) -> V2 a -> m #

toNonEmpty :: V2 a -> NonEmpty a #

maximum :: Ord a => V2 a -> a #

minimum :: Ord a => V2 a -> a #

head :: V2 a -> a #

last :: V2 a -> a #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> V2 a -> b #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> V2 a -> b #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> V2 a -> b #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> V2 a -> b #

Eq1 V2 
Instance details

Defined in Linear.V2

Methods

liftEq :: (a -> b -> Bool) -> V2 a -> V2 b -> Bool #

Ord1 V2 
Instance details

Defined in Linear.V2

Methods

liftCompare :: (a -> b -> Ordering) -> V2 a -> V2 b -> Ordering #

Read1 V2 
Instance details

Defined in Linear.V2

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V2 a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [V2 a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (V2 a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [V2 a] #

Show1 V2 
Instance details

Defined in Linear.V2

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V2 a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [V2 a] -> ShowS #

Serial1 V2 
Instance details

Defined in Linear.V2

Methods

serializeWith :: MonadPut m => (a -> m ()) -> V2 a -> m () Source #

deserializeWith :: MonadGet m => m a -> m (V2 a) Source #

Distributive V2 
Instance details

Defined in Linear.V2

Methods

distribute :: Functor f => f (V2 a) -> V2 (f a) Source #

collect :: Functor f => (a -> V2 b) -> f a -> V2 (f b) Source #

distributeM :: Monad m => m (V2 a) -> V2 (m a) Source #

collectM :: Monad m => (a -> V2 b) -> m a -> V2 (m b) Source #

Applicative V2 
Instance details

Defined in Linear.V2

Methods

pure :: a -> V2 a #

(<*>) :: V2 (a -> b) -> V2 a -> V2 b #

liftA2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c #

(*>) :: V2 a -> V2 b -> V2 b #

(<*) :: V2 a -> V2 b -> V2 a #

Functor V2 
Instance details

Defined in Linear.V2

Methods

fmap :: (a -> b) -> V2 a -> V2 b #

(<$) :: a -> V2 b -> V2 a #

Monad V2 
Instance details

Defined in Linear.V2

Methods

(>>=) :: V2 a -> (a -> V2 b) -> V2 b #

(>>) :: V2 a -> V2 b -> V2 b #

return :: a -> V2 a #

MonadFix V2 
Instance details

Defined in Linear.V2

Methods

mfix :: (a -> V2 a) -> V2 a #

Foldable V2 
Instance details

Defined in Linear.V2

Methods

fold :: Monoid m => V2 m -> m #

foldMap :: Monoid m => (a -> m) -> V2 a -> m #

foldMap' :: Monoid m => (a -> m) -> V2 a -> m #

foldr :: (a -> b -> b) -> b -> V2 a -> b #

foldr' :: (a -> b -> b) -> b -> V2 a -> b #

foldl :: (b -> a -> b) -> b -> V2 a -> b #

foldl' :: (b -> a -> b) -> b -> V2 a -> b #

foldr1 :: (a -> a -> a) -> V2 a -> a #

foldl1 :: (a -> a -> a) -> V2 a -> a #

toList :: V2 a -> [a] #

null :: V2 a -> Bool #

length :: V2 a -> Int #

elem :: Eq a => a -> V2 a -> Bool #

maximum :: Ord a => V2 a -> a #

minimum :: Ord a => V2 a -> a #

sum :: Num a => V2 a -> a #

product :: Num a => V2 a -> a #

Traversable V2 
Instance details

Defined in Linear.V2

Methods

traverse :: Applicative f => (a -> f b) -> V2 a -> f (V2 b) #

sequenceA :: Applicative f => V2 (f a) -> f (V2 a) #

mapM :: Monad m => (a -> m b) -> V2 a -> m (V2 b) #

sequence :: Monad m => V2 (m a) -> m (V2 a) #

Hashable1 V2 
Instance details

Defined in Linear.V2

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> V2 a -> Int Source #

Affine V2 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V2 
Instance details

Defined in Linear.Affine

type Diff V2 = V2

Methods

(.-.) :: Num a => V2 a -> V2 a -> Diff V2 a Source #

(.+^) :: Num a => V2 a -> Diff V2 a -> V2 a Source #

(.-^) :: Num a => V2 a -> Diff V2 a -> V2 a Source #

Metric V2 
Instance details

Defined in Linear.V2

Methods

dot :: Num a => V2 a -> V2 a -> a Source #

quadrance :: Num a => V2 a -> a Source #

qd :: Num a => V2 a -> V2 a -> a Source #

distance :: Floating a => V2 a -> V2 a -> a Source #

norm :: Floating a => V2 a -> a Source #

signorm :: Floating a => V2 a -> V2 a Source #

Trace V2 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => V2 (V2 a) -> a Source #

diagonal :: V2 (V2 a) -> V2 a Source #

Finite V2 
Instance details

Defined in Linear.V2

Associated Types

type Size V2 
Instance details

Defined in Linear.V2

type Size V2 = 2

Methods

toV :: V2 a -> V (Size V2) a Source #

fromV :: V (Size V2) a -> V2 a Source #

R1 V2 
Instance details

Defined in Linear.V2

Methods

_x :: Lens' (V2 a) a Source #

R2 V2 
Instance details

Defined in Linear.V2

Methods

_y :: Lens' (V2 a) a Source #

_xy :: Lens' (V2 a) (V2 a) Source #

Additive V2 
Instance details

Defined in Linear.V2

Methods

zero :: Num a => V2 a Source #

(^+^) :: Num a => V2 a -> V2 a -> V2 a Source #

(^-^) :: Num a => V2 a -> V2 a -> V2 a Source #

lerp :: Num a => a -> V2 a -> V2 a -> V2 a Source #

liftU2 :: (a -> a -> a) -> V2 a -> V2 a -> V2 a Source #

liftI2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c Source #

Apply V2 
Instance details

Defined in Linear.V2

Methods

(<.>) :: V2 (a -> b) -> V2 a -> V2 b Source #

(.>) :: V2 a -> V2 b -> V2 b Source #

(<.) :: V2 a -> V2 b -> V2 a Source #

liftF2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c Source #

Bind V2 
Instance details

Defined in Linear.V2

Methods

(>>-) :: V2 a -> (a -> V2 b) -> V2 b Source #

join :: V2 (V2 a) -> V2 a Source #

Traversable1 V2 
Instance details

Defined in Linear.V2

Methods

traverse1 :: Apply f => (a -> f b) -> V2 a -> f (V2 b) Source #

sequence1 :: Apply f => V2 (f b) -> f (V2 b) Source #

Generic1 V2 
Instance details

Defined in Linear.V2

Associated Types

type Rep1 V2 
Instance details

Defined in Linear.V2

type Rep1 V2 = D1 ('MetaData "V2" "Linear.V2" "linear-1.23.1-4d1e410d44f205bb3e41019c738988ce2ab4eb665f04e18eaa3a1d1856e2566c" 'False) (C1 ('MetaCons "V2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1))

Methods

from1 :: V2 a -> Rep1 V2 a #

to1 :: Rep1 V2 a -> V2 a #

Num r => Coalgebra r (E V2) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V2 -> r) -> E V2 -> E V2 -> r Source #

counital :: (E V2 -> r) -> r Source #

Lift a => Lift (V2 a :: Type) 
Instance details

Defined in Linear.V2

Methods

lift :: Quote m => V2 a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => V2 a -> Code m (V2 a) #

Unbox a => Vector Vector (V2 a) 
Instance details

Defined in Linear.V2

Methods

basicUnsafeFreeze :: Mutable Vector s (V2 a) -> ST s (Vector (V2 a)) Source #

basicUnsafeThaw :: Vector (V2 a) -> ST s (Mutable Vector s (V2 a)) Source #

basicLength :: Vector (V2 a) -> Int Source #

basicUnsafeSlice :: Int -> Int -> Vector (V2 a) -> Vector (V2 a) Source #

basicUnsafeIndexM :: Vector (V2 a) -> Int -> Box (V2 a) Source #

basicUnsafeCopy :: Mutable Vector s (V2 a) -> Vector (V2 a) -> ST s () Source #

elemseq :: Vector (V2 a) -> V2 a -> b -> b Source #

Unbox a => MVector MVector (V2 a) 
Instance details

Defined in Linear.V2

Methods

basicLength :: MVector s (V2 a) -> Int Source #

basicUnsafeSlice :: Int -> Int -> MVector s (V2 a) -> MVector s (V2 a) Source #

basicOverlaps :: MVector s (V2 a) -> MVector s (V2 a) -> Bool Source #

basicUnsafeNew :: Int -> ST s (MVector s (V2 a)) Source #

basicInitialize :: MVector s (V2 a) -> ST s () Source #

basicUnsafeReplicate :: Int -> V2 a -> ST s (MVector s (V2 a)) Source #

basicUnsafeRead :: MVector s (V2 a) -> Int -> ST s (V2 a) Source #

basicUnsafeWrite :: MVector s (V2 a) -> Int -> V2 a -> ST s () Source #

basicClear :: MVector s (V2 a) -> ST s () Source #

basicSet :: MVector s (V2 a) -> V2 a -> ST s () Source #

basicUnsafeCopy :: MVector s (V2 a) -> MVector s (V2 a) -> ST s () Source #

basicUnsafeMove :: MVector s (V2 a) -> MVector s (V2 a) -> ST s () Source #

basicUnsafeGrow :: MVector s (V2 a) -> Int -> ST s (MVector s (V2 a)) Source #

Binary a => Binary (V2 a) 
Instance details

Defined in Linear.V2

Methods

put :: V2 a -> Put #

get :: Get (V2 a) #

putList :: [V2 a] -> Put #

Serial a => Serial (V2 a) 
Instance details

Defined in Linear.V2

Methods

serialize :: MonadPut m => V2 a -> m () Source #

deserialize :: MonadGet m => m (V2 a) Source #

Serialize a => Serialize (V2 a) 
Instance details

Defined in Linear.V2

Methods

put :: Putter (V2 a) Source #

get :: Get (V2 a) Source #

NFData a => NFData (V2 a) 
Instance details

Defined in Linear.V2

Methods

rnf :: V2 a -> () #

Monoid a => Monoid (V2 a) 
Instance details

Defined in Linear.V2

Methods

mempty :: V2 a #

mappend :: V2 a -> V2 a -> V2 a #

mconcat :: [V2 a] -> V2 a #

Semigroup a => Semigroup (V2 a) 
Instance details

Defined in Linear.V2

Methods

(<>) :: V2 a -> V2 a -> V2 a #

sconcat :: NonEmpty (V2 a) -> V2 a #

stimes :: Integral b => b -> V2 a -> V2 a #

Data a => Data (V2 a) 
Instance details

Defined in Linear.V2

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V2 a -> c (V2 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V2 a) #

toConstr :: V2 a -> Constr #

dataTypeOf :: V2 a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V2 a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V2 a)) #

gmapT :: (forall b. Data b => b -> b) -> V2 a -> V2 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V2 a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V2 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> V2 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> V2 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> V2 a -> m (V2 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V2 a -> m (V2 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V2 a -> m (V2 a) #

Bounded a => Bounded (V2 a) 
Instance details

Defined in Linear.V2

Methods

minBound :: V2 a #

maxBound :: V2 a #

Floating a => Floating (V2 a) 
Instance details

Defined in Linear.V2

Methods

pi :: V2 a #

exp :: V2 a -> V2 a #

log :: V2 a -> V2 a #

sqrt :: V2 a -> V2 a #

(**) :: V2 a -> V2 a -> V2 a #

logBase :: V2 a -> V2 a -> V2 a #

sin :: V2 a -> V2 a #

cos :: V2 a -> V2 a #

tan :: V2 a -> V2 a #

asin :: V2 a -> V2 a #

acos :: V2 a -> V2 a #

atan :: V2 a -> V2 a #

sinh :: V2 a -> V2 a #

cosh :: V2 a -> V2 a #

tanh :: V2 a -> V2 a #

asinh :: V2 a -> V2 a #

acosh :: V2 a -> V2 a #

atanh :: V2 a -> V2 a #

log1p :: V2 a -> V2 a #

expm1 :: V2 a -> V2 a #

log1pexp :: V2 a -> V2 a #

log1mexp :: V2 a -> V2 a #

Storable a => Storable (V2 a) 
Instance details

Defined in Linear.V2

Methods

sizeOf :: V2 a -> Int #

alignment :: V2 a -> Int #

peekElemOff :: Ptr (V2 a) -> Int -> IO (V2 a) #

pokeElemOff :: Ptr (V2 a) -> Int -> V2 a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (V2 a) #

pokeByteOff :: Ptr b -> Int -> V2 a -> IO () #

peek :: Ptr (V2 a) -> IO (V2 a) #

poke :: Ptr (V2 a) -> V2 a -> IO () #

Generic (V2 a) 
Instance details

Defined in Linear.V2

Associated Types

type Rep (V2 a) 
Instance details

Defined in Linear.V2

type Rep (V2 a) = D1 ('MetaData "V2" "Linear.V2" "linear-1.23.1-4d1e410d44f205bb3e41019c738988ce2ab4eb665f04e18eaa3a1d1856e2566c" 'False) (C1 ('MetaCons "V2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))

Methods

from :: V2 a -> Rep (V2 a) x #

to :: Rep (V2 a) x -> V2 a #

Ix a => Ix (V2 a) 
Instance details

Defined in Linear.V2

Methods

range :: (V2 a, V2 a) -> [V2 a] #

index :: (V2 a, V2 a) -> V2 a -> Int #

unsafeIndex :: (V2 a, V2 a) -> V2 a -> Int #

inRange :: (V2 a, V2 a) -> V2 a -> Bool #

rangeSize :: (V2 a, V2 a) -> Int #

unsafeRangeSize :: (V2 a, V2 a) -> Int #

Num a => Num (V2 a) 
Instance details

Defined in Linear.V2

Methods

(+) :: V2 a -> V2 a -> V2 a #

(-) :: V2 a -> V2 a -> V2 a #

(*) :: V2 a -> V2 a -> V2 a #

negate :: V2 a -> V2 a #

abs :: V2 a -> V2 a #

signum :: V2 a -> V2 a #

fromInteger :: Integer -> V2 a #

Read a => Read (V2 a) 
Instance details

Defined in Linear.V2

Fractional a => Fractional (V2 a) 
Instance details

Defined in Linear.V2

Methods

(/) :: V2 a -> V2 a -> V2 a #

recip :: V2 a -> V2 a #

fromRational :: Rational -> V2 a #

Show a => Show (V2 a) 
Instance details

Defined in Linear.V2

Methods

showsPrec :: Int -> V2 a -> ShowS #

show :: V2 a -> String #

showList :: [V2 a] -> ShowS #

Eq a => Eq (V2 a) 
Instance details

Defined in Linear.V2

Methods

(==) :: V2 a -> V2 a -> Bool #

(/=) :: V2 a -> V2 a -> Bool #

Ord a => Ord (V2 a) 
Instance details

Defined in Linear.V2

Methods

compare :: V2 a -> V2 a -> Ordering #

(<) :: V2 a -> V2 a -> Bool #

(<=) :: V2 a -> V2 a -> Bool #

(>) :: V2 a -> V2 a -> Bool #

(>=) :: V2 a -> V2 a -> Bool #

max :: V2 a -> V2 a -> V2 a #

min :: V2 a -> V2 a -> V2 a #

Hashable a => Hashable (V2 a) 
Instance details

Defined in Linear.V2

Methods

hashWithSalt :: Int -> V2 a -> Int Source #

hash :: V2 a -> Int Source #

Ixed (V2 a) 
Instance details

Defined in Linear.V2

Methods

ix :: Index (V2 a) -> Traversal' (V2 a) (IxValue (V2 a)) Source #

Epsilon a => Epsilon (V2 a) 
Instance details

Defined in Linear.V2

Methods

nearZero :: V2 a -> Bool Source #

Random a => Random (V2 a) 
Instance details

Defined in Linear.V2

Methods

randomR :: RandomGen g => (V2 a, V2 a) -> g -> (V2 a, g) Source #

random :: RandomGen g => g -> (V2 a, g) Source #

randomRs :: RandomGen g => (V2 a, V2 a) -> g -> [V2 a] Source #

randoms :: RandomGen g => g -> [V2 a] Source #

Uniform a => Uniform (V2 a) 
Instance details

Defined in Linear.V2

Methods

uniformM :: StatefulGen g m => g -> m (V2 a) Source #

UniformRange a => UniformRange (V2 a) 
Instance details

Defined in Linear.V2

Methods

uniformRM :: StatefulGen g m => (V2 a, V2 a) -> g -> m (V2 a) Source #

Unbox a => Unbox (V2 a) 
Instance details

Defined in Linear.V2

FoldableWithIndex (E V2) V2 
Instance details

Defined in Linear.V2

Methods

ifoldMap :: Monoid m => (E V2 -> a -> m) -> V2 a -> m Source #

ifoldMap' :: Monoid m => (E V2 -> a -> m) -> V2 a -> m Source #

ifoldr :: (E V2 -> a -> b -> b) -> b -> V2 a -> b Source #

ifoldl :: (E V2 -> b -> a -> b) -> b -> V2 a -> b Source #

ifoldr' :: (E V2 -> a -> b -> b) -> b -> V2 a -> b Source #

ifoldl' :: (E V2 -> b -> a -> b) -> b -> V2 a -> b Source #

FunctorWithIndex (E V2) V2 
Instance details

Defined in Linear.V2

Methods

imap :: (E V2 -> a -> b) -> V2 a -> V2 b Source #

TraversableWithIndex (E V2) V2 
Instance details

Defined in Linear.V2

Methods

itraverse :: Applicative f => (E V2 -> a -> f b) -> V2 a -> f (V2 b) Source #

Each (V2 a) (V2 b) a b 
Instance details

Defined in Linear.V2

Methods

each :: Traversal (V2 a) (V2 b) a b Source #

Field1 (V2 a) (V2 a) a a 
Instance details

Defined in Linear.V2

Methods

_1 :: Lens (V2 a) (V2 a) a a Source #

Field2 (V2 a) (V2 a) a a 
Instance details

Defined in Linear.V2

Methods

_2 :: Lens (V2 a) (V2 a) a a Source #

type Rep V2 
Instance details

Defined in Linear.V2

type Rep V2 = E V2
type Diff V2 
Instance details

Defined in Linear.Affine

type Diff V2 = V2
type Size V2 
Instance details

Defined in Linear.V2

type Size V2 = 2
type Rep1 V2 
Instance details

Defined in Linear.V2

type Rep1 V2 = D1 ('MetaData "V2" "Linear.V2" "linear-1.23.1-4d1e410d44f205bb3e41019c738988ce2ab4eb665f04e18eaa3a1d1856e2566c" 'False) (C1 ('MetaCons "V2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1))
data MVector s (V2 a) 
Instance details

Defined in Linear.V2

data MVector s (V2 a) = MV_V2 !Int !(MVector s a)
type Rep (V2 a) 
Instance details

Defined in Linear.V2

type Rep (V2 a) = D1 ('MetaData "V2" "Linear.V2" "linear-1.23.1-4d1e410d44f205bb3e41019c738988ce2ab4eb665f04e18eaa3a1d1856e2566c" 'False) (C1 ('MetaCons "V2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))
type Index (V2 a) 
Instance details

Defined in Linear.V2

type Index (V2 a) = E V2
type IxValue (V2 a) 
Instance details

Defined in Linear.V2

type IxValue (V2 a) = a
data Vector (V2 a) 
Instance details

Defined in Linear.V2

data Vector (V2 a) = V_V2 !Int !(Vector a)