swarm-0.7.0.0: 2D resource gathering game with programmable robots
LicenseBSD-3-Clause
Safe HaskellNone
LanguageHaskell2010

Swarm.Game.Location

Description

Locations and headings.

Synopsis

Documentation

type Location = Point V2 Int32 Source #

A Location is a pair of (x,y) coordinates, both up to 32 bits. The positive x-axis points east and the positive y-axis points north. These are the coordinates that are shown to players.

See also the Coords type defined in Swarm.Game.World, which use a (row, column) format instead, which is more convenient for internal use. The Swarm.Game.World module also defines conversions between Location and Coords.

pattern Location :: Int32 -> Int32 -> Location Source #

A convenient way to pattern-match on Location values.

Heading and Direction functions

type Heading = V2 Int32 Source #

A Heading is a 2D vector, with 32-bit coordinates.

Location and Heading are both represented using types from the linear package, so they can be manipulated using a large number of operators from that package. For example:

applyTurn :: Direction -> Heading -> Heading Source #

The applyTurn function gives the meaning of each Direction by turning relative to the given heading or by turning to an absolute heading.

>>> applyTurn (DRelative (DPlanar DLeft)) (V2 5 3)
V2 (-3) 5
>>> applyTurn (DAbsolute DWest) (V2 5 3)
V2 (-1) 0

relativeTo :: AbsoluteDir -> AbsoluteDir -> PlanarRelativeDir Source #

Return the PlanarRelativeDir which would result in turning to the first (target) direction from the second (reference) direction.

>>> DWest `relativeTo` DSouth
DRight
>>> DWest `relativeTo` DWest
DForward

toDirection :: Heading -> Maybe Direction Source #

Possibly convert a heading into a Direction---that is, if the vector happens to be a unit vector in one of the cardinal directions.

>>> toDirection (V2 0 (-1))
Just (DAbsolute DSouth)
>>> toDirection (V2 3 7)
Nothing

toAbsDirection :: Heading -> Maybe AbsoluteDir Source #

Like toDirection, but preserve the type guarantee of an absolute direction

nearestDirection :: Heading -> AbsoluteDir Source #

Compute the absolute direction nearest to a given Heading.

Logic adapted from https://gamedev.stackexchange.com/questions/49290/#comment213403_49300.

isCardinal :: Direction -> Bool #

Check if the direction is absolute (e.g. north or south).

north :: Heading Source #

The cardinal direction north = V2 0 1.

south :: Heading Source #

The cardinal direction south = V2 0 (-1).

east :: Heading Source #

The cardinal direction east = V2 1 0.

west :: Heading Source #

The cardinal direction west = V2 (-1) 0.

Utility functions

manhattan :: Location -> Location -> Int32 Source #

Manhattan distance between world locations.

euclidean :: Location -> Location -> Double Source #

Euclidean distance between world locations.

asVector :: Location -> V2 Int32 Source #

Converts a Point to a vector offset from the origin.

getLocsInArea :: Location -> Int32 -> [Location] Source #

Get all the locations that are within a certain manhattan distance from a given location.

>>> getLocsInArea (P (V2 0 0)) 1
[P (V2 0 0),P (V2 0 1),P (V2 0 (-1)),P (V2 1 0),P (V2 (-1) 0)]
>>> map (\i -> length (getLocsInArea origin i)) [0..8]
[1,5,13,25,41,61,85,113,145]

See also Swarm.Game.Step.Const.genDiamondSides.

getElemsInArea :: Location -> Int32 -> Map Location e -> [e] Source #

Get elements that are within a certain manhattan distance from location.

>>> v2s i = [(p, manhattan origin p) | x <- [-i..i], y <- [-i..i], let p = Location x y]
>>> v2s 0
[(P (V2 0 0),0)]
>>> map (\i -> length (getElemsInArea origin i (Map.fromList $ v2s i))) [0..8]
[1,5,13,25,41,61,85,113,145]

