| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
SDL.Vect
Description
SDL's vector representation.
By default, re-exports the Linear and Linear.Affine modules from the
linear package. With the no-linear Cabal flag, instead exports a
duplicate implementation of the V2, V3, V4 and Point types from
SDL.Internal.Vect, which provides as many instances as possible for those
types while avoiding any additional dependencies.
Documentation
module Linear.Affine
module Linear
Point
newtype Point (f :: Type -> Type) a #
A handy wrapper to help distinguish points from vectors at the type level
Constructors
| P (f a) |
Instances
| Generic1 (Point f :: Type -> Type) | |
| Unbox (f a) => Vector Vector (Point f a) | |
Defined in Linear.Affine Methods basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Point f a) -> m (Vector (Point f a)) # basicUnsafeThaw :: PrimMonad m => Vector (Point f a) -> m (Mutable Vector (PrimState m) (Point f a)) # basicLength :: Vector (Point f a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (Point f a) -> Vector (Point f a) # basicUnsafeIndexM :: Monad m => Vector (Point f a) -> Int -> m (Point f a) # basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Point f a) -> Vector (Point f a) -> m () # | |
| Unbox (f a) => MVector MVector (Point f a) | |
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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Point f a)) # basicInitialize :: PrimMonad m => MVector (PrimState m) (Point f a) -> m () # basicUnsafeReplicate :: PrimMonad m => Int -> Point f a -> m (MVector (PrimState m) (Point f a)) # basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Point f a) -> Int -> m (Point f a) # basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Point f a) -> Int -> Point f a -> m () # basicClear :: PrimMonad m => MVector (PrimState m) (Point f a) -> m () # basicSet :: PrimMonad m => MVector (PrimState m) (Point f a) -> Point f a -> m () # basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Point f a) -> MVector (PrimState m) (Point f a) -> m () # basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Point f a) -> MVector (PrimState m) (Point f a) -> m () # basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Point f a) -> Int -> m (MVector (PrimState m) (Point f a)) # | |
| Representable f => Representable (Point f) | |
| Foldable f => Foldable (Point f) | |
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 # elem :: Eq a => a -> Point f a -> Bool # maximum :: Ord a => Point f a -> a # minimum :: Ord a => Point f a -> a # | |
| Eq1 f => Eq1 (Point f) | |
| Ord1 f => Ord1 (Point f) | |
Defined in Linear.Affine | |
| Read1 f => Read1 (Point f) | |
Defined in Linear.Affine | |
| Show1 f => Show1 (Point f) | |
| Traversable f => Traversable (Point f) | |
| Applicative f => Applicative (Point f) | |
| Functor f => Functor (Point f) | |
| Monad f => Monad (Point f) | |
| Serial1 f => Serial1 (Point f) | |
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) | |
| Hashable1 f => Hashable1 (Point f) | |
Defined in Linear.Affine | |
| Additive f => Affine (Point f) | |
| Metric f => Metric (Point f) | |
Defined in Linear.Affine | |
| Finite f => Finite (Point f) | |
| R1 f => R1 (Point f) | |
Defined in Linear.Affine | |
| R2 f => R2 (Point f) | |
| R3 f => R3 (Point f) | |
| R4 f => R4 (Point f) | |
| Additive f => Additive (Point f) | |
Defined in Linear.Affine Methods (^+^) :: 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) | |
| Bind f => Bind (Point f) | |
| (Typeable f, Typeable a, Data (f a)) => Data (Point f a) | |
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) | |
Defined in Linear.Affine | |
| Monoid (f a) => Monoid (Point f a) | |
| Semigroup (f a) => Semigroup (Point f a) | |
| Generic (Point f a) | |
| Ix (f a) => Ix (Point f a) | |
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) | |
Defined in Linear.Affine | |
| Read (f a) => Read (Point f a) | |
| Fractional (f a) => Fractional (Point f a) | |
| Show (f a) => Show (Point f a) | |
| Binary (f a) => Binary (Point f a) | |
| Serial (f a) => Serial (Point f a) | |
Defined in Linear.Affine | |
| Serialize (f a) => Serialize (Point f a) | |
| NFData (f a) => NFData (Point f a) | |
Defined in Linear.Affine | |
| Eq (f a) => Eq (Point f a) | |
| Ord (f a) => Ord (Point f a) | |
| Hashable (f a) => Hashable (Point f a) | |
Defined in Linear.Affine | |
| Ixed (f a) => Ixed (Point f a) | |
Defined in Linear.Affine | |
| Wrapped (Point f a) | |
| Epsilon (f a) => Epsilon (Point f a) | |
Defined in Linear.Affine | |
| Random (f a) => Random (Point f a) | |
| Unbox (f a) => Unbox (Point f a) | |
Defined in Linear.Affine | |
| t ~ Point g b => Rewrapped (Point f a) t | |
Defined in Linear.Affine | |
| Traversable f => Each (Point f a) (Point f b) a b | |
| type Rep1 (Point f :: Type -> Type) | |
| newtype MVector s (Point f a) | |
Defined in Linear.Affine | |
| type Rep (Point f) | |
Defined in Linear.Affine | |
| type Diff (Point f) | |
Defined in Linear.Affine | |
| type Size (Point f) | |
Defined in Linear.Affine | |
| type Rep (Point f a) | |
Defined in Linear.Affine | |
| type Index (Point f a) | |
Defined in Linear.Affine | |
| type IxValue (Point f a) | |
Defined in Linear.Affine | |
| type Unwrapped (Point f a) | |
Defined in Linear.Affine | |
| newtype Vector (Point f a) | |
Defined in Linear.Affine | |
Vectors
A 2-dimensional vector
>>>pure 1 :: V2 IntV2 1 1
>>>V2 1 2 + V2 3 4V2 4 6
>>>V2 1 2 * V2 3 4V2 3 8
>>>sum (V2 1 2)3
Constructors
| V2 !a !a |
Instances
| Representable V2 | |
| MonadFix V2 | |
| MonadZip V2 | |
| Foldable V2 | |
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 # elem :: Eq a => a -> V2 a -> Bool # maximum :: Ord a => V2 a -> a # | |
| Eq1 V2 | |
| Ord1 V2 | |
| Read1 V2 | |
| Show1 V2 | |
| Traversable V2 | |
| Applicative V2 | |
| Functor V2 | |
| Monad V2 | |
| Serial1 V2 | |
Defined in Linear.V2 Methods serializeWith :: MonadPut m => (a -> m ()) -> V2 a -> m () # deserializeWith :: MonadGet m => m a -> m (V2 a) # | |
| Distributive V2 | |
| Hashable1 V2 | |
| Affine V2 | |
| Metric V2 | |
| Trace V2 | |
| Finite V2 | |
| R1 V2 | |
| R2 V2 | |
| Additive V2 | |
| Apply V2 | |
| Bind V2 | |
| Foldable1 V2 | |
| Traversable1 V2 | |
| Generic1 V2 | |
| Num r => Coalgebra r (E V2) | |
| Unbox a => Vector Vector (V2 a) | |
Defined in Linear.V2 Methods basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (V2 a) -> m (Vector (V2 a)) # basicUnsafeThaw :: PrimMonad m => Vector (V2 a) -> m (Mutable Vector (PrimState m) (V2 a)) # basicLength :: Vector (V2 a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (V2 a) -> Vector (V2 a) # basicUnsafeIndexM :: Monad m => Vector (V2 a) -> Int -> m (V2 a) # basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (V2 a) -> Vector (V2 a) -> m () # | |
| Unbox a => MVector MVector (V2 a) | |
Defined in Linear.V2 Methods basicLength :: MVector s (V2 a) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (V2 a) -> MVector s (V2 a) # basicOverlaps :: MVector s (V2 a) -> MVector s (V2 a) -> Bool # basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (V2 a)) # basicInitialize :: PrimMonad m => MVector (PrimState m) (V2 a) -> m () # basicUnsafeReplicate :: PrimMonad m => Int -> V2 a -> m (MVector (PrimState m) (V2 a)) # basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (V2 a) -> Int -> m (V2 a) # basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (V2 a) -> Int -> V2 a -> m () # basicClear :: PrimMonad m => MVector (PrimState m) (V2 a) -> m () # basicSet :: PrimMonad m => MVector (PrimState m) (V2 a) -> V2 a -> m () # basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (V2 a) -> MVector (PrimState m) (V2 a) -> m () # basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (V2 a) -> MVector (PrimState m) (V2 a) -> m () # basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (V2 a) -> Int -> m (MVector (PrimState m) (V2 a)) # | |
| Data a => Data (V2 a) | |
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) # 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) # | |
| Storable a => Storable (V2 a) | |
| Monoid a => Monoid (V2 a) | |
| Semigroup a => Semigroup (V2 a) | |
| Bounded a => Bounded (V2 a) | |
| Floating a => Floating (V2 a) | |
| Generic (V2 a) | |
| Ix a => Ix (V2 a) | |
| Num a => Num (V2 a) | |
| Read a => Read (V2 a) | |
| Fractional a => Fractional (V2 a) | |
| Show a => Show (V2 a) | |
| Binary a => Binary (V2 a) | |
| Serial a => Serial (V2 a) | |
| Serialize a => Serialize (V2 a) | |
| NFData a => NFData (V2 a) | |
| Eq a => Eq (V2 a) | |
| Ord a => Ord (V2 a) | |
| Hashable a => Hashable (V2 a) | |
| Ixed (V2 a) | |
| Epsilon a => Epsilon (V2 a) | |
| Random a => Random (V2 a) | |
| Unbox a => Unbox (V2 a) | |
Defined in Linear.V2 | |
| FoldableWithIndex (E V2) V2 | |
| FunctorWithIndex (E V2) V2 | |
| TraversableWithIndex (E V2) V2 | |
| Lift a => Lift (V2 a :: Type) | |
| Each (V2 a) (V2 b) a b | |
| Field1 (V2 a) (V2 a) a a | |
| Field2 (V2 a) (V2 a) a a | |
| type Rep V2 | |
| type Diff V2 | |
Defined in Linear.Affine | |
| type Size V2 | |
| type Rep1 V2 | |
Defined in Linear.V2 type Rep1 V2 = D1 ('MetaData "V2" "Linear.V2" "linear-1.21.10-HcGEEMqTUu573HoPdRTIRY" '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) | |
| type Rep (V2 a) | |
Defined in Linear.V2 type Rep (V2 a) = D1 ('MetaData "V2" "Linear.V2" "linear-1.21.10-HcGEEMqTUu573HoPdRTIRY" '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) | |
| type IxValue (V2 a) | |
| data Vector (V2 a) | |
A 3-dimensional vector
Constructors
| V3 !a !a !a |
Instances
A 4-dimensional vector.
Constructors
| V4 !a !a !a !a |