shapes-0.1.0.0: physics engine and other tools for 2D shapes

Safe HaskellNone
LanguageHaskell2010

Utils.Utils

Description

A bunch of unrelated utility functions and types.

Synopsis

Documentation

data SP a b Source #

Constructors

SP 

Fields

Instances

(Unbox a, Unbox b) => Vector Vector (SP a b) Source # 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (SP a b) -> m (Vector (SP a b)) #

basicUnsafeThaw :: PrimMonad m => Vector (SP a b) -> m (Mutable Vector (PrimState m) (SP a b)) #

basicLength :: Vector (SP a b) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (SP a b) -> Vector (SP a b) #

basicUnsafeIndexM :: Monad m => Vector (SP a b) -> Int -> m (SP a b) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (SP a b) -> Vector (SP a b) -> m () #

elemseq :: Vector (SP a b) -> SP a b -> b -> b #

(Unbox a, Unbox b) => MVector MVector (SP a b) Source # 

Methods

basicLength :: MVector s (SP a b) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (SP a b) -> MVector s (SP a b) #

basicOverlaps :: MVector s (SP a b) -> MVector s (SP a b) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (SP a b)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (SP a b) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> SP a b -> m (MVector (PrimState m) (SP a b)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (SP a b) -> Int -> m (SP a b) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (SP a b) -> Int -> SP a b -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (SP a b) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (SP a b) -> SP a b -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (SP a b) -> MVector (PrimState m) (SP a b) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (SP a b) -> MVector (PrimState m) (SP a b) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (SP a b) -> Int -> m (MVector (PrimState m) (SP a b)) #

(Eq b, Eq a) => Eq (SP a b) Source # 

Methods

(==) :: SP a b -> SP a b -> Bool #

(/=) :: SP a b -> SP a b -> Bool #

(Ord b, Ord a) => Ord (SP a b) Source # 

Methods

compare :: SP a b -> SP a b -> Ordering #

(<) :: SP a b -> SP a b -> Bool #

(<=) :: SP a b -> SP a b -> Bool #

(>) :: SP a b -> SP a b -> Bool #

(>=) :: SP a b -> SP a b -> Bool #

max :: SP a b -> SP a b -> SP a b #

min :: SP a b -> SP a b -> SP a b #

(Show b, Show a) => Show (SP a b) Source # 

Methods

showsPrec :: Int -> SP a b -> ShowS #

show :: SP a b -> String #

showList :: [SP a b] -> ShowS #

Generic (SP a b) Source # 

Associated Types

type Rep (SP a b) :: * -> * #

Methods

from :: SP a b -> Rep (SP a b) x #

to :: Rep (SP a b) x -> SP a b #

(NFData b, NFData a) => NFData (SP a b) Source # 

Methods

rnf :: SP a b -> () #

(Unbox a, Unbox b) => Unbox (SP a b) Source # 
data MVector s (SP a b) Source # 
data MVector s (SP a b) = MV_SP (MVector s (a, b))
type Rep (SP a b) Source # 
type Rep (SP a b) = D1 * (MetaData "SP" "Utils.Utils" "shapes-0.1.0.0-E6UUiYRpOc15rGTlEn6KOE" False) (C1 * (MetaCons "SP" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_spFst") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * a)) (S1 * (MetaSel (Just Symbol "_spSnd") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * b))))
data Vector (SP a b) Source # 
data Vector (SP a b) = V_SP (Vector (a, b))

spSnd :: forall a b b. Lens (SP a b) (SP a b) b b Source #

spFst :: forall a b a. Lens (SP a b) (SP a b) a a Source #

type SP' a = SP a a Source #

toSP :: (a, b) -> SP a b Source #

fromSP :: SP a b -> (a, b) Source #

spMap :: (a -> b) -> SP a a -> SP b b Source #

pairMap :: (a -> b) -> (a, a) -> (b, b) Source #

pairAp :: (a -> b, c -> d) -> (a, c) -> (b, d) Source #

pairFold :: Monoid m => (m, m) -> m Source #

maybeChange :: a -> (a -> Maybe a) -> a Source #

toMaybe :: Bool -> a -> Maybe a Source #

maybeBranch :: (a -> a -> Bool) -> Maybe a -> Maybe a -> Maybe (Either a a) Source #

maybeBranchBoth :: (a -> a -> Bool) -> Maybe a -> Maybe a -> Maybe (Either a a) Source #

takeIfAll :: (a -> Bool) -> [a] -> Maybe [a] Source #

cycles :: [a] -> [[a]] Source #

data Loop a Source #

Constructors

Loop 

Fields

Instances

(Show a, Eq a) => Show (Loop a) Source # 

Methods

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

show :: Loop a -> String #

showList :: [Loop a] -> ShowS #

loopify :: [a] -> Loop a Source #

takeNext :: Int -> Loop a -> [Loop a] Source #

takePrev :: Int -> Loop a -> [Loop a] Source #

takeDir :: (Loop a -> Loop a) -> Int -> Loop a -> [Loop a] Source #

folds :: (b -> b) -> b -> [a] -> [b] Source #

data Flipping a Source #

Constructors

Same !a 
Flip !a 

Instances

Functor Flipping Source # 

Methods

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

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

Unbox a => Vector Vector (Flipping a) Source # 
Unbox a => MVector MVector (Flipping a) Source # 
Show a => Show (Flipping a) Source # 

Methods

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

show :: Flipping a -> String #

showList :: [Flipping a] -> ShowS #

Unbox a => Unbox (Flipping a) Source # 
Flippable (Flipping x) Source # 

Methods

flipp :: Flipping x -> Flipping x Source #

data MVector s (Flipping a) Source # 
data MVector s (Flipping a) = MV_Flipping (MVector s (Bool, a))
data Vector (Flipping a) Source # 

flipUnsafe :: (a -> (b, b) -> c) -> Flipping a -> (b, b) -> c Source #

flipMap :: (a -> (b, b) -> c) -> Flipping a -> (b, b) -> Flipping c Source #

flipExtractWith :: (a -> b, a -> b) -> Flipping a -> b Source #

flipExtractPair :: (a -> (b, b)) -> Flipping a -> (b, b) Source #

class Flippable f where Source #

Minimal complete definition

flipp

Methods

flipp :: f -> f Source #

Instances

Flippable Constraint Source # 
Flippable (Flipping x) Source # 

Methods

flipp :: Flipping x -> Flipping x Source #

Flippable (x, x) Source # 

Methods

flipp :: (x, x) -> (x, x) Source #

flipInjectF :: Functor f => Flipping (f a) -> f (Flipping a) Source #

eitherBranchBoth :: (b -> b -> Bool) -> Either a b -> Either a b -> Flipping (Either a b) Source #

Combine two Eithers, using the provided function to choose between two Rights. Always choose the first Left.

ixZipWith :: (Ixed s, TraversableWithIndex (Index s) t) => (a -> Maybe (IxValue s) -> b) -> t a -> s -> t b Source #

overWith :: Lens' s a -> ((a, a) -> (a, a)) -> (s, s) -> (s, s) Source #

findOrInsert :: Key -> a -> IntMap a -> (Maybe a, IntMap a) Source #

findOrInsert' :: Key -> a -> IntMap a -> (a, IntMap a) Source #

posMod :: Integral a => a -> a -> a Source #

pairix :: Ixed m => (Index m, Index m) -> Traversal' m (IxValue m, IxValue m) Source #

pairOver :: (forall f. Functor f => (b -> f b) -> a -> f a) -> ((b, b) -> (b, b)) -> (a, a) -> (a, a) Source #

pairView :: (forall f. Functor f => (b -> f b) -> a -> f a) -> (a, a) -> (b, b) Source #

pairView' :: (forall f. Applicative f => (b -> f b) -> a -> f a) -> (a, a) -> Maybe (b, b) Source #

pairSet :: (forall f. Functor f => (b -> f b) -> a -> f a) -> (b, b) -> (a, a) -> (a, a) Source #

iixOver :: (forall f. Applicative f => k -> (b -> f b) -> a -> f a) -> ((b, b) -> (b, b)) -> (k, k) -> a -> a Source #

iixOver' :: Monad m => (forall f. Applicative f => k -> (b -> f b) -> a -> f a) -> ((b, b) -> m (b, b)) -> (k, k) -> a -> m a Source #

iixView :: (forall f. Applicative f => k -> (b -> f b) -> a -> f a) -> (k, k) -> a -> Maybe (b, b) Source #

liftMaybe :: Monad m => Maybe a -> MaybeT m a Source #

liftMaybe' :: Monad m => m a -> MaybeT m a Source #