The last test is the sequence "Centered square numbers": https://oeis.org/A001844

Re-exports for convenience

class Additive (Diff p) => Affine (p :: Type -> Type) where #

An affine space is roughly a vector space in which we have forgotten or at least pretend to have forgotten the origin.

a .+^ (b .-. a)  =  b@
(a .+^ u) .+^ v  =  a .+^ (u ^+^ v)@
(a .-. b) ^+^ v  =  (a .+^ v) .-. q@

Minimal complete definition

(.-.), (.+^)

Associated Types

type Diff (p :: Type -> Type) :: Type -> Type #

Methods

(.-.) :: Num a => p a -> p a -> Diff p a infixl 6 #

Get the difference between two points as a vector offset.

(.+^) :: Num a => p a -> Diff p a -> p a infixl 6 #

Add a vector offset to a point.

(.-^) :: Num a => p a -> Diff p a -> p a infixl 6 #

Subtract a vector offset from a point.

Instances

Instances details
Affine ZipList 
Instance details

Defined in Linear.Affine

Associated Types

type Diff ZipList 
Instance details

Defined in Linear.Affine

Methods

(.-.) :: Num a => ZipList a -> ZipList a -> Diff ZipList a #

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

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

Affine Complex 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Complex 
Instance details

Defined in Linear.Affine

Methods

(.-.) :: Num a => Complex a -> Complex a -> Diff Complex a #

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

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

Affine Identity 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Identity 
Instance details

Defined in Linear.Affine

Methods

(.-.) :: Num a => Identity a -> Identity a -> Diff Identity a #

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

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

Affine IntMap 
Instance details

Defined in Linear.Affine

Associated Types

type Diff IntMap 
Instance details

Defined in Linear.Affine

Methods

(.-.) :: Num a => IntMap a -> IntMap a -> Diff IntMap a #

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

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

Affine Plucker 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Plucker 
Instance details

Defined in Linear.Affine

Methods

(.-.) :: Num a => Plucker a -> Plucker a -> Diff Plucker a #

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

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

Affine Quaternion 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Quaternion 
Instance details

Defined in Linear.Affine

Affine V0 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V0 
Instance details

Defined in Linear.Affine

type Diff V0 = V0

Methods

(.-.) :: Num a => V0 a -> V0 a -> Diff V0 a #

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

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

Affine V1 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V1 
Instance details

Defined in Linear.Affine

type Diff V1 = V1

Methods

(.-.) :: Num a => V1 a -> V1 a -> Diff V1 a #

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

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

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 #

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

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

Affine V3 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V3 
Instance details

Defined in Linear.Affine

type Diff V3 = V3

Methods

(.-.) :: Num a => V3 a -> V3 a -> Diff V3 a #

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

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

Affine V4 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V4 
Instance details

Defined in Linear.Affine

type Diff V4 = V4

Methods

(.-.) :: Num a => V4 a -> V4 a -> Diff V4 a #

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

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

Affine Vector 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Vector 
Instance details

Defined in Linear.Affine

type Diff Vector = Vector

Methods

(.-.) :: Num a => Vector a -> Vector a -> Diff Vector a #

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

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

Affine Maybe 
Instance details

Defined in Linear.Affine

Associated Types

type Diff Maybe 
Instance details

Defined in Linear.Affine

Methods

(.-.) :: Num a => Maybe a -> Maybe a -> Diff Maybe a #

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

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

Affine [] 
Instance details

Defined in Linear.Affine

Associated Types

type Diff [] 
Instance details

Defined in Linear.Affine

type Diff [] = []

Methods

(.-.) :: Num a => [a] -> [a] -> Diff [] a #

(.+^) :: Num a => [a] -> Diff [] a -> [a] #

(.-^) :: Num a => [a] -> Diff [] a -> [a] #

Ord k => Affine (Map k) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (Map k) 
Instance details

Defined in Linear.Affine

type Diff (Map k) = Map k

Methods

(.-.) :: Num a => Map k a -> Map k a -> Diff (Map k) a #

(.+^) :: Num a => Map k a -> Diff (Map k) a -> Map k a #

(.-^) :: Num a => Map k a -> Diff (Map k) a -> Map k a #

Additive f => Affine (Point f) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (Point f) 
Instance details

Defined in Linear.Affine

type Diff (Point f) = f

Methods

(.-.) :: Num a => Point f a -> Point f a -> Diff (Point f) a #

(.+^) :: Num a => Point f a -> Diff (Point f) a -> Point f a #

(.-^) :: Num a => Point f a -> Diff (Point f) a -> Point f a #

(Eq k, Hashable k) => Affine (HashMap k) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (HashMap k) 
Instance details

Defined in Linear.Affine

type Diff (HashMap k) = HashMap k

Methods

(.-.) :: Num a => HashMap k a -> HashMap k a -> Diff (HashMap k) a #

(.+^) :: Num a => HashMap k a -> Diff (HashMap k) a -> HashMap k a #

(.-^) :: Num a => HashMap k a -> Diff (HashMap k) a -> HashMap k a #

Dim n => Affine (V n) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (V n) 
Instance details

Defined in Linear.Affine

type Diff (V n) = V n

Methods

(.-.) :: Num a => V n a -> V n a -> Diff (V n) a #

(.+^) :: Num a => V n a -> Diff (V n) a -> V n a #

(.-^) :: Num a => V n a -> Diff (V n) a -> V n a #

(Affine f, Affine g) => Affine (Product f g) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (Product f g) 
Instance details

Defined in Linear.Affine

type Diff (Product f g) = Product (Diff f) (Diff g)

Methods

(.-.) :: Num a => Product f g a -> Product f g a -> Diff (Product f g) a #

(.+^) :: Num a => Product f g a -> Diff (Product f g) a -> Product f g a #

(.-^) :: Num a => Product f g a -> Diff (Product f g) a -> Product f g a #

Affine ((->) b) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff ((->) b) 
Instance details

Defined in Linear.Affine

type Diff ((->) b) = (->) b

Methods

(.-.) :: Num a => (b -> a) -> (b -> a) -> Diff ((->) b) a #

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

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

newtype Point (f :: Type -> Type) a #

A handy wrapper to help distinguish points from vectors at the type level

Constructors

P (f a) 

Instances

Instances details
FromJSON Location Source # 
Instance details

Defined in Swarm.Game.Location

ToJSON Location Source # 
Instance details

Defined in Swarm.Game.Location

Generic1 (Point f :: Type -> Type) 
Instance details

Defined in Linear.Affine

Associated Types

type Rep1 (Point f :: Type -> Type) 
Instance details

Defined in Linear.Affine

type Rep1 (Point f :: Type -> Type) = D1 ('MetaData "Point" "Linear.Affine" "linear-1.23.1-AIWD1zxQJEl7uo4Wlo38k" 'True) (C1 ('MetaCons "P" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 f)))

Methods

from1 :: Point f a -> Rep1 (Point f) a #

to1 :: Rep1 (Point f) a -> Point f a #

Unbox (f a) => Vector Vector (Point f a) 
Instance details

Defined in Linear.Affine

Methods

basicUnsafeFreeze :: Mutable Vector s (Point f a) -> ST s (Vector (Point f a))

basicUnsafeThaw :: Vector (Point f a) -> ST s (Mutable Vector s (Point f a))

basicLength :: Vector (Point f a) -> Int

basicUnsafeSlice :: Int -> Int -> Vector (Point f a) -> Vector (Point f a)

basicUnsafeIndexM :: Vector (Point f a) -> Int -> Box (Point f a)

basicUnsafeCopy :: Mutable Vector s (Point f a) -> Vector (Point f a) -> ST s ()

elemseq :: Vector (Point f a) -> Point f a -> b -> b

Unbox (f a) => MVector MVector (Point f a) 
Instance details

Defined in Linear.Affine

Methods

basicLength :: MVector s (Point f a) -> Int

basicUnsafeSlice :: Int -> Int -> MVector s (Point f a) -> MVector s (Point f a)

basicOverlaps :: MVector s (Point f a) -> MVector s (Point f a) -> Bool

basicUnsafeNew :: Int -> ST s (MVector s (Point f a))

basicInitialize :: MVector s (Point f a) -> ST s ()

basicUnsafeReplicate :: Int -> Point f a -> ST s (MVector s (Point f a))

basicUnsafeRead :: MVector s (Point f a) -> Int -> ST s (Point f a)

basicUnsafeWrite :: MVector s (Point f a) -> Int -> Point f a -> ST s ()

basicClear :: MVector s (Point f a) -> ST s ()

basicSet :: MVector s (Point f a) -> Point f a -> ST s ()

basicUnsafeCopy :: MVector s (Point f a) -> MVector s (Point f a) -> ST s ()

basicUnsafeMove :: MVector s (Point f a) -> MVector s (Point f a) -> ST s ()

basicUnsafeGrow :: MVector s (Point f a) -> Int -> ST s (MVector s (Point f a))

Representable f => Representable (Point f) 
Instance details

Defined in Linear.Affine

Associated Types

type Rep (Point f) 
Instance details

Defined in Linear.Affine

type Rep (Point f) = Rep f

Methods

tabulate :: (Rep (Point f) -> a) -> Point f a #

index :: Point f a -> Rep (Point f) -> a #

Foldable f => Foldable (Point f) 
Instance details

Defined in Linear.Affine

Methods

fold :: Monoid m => Point f m -> m #

foldMap :: Monoid m => (a -> m) -> Point f a -> m #

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

foldr :: (a -> b -> b) -> b -> Point f a -> b #

foldr' :: (a -> b -> b) -> b -> Point f a -> b #

foldl :: (b -> a -> b) -> b -> Point f a -> b #

foldl' :: (b -> a -> b) -> b -> Point f a -> b #

foldr1 :: (a -> a -> a) -> Point f a -> a #

foldl1 :: (a -> a -> a) -> Point f a -> a #

toList :: Point f a -> [a] #

null :: Point f a -> Bool #

length :: Point f a -> Int #

elem :: Eq a => a -> Point f a -> Bool #

maximum :: Ord a => Point f a -> a #

minimum :: Ord a => Point f a -> a #

sum :: Num a => Point f a -> a #

product :: Num a => Point f a -> a #

Eq1 f => Eq1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

liftEq :: (a -> b -> Bool) -> Point f a -> Point f b -> Bool #

Ord1 f => Ord1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

liftCompare :: (a -> b -> Ordering) -> Point f a -> Point f b -> Ordering #

Read1 f => Read1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

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

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

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Point f a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Point f a] #

Show1 f => Show1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

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

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

Traversable f => Traversable (Point f) 
Instance details

Defined in Linear.Affine

Methods

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

sequenceA :: Applicative f0 => Point f (f0 a) -> f0 (Point f a) #

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

sequence :: Monad m => Point f (m a) -> m (Point f a) #

Applicative f => Applicative (Point f) 
Instance details

Defined in Linear.Affine

Methods

pure :: a -> Point f a #

(<*>) :: Point f (a -> b) -> Point f a -> Point f b #

liftA2 :: (a -> b -> c) -> Point f a -> Point f b -> Point f c #

(*>) :: Point f a -> Point f b -> Point f b #

(<*) :: Point f a -> Point f b -> Point f a #

Functor f => Functor (Point f) 
Instance details

Defined in Linear.Affine

Methods

fmap :: (a -> b) -> Point f a -> Point f b #

(<$) :: a -> Point f b -> Point f a #

Monad f => Monad (Point f) 
Instance details

Defined in Linear.Affine

Methods

(>>=) :: Point f a -> (a -> Point f b) -> Point f b #

(>>) :: Point f a -> Point f b -> Point f b #

return :: a -> Point f a #

Serial1 f => Serial1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

serializeWith :: MonadPut m => (a -> m ()) -> Point f a -> m () #

deserializeWith :: MonadGet m => m a -> m (Point f a) #

Distributive f => Distributive (Point f) 
Instance details

Defined in Linear.Affine

Methods

distribute :: Functor f0 => f0 (Point f a) -> Point f (f0 a) #

collect :: Functor f0 => (a -> Point f b) -> f0 a -> Point f (f0 b) #

distributeM :: Monad m => m (Point f a) -> Point f (m a) #

collectM :: Monad m => (a -> Point f b) -> m a -> Point f (m b) #

Hashable1 f => Hashable1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Point f a -> Int #

Additive f => Affine (Point f) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (Point f) 
Instance details

Defined in Linear.Affine

type Diff (Point f) = f

Methods

(.-.) :: Num a => Point f a -> Point f a -> Diff (Point f) a #

(.+^) :: Num a => Point f a -> Diff (Point f) a -> Point f a #

(.-^) :: Num a => Point f a -> Diff (Point f) a -> Point f a #

Metric f => Metric (Point f) 
Instance details

Defined in Linear.Affine

Methods

dot :: Num a => Point f a -> Point f a -> a #

quadrance :: Num a => Point f a -> a #

qd :: Num a => Point f a -> Point f a -> a #

distance :: Floating a => Point f a -> Point f a -> a #

norm :: Floating a => Point f a -> a #

signorm :: Floating a => Point f a -> Point f a #

Finite f => Finite (Point f) 
Instance details

Defined in Linear.Affine

Associated Types

type Size (Point f) 
Instance details

Defined in Linear.Affine

type Size (Point f) = Size f

Methods

toV :: Point f a -> V (Size (Point f)) a #

fromV :: V (Size (Point f)) a -> Point f a #

R1 f => R1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_x :: Lens' (Point f a) a #

R2 f => R2 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_y :: Lens' (Point f a) a #

_xy :: Lens' (Point f a) (V2 a) #

R3 f => R3 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_z :: Lens' (Point f a) a #

_xyz :: Lens' (Point f a) (V3 a) #

R4 f => R4 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_w :: Lens' (Point f a) a #

_xyzw :: Lens' (Point f a) (V4 a) #

Additive f => Additive (Point f) 
Instance details

Defined in Linear.Affine

Methods

zero :: Num a => Point f a #

(^+^) :: Num a => Point f a -> Point f a -> Point f a #

(^-^) :: Num a => Point f a -> Point f a -> Point f a #

lerp :: Num a => a -> Point f a -> Point f a -> Point f a #

liftU2 :: (a -> a -> a) -> Point f a -> Point f a -> Point f a #

liftI2 :: (a -> b -> c) -> Point f a -> Point f b -> Point f c #

Apply f => Apply (Point f) 
Instance details

Defined in Linear.Affine

Methods

(<.>) :: Point f (a -> b) -> Point f a -> Point f b #

(.>) :: Point f a -> Point f b -> Point f b #

(<.) :: Point f a -> Point f b -> Point f a #

liftF2 :: (a -> b -> c) -> Point f a -> Point f b -> Point f c #

Bind f => Bind (Point f) 
Instance details

Defined in Linear.Affine

Methods

(>>-) :: Point f a -> (a -> Point f b) -> Point f b #

join :: Point f (Point f a) -> Point f a #

(Typeable f, Typeable a, Data (f a)) => Data (Point f a) 
Instance details

Defined in Linear.Affine

Methods

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

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

toConstr :: Point f a -> Constr #

dataTypeOf :: Point f a -> DataType #

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

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

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

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

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

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

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

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

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

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

Storable (f a) => Storable (Point f a) 
Instance details

Defined in Linear.Affine

Methods

sizeOf :: Point f a -> Int #

alignment :: Point f a -> Int #

peekElemOff :: Ptr (Point f a) -> Int -> IO (Point f a) #

pokeElemOff :: Ptr (Point f a) -> Int -> Point f a -> IO () #

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

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

peek :: Ptr (Point f a) -> IO (Point f a) #

poke :: Ptr (Point f a) -> Point f a -> IO () #

Monoid (f a) => Monoid (Point f a) 
Instance details

Defined in Linear.Affine

Methods

mempty :: Point f a #

mappend :: Point f a -> Point f a -> Point f a #

mconcat :: [Point f a] -> Point f a #

Semigroup (f a) => Semigroup (Point f a) 
Instance details

Defined in Linear.Affine

Methods

(<>) :: Point f a -> Point f a -> Point f a #

sconcat :: NonEmpty (Point f a) -> Point f a #

stimes :: Integral b => b -> Point f a -> Point f a #

Generic (Point f a) 
Instance details

Defined in Linear.Affine

Associated Types

type Rep (Point f a) 
Instance details

Defined in Linear.Affine

type Rep (Point f a) = D1 ('MetaData "Point" "Linear.Affine" "linear-1.23.1-AIWD1zxQJEl7uo4Wlo38k" 'True) (C1 ('MetaCons "P" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a))))

Methods

from :: Point f a -> Rep (Point f a) x #

to :: Rep (Point f a) x -> Point f a #

Ix (f a) => Ix (Point f a) 
Instance details

Defined in Linear.Affine

Methods

range :: (Point f a, Point f a) -> [Point f a] #

index :: (Point f a, Point f a) -> Point f a -> Int #

unsafeIndex :: (Point f a, Point f a) -> Point f a -> Int #

inRange :: (Point f a, Point f a) -> Point f a -> Bool #

rangeSize :: (Point f a, Point f a) -> Int #

unsafeRangeSize :: (Point f a, Point f a) -> Int #

Num (f a) => Num (Point f a) 
Instance details

Defined in Linear.Affine

Methods

(+) :: Point f a -> Point f a -> Point f a #

(-) :: Point f a -> Point f a -> Point f a #

(*) :: Point f a -> Point f a -> Point f a #

negate :: Point f a -> Point f a #

abs :: Point f a -> Point f a #

signum :: Point f a -> Point f a #

fromInteger :: Integer -> Point f a #

Read (f a) => Read (Point f a) 
Instance details

Defined in Linear.Affine

Fractional (f a) => Fractional (Point f a) 
Instance details

Defined in Linear.Affine

Methods

(/) :: Point f a -> Point f a -> Point f a #

recip :: Point f a -> Point f a #

fromRational :: Rational -> Point f a #

Show (f a) => Show (Point f a) 
Instance details

Defined in Linear.Affine

Methods

showsPrec :: Int -> Point f a -> ShowS #

show :: Point f a -> String #

showList :: [Point f a] -> ShowS #

Binary (f a) => Binary (Point f a) 
Instance details

Defined in Linear.Affine

Methods

put :: Point f a -> Put #

get :: Get (Point f a) #

putList :: [Point f a] -> Put #

Serial (f a) => Serial (Point f a) 
Instance details

Defined in Linear.Affine

Methods

serialize :: MonadPut m => Point f a -> m () #

deserialize :: MonadGet m => m (Point f a) #

Serialize (f a) => Serialize (Point f a) 
Instance details

Defined in Linear.Affine

Methods

put :: Putter (Point f a) #

get :: Get (Point f a) #

NFData (f a) => NFData (Point f a) 
Instance details

Defined in Linear.Affine

Methods

rnf :: Point f a -> () #

Eq (f a) => Eq (Point f a) 
Instance details

Defined in Linear.Affine

Methods

(==) :: Point f a -> Point f a -> Bool #

(/=) :: Point f a -> Point f a -> Bool #

Ord (f a) => Ord (Point f a) 
Instance details

Defined in Linear.Affine

Methods

compare :: Point f a -> Point f a -> Ordering #

(<) :: Point f a -> Point f a -> Bool #

(<=) :: Point f a -> Point f a -> Bool #

(>) :: Point f a -> Point f a -> Bool #

(>=) :: Point f a -> Point f a -> Bool #

max :: Point f a -> Point f a -> Point f a #

min :: Point f a -> Point f a -> Point f a #

Hashable (f a) => Hashable (Point f a) 
Instance details

Defined in Linear.Affine

Methods

hashWithSalt :: Int -> Point f a -> Int #

hash :: Point f a -> Int #

Ixed (f a) => Ixed (Point f a) 
Instance details

Defined in Linear.Affine

Methods

ix :: Index (Point f a) -> Traversal' (Point f a) (IxValue (Point f a)) #

Wrapped (Point f a) 
Instance details

Defined in Linear.Affine

Associated Types

type Unwrapped (Point f a) 
Instance details

Defined in Linear.Affine

type Unwrapped (Point f a) = f a

Methods

_Wrapped' :: Iso' (Point f a) (Unwrapped (Point f a)) #

Epsilon (f a) => Epsilon (Point f a) 
Instance details

Defined in Linear.Affine

Methods

nearZero :: Point f a -> Bool #

Random (f a) => Random (Point f a) 
Instance details

Defined in Linear.Affine

Methods

randomR :: RandomGen g => (Point f a, Point f a) -> g -> (Point f a, g) #

random :: RandomGen g => g -> (Point f a, g) #

randomRs :: RandomGen g => (Point f a, Point f a) -> g -> [Point f a] #

randoms :: RandomGen g => g -> [Point f a] #

Unbox (f a) => Unbox (Point f a) 
Instance details

Defined in Linear.Affine

t ~ Point g b => Rewrapped (Point f a) t 
Instance details

Defined in Linear.Affine

Traversable f => Each (Point f a) (Point f b) a b 
Instance details

Defined in Linear.Affine

Methods

each :: Traversal (Point f a) (Point f b) a b #

type Rep1 (Point f :: Type -> Type) 
Instance details

Defined in Linear.Affine

type Rep1 (Point f :: Type -> Type) = D1 ('MetaData "Point" "Linear.Affine" "linear-1.23.1-AIWD1zxQJEl7uo4Wlo38k" 'True) (C1 ('MetaCons "P" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 f)))
newtype MVector s (Point f a) 
Instance details

Defined in Linear.Affine

newtype MVector s (Point f a) = MV_P (MVector s (f a))
type Rep (Point f) 
Instance details

Defined in Linear.Affine

type Rep (Point f) = Rep f
type Diff (Point f) 
Instance details

Defined in Linear.Affine

type Diff (Point f) = f
type Size (Point f) 
Instance details

Defined in Linear.Affine

type Size (Point f) = Size f
type Rep (Point f a) 
Instance details

Defined in Linear.Affine

type Rep (Point f a) = D1 ('MetaData "Point" "Linear.Affine" "linear-1.23.1-AIWD1zxQJEl7uo4Wlo38k" 'True) (C1 ('MetaCons "P" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a))))
type Index (Point f a) 
Instance details

Defined in Linear.Affine

type Index (Point f a) = Index (f a)
type IxValue (Point f a) 
Instance details

Defined in Linear.Affine

type IxValue (Point f a) = IxValue (f a)
type Unwrapped (Point f a) 
Instance details

Defined in Linear.Affine

type Unwrapped (Point f a) = f a
newtype Vector (Point f a) 
Instance details

Defined in Linear.Affine

newtype Vector (Point f a) = V_P (Vector (f a))

origin :: forall (f :: Type -> Type) a. (Additive f, Num a) => Point f a #

Vector spaces have origins.

Orphan instances