mmm-0.1.0.0: Minecraft 1.21.4 implementation in Haskell
Copyright(c) axionbuster 2025
LicenseBSD-3-Clause
Safe HaskellNone
LanguageGHC2021

M.Collision.Pure

Description

Core collision detection primitives and algorithms in pure form. Provides AABB collision testing, shape interfaces, and hit detection utilities.

Synopsis

Documentation

class Shape (s :: Type -> Type) where Source #

an AABB type class used for collision detection and resolution

Minimal complete definition

intersecting, crossing, hitting, translate, corners, tomanyboxes

Methods

intersecting :: (Fractional a, Ord a) => s a -> s a -> Bool Source #

check if two shapes intersect

crossing :: RealFloat a => V3 a -> V3 a -> s a -> Hit a Source #

check if a ray will hit the shape and return the hit data

hitting :: RealFloat a => V3 a -> s a -> s a -> Hit a Source #

check if the first shape will collide into the second shape if it moves with the given displacement

translate :: Num a => V3 a -> s a -> s a Source #

translate the shape by the given displacement

corners :: (Fractional a, Ord a) => s a -> V2 (V3 a) Source #

the locations of the lower and higher corners of the shape respectively

tomanyboxes :: s a -> ManyBoxes [] a Source #

convert a Shape to a ManyBoxes of Boxes with a list container, which is a canonical form for ManyBoxes

scenter :: (Fractional a, Ord a) => s a -> V3 a Source #

the center of the shape

sdimensions :: (Fractional a, Ord a) => s a -> V3 a Source #

the dimensions of the shape

Instances

Instances details
Shape Box Source # 
Instance details

Defined in M.Collision.Pure

Methods

intersecting :: (Fractional a, Ord a) => Box a -> Box a -> Bool Source #

crossing :: RealFloat a => V3 a -> V3 a -> Box a -> Hit a Source #

hitting :: RealFloat a => V3 a -> Box a -> Box a -> Hit a Source #

translate :: Num a => V3 a -> Box a -> Box a Source #

corners :: (Fractional a, Ord a) => Box a -> V2 (V3 a) Source #

tomanyboxes :: Box a -> ManyBoxes [] a Source #

scenter :: (Fractional a, Ord a) => Box a -> V3 a Source #

sdimensions :: (Fractional a, Ord a) => Box a -> V3 a Source #

Shape SomeShape1 Source # 
Instance details

Defined in M.Collision.Pure

Methods

intersecting :: (Fractional a, Ord a) => SomeShape1 a -> SomeShape1 a -> Bool Source #

crossing :: RealFloat a => V3 a -> V3 a -> SomeShape1 a -> Hit a Source #

hitting :: RealFloat a => V3 a -> SomeShape1 a -> SomeShape1 a -> Hit a Source #

translate :: Num a => V3 a -> SomeShape1 a -> SomeShape1 a Source #

corners :: (Fractional a, Ord a) => SomeShape1 a -> V2 (V3 a) Source #

tomanyboxes :: SomeShape1 a -> ManyBoxes [] a Source #

scenter :: (Fractional a, Ord a) => SomeShape1 a -> V3 a Source #

sdimensions :: (Fractional a, Ord a) => SomeShape1 a -> V3 a Source #

(Functor f, Foldable f) => Shape (ManyBoxes f) Source # 
Instance details

Defined in M.Collision.Pure

Methods

intersecting :: (Fractional a, Ord a) => ManyBoxes f a -> ManyBoxes f a -> Bool Source #

crossing :: RealFloat a => V3 a -> V3 a -> ManyBoxes f a -> Hit a Source #

hitting :: RealFloat a => V3 a -> ManyBoxes f a -> ManyBoxes f a -> Hit a Source #

translate :: Num a => V3 a -> ManyBoxes f a -> ManyBoxes f a Source #

corners :: (Fractional a, Ord a) => ManyBoxes f a -> V2 (V3 a) Source #

tomanyboxes :: ManyBoxes f a -> ManyBoxes [] a Source #

scenter :: (Fractional a, Ord a) => ManyBoxes f a -> V3 a Source #

sdimensions :: (Fractional a, Ord a) => ManyBoxes f a -> V3 a Source #

data SomeShape1 a Source #

existential Shape type but where numeric type is erased

see also: castshape1

Constructors

(Typeable (s a), Show (s a), Shape s) => SomeShape1 (s a) 

Instances

Instances details
Shape SomeShape1 Source # 
Instance details

Defined in M.Collision.Pure

Methods

intersecting :: (Fractional a, Ord a) => SomeShape1 a -> SomeShape1 a -> Bool Source #

crossing :: RealFloat a => V3 a -> V3 a -> SomeShape1 a -> Hit a Source #

hitting :: RealFloat a => V3 a -> SomeShape1 a -> SomeShape1 a -> Hit a Source #

translate :: Num a => V3 a -> SomeShape1 a -> SomeShape1 a Source #

corners :: (Fractional a, Ord a) => SomeShape1 a -> V2 (V3 a) Source #

tomanyboxes :: SomeShape1 a -> ManyBoxes [] a Source #

scenter :: (Fractional a, Ord a) => SomeShape1 a -> V3 a Source #

sdimensions :: (Fractional a, Ord a) => SomeShape1 a -> V3 a Source #

Show (SomeShape1 a) Source # 
Instance details

Defined in M.Collision.Pure

data Hit a Source #

a collision resolution data type

no hit is represented by a hit at infinity (other fields are unspecified)

Constructors

Hit 

Fields

  • hittime :: !a

    proportion of move completed in [0, 1]

  • hitwhere :: !(V3 a)

    the point of collision

    if you're using Box, this is the center of the box

  • hitnorm :: !(V3 a)

    normal vector of the surface hit

    a signum vector, so each component is either -1, 0, or 1

Instances

Instances details
Functor Hit Source # 
Instance details

Defined in M.Collision.Pure

Methods

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

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

Data a => Data (Hit a) Source # 
Instance details

Defined in M.Collision.Pure

Methods

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

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

toConstr :: Hit a -> Constr #

dataTypeOf :: Hit a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (Hit a) Source # 
Instance details

Defined in M.Collision.Pure

Associated Types

type Rep (Hit a) 
Instance details

Defined in M.Collision.Pure

type Rep (Hit a) = D1 ('MetaData "Hit" "M.Collision.Pure" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (C1 ('MetaCons "Hit" 'PrefixI 'True) (S1 ('MetaSel ('Just "hittime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: (S1 ('MetaSel ('Just "hitwhere") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V3 a)) :*: S1 ('MetaSel ('Just "hitnorm") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V3 a)))))

Methods

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

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

Show a => Show (Hit a) Source # 
Instance details

Defined in M.Collision.Pure

Methods

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

show :: Hit a -> String #

showList :: [Hit a] -> ShowS #

Eq a => Eq (Hit a) Source # 
Instance details

Defined in M.Collision.Pure

Methods

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

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

Hashable a => Hashable (Hit a) Source # 
Instance details

Defined in M.Collision.Pure

Methods

hashWithSalt :: Int -> Hit a -> Int

hash :: Hit a -> Int

type Rep (Hit a) Source # 
Instance details

Defined in M.Collision.Pure

type Rep (Hit a) = D1 ('MetaData "Hit" "M.Collision.Pure" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (C1 ('MetaCons "Hit" 'PrefixI 'True) (S1 ('MetaSel ('Just "hittime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: (S1 ('MetaSel ('Just "hitwhere") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V3 a)) :*: S1 ('MetaSel ('Just "hitnorm") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V3 a)))))

newtype Hit' a Source #

internal newtype used with Min to find the closest hit

Constructors

Hit' 

Fields

Instances

Instances details
(Fractional a, Num a) => Bounded (Hit' a) Source # 
Instance details

Defined in M.Collision.Pure

Methods

minBound :: Hit' a #

maxBound :: Hit' a #

Show a => Show (Hit' a) Source # 
Instance details

Defined in M.Collision.Pure

Methods

showsPrec :: Int -> Hit' a -> ShowS #

show :: Hit' a -> String #

showList :: [Hit' a] -> ShowS #

Eq a => Eq (Hit' a) Source # 
Instance details

Defined in M.Collision.Pure

Methods

(==) :: Hit' a -> Hit' a -> Bool #

(/=) :: Hit' a -> Hit' a -> Bool #

Ord a => Ord (Hit' a) Source # 
Instance details

Defined in M.Collision.Pure

Methods

compare :: Hit' a -> Hit' a -> Ordering #

(<) :: Hit' a -> Hit' a -> Bool #

(<=) :: Hit' a -> Hit' a -> Bool #

(>) :: Hit' a -> Hit' a -> Bool #

(>=) :: Hit' a -> Hit' a -> Bool #

max :: Hit' a -> Hit' a -> Hit' a #

min :: Hit' a -> Hit' a -> Hit' a #

Hashable a => Hashable (Hit' a) Source # 
Instance details

Defined in M.Collision.Pure

Methods

hashWithSalt :: Int -> Hit' a -> Int

hash :: Hit' a -> Int

data Box a Source #

a box in 3D space, located either relatively or absolutely

Constructors

Box 

Fields

  • dimensions :: !(V3 a)

    the dimensions of the box

  • center :: !(V3 a)

    the center of the box

Bundled Patterns

pattern Box' :: Fractional a => V3 a -> V3 a -> Box a

bidrectional pattern for Box but with corner locations (low to high)

you can use the locorner' and hicorner' patterns to extract the corners, respectively

Instances

Instances details
Applicative Box Source # 
Instance details

Defined in M.Collision.Pure

Methods

pure :: a -> Box a #

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

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

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

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

Functor Box Source # 
Instance details

Defined in M.Collision.Pure

Methods

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

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

Shape Box Source # 
Instance details

Defined in M.Collision.Pure

Methods

intersecting :: (Fractional a, Ord a) => Box a -> Box a -> Bool Source #

crossing :: RealFloat a => V3 a -> V3 a -> Box a -> Hit a Source #

hitting :: RealFloat a => V3 a -> Box a -> Box a -> Hit a Source #

translate :: Num a => V3 a -> Box a -> Box a Source #

corners :: (Fractional a, Ord a) => Box a -> V2 (V3 a) Source #

tomanyboxes :: Box a -> ManyBoxes [] a Source #

scenter :: (Fractional a, Ord a) => Box a -> V3 a Source #

sdimensions :: (Fractional a, Ord a) => Box a -> V3 a Source #

Data a => Data (Box a) Source # 
Instance details

Defined in M.Collision.Pure

Methods

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

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

toConstr :: Box a -> Constr #

dataTypeOf :: Box a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (Box a) Source # 
Instance details

Defined in M.Collision.Pure

Associated Types

type Rep (Box a) 
Instance details

Defined in M.Collision.Pure

type Rep (Box a) = D1 ('MetaData "Box" "M.Collision.Pure" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (C1 ('MetaCons "Box" 'PrefixI 'True) (S1 ('MetaSel ('Just "dimensions") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V3 a)) :*: S1 ('MetaSel ('Just "center") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V3 a))))

Methods

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

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

Show a => Show (Box a) Source # 
Instance details

Defined in M.Collision.Pure

Methods

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

show :: Box a -> String #

showList :: [Box a] -> ShowS #

Eq a => Eq (Box a) Source # 
Instance details

Defined in M.Collision.Pure

Methods

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

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

Hashable a => Hashable (Box a) Source # 
Instance details

Defined in M.Collision.Pure

Methods

hashWithSalt :: Int -> Box a -> Int

hash :: Box a -> Int

type Rep (Box a) Source # 
Instance details

Defined in M.Collision.Pure

type Rep (Box a) = D1 ('MetaData "Box" "M.Collision.Pure" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (C1 ('MetaCons "Box" 'PrefixI 'True) (S1 ('MetaSel ('Just "dimensions") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V3 a)) :*: S1 ('MetaSel ('Just "center") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V3 a))))

newtype ManyBoxes (f :: Type -> Type) a Source #

a newtype over a Foldable Functor container of Boxes

the low and high corners are those of the smallest bounding box

Constructors

ManyBoxes (f (Box a)) 

Instances

Instances details
Functor f => Functor (ManyBoxes f) Source # 
Instance details

Defined in M.Collision.Pure

Methods

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

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

(Functor f, Foldable f) => Shape (ManyBoxes f) Source # 
Instance details

Defined in M.Collision.Pure

Methods

intersecting :: (Fractional a, Ord a) => ManyBoxes f a -> ManyBoxes f a -> Bool Source #

crossing :: RealFloat a => V3 a -> V3 a -> ManyBoxes f a -> Hit a Source #

hitting :: RealFloat a => V3 a -> ManyBoxes f a -> ManyBoxes f a -> Hit a Source #

translate :: Num a => V3 a -> ManyBoxes f a -> ManyBoxes f a Source #

corners :: (Fractional a, Ord a) => ManyBoxes f a -> V2 (V3 a) Source #

tomanyboxes :: ManyBoxes f a -> ManyBoxes [] a Source #

scenter :: (Fractional a, Ord a) => ManyBoxes f a -> V3 a Source #

sdimensions :: (Fractional a, Ord a) => ManyBoxes f a -> V3 a Source #

(Typeable f, Typeable a, Data (f (Box a))) => Data (ManyBoxes f a) Source # 
Instance details

Defined in M.Collision.Pure

Methods

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

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

toConstr :: ManyBoxes f a -> Constr #

dataTypeOf :: ManyBoxes f a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (ManyBoxes f a) Source # 
Instance details

Defined in M.Collision.Pure

Associated Types

type Rep (ManyBoxes f a) 
Instance details

Defined in M.Collision.Pure

type Rep (ManyBoxes f a) = D1 ('MetaData "ManyBoxes" "M.Collision.Pure" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'True) (C1 ('MetaCons "ManyBoxes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (Box a)))))

Methods

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

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

Show (f (Box a)) => Show (ManyBoxes f a) Source # 
Instance details

Defined in M.Collision.Pure

Methods

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

show :: ManyBoxes f a -> String #

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

Eq (f (Box a)) => Eq (ManyBoxes f a) Source # 
Instance details

Defined in M.Collision.Pure

Methods

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

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

Ord (f (Box a)) => Ord (ManyBoxes f a) Source # 
Instance details

Defined in M.Collision.Pure

Methods

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

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

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

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

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

max :: ManyBoxes f a -> ManyBoxes f a -> ManyBoxes f a #

min :: ManyBoxes f a -> ManyBoxes f a -> ManyBoxes f a #

Hashable (f (Box a)) => Hashable (ManyBoxes f a) Source # 
Instance details

Defined in M.Collision.Pure

Methods

hashWithSalt :: Int -> ManyBoxes f a -> Int

hash :: ManyBoxes f a -> Int

type Rep (ManyBoxes f a) Source # 
Instance details

Defined in M.Collision.Pure

type Rep (ManyBoxes f a) = D1 ('MetaData "ManyBoxes" "M.Collision.Pure" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'True) (C1 ('MetaCons "ManyBoxes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (Box a)))))

type ManyBoxes_ a = ManyBoxes [] a Source #

a type alias for a list of Boxes (canonical form for ManyBoxes)

_dimensions :: forall a f. Functor f => (V3 a -> f (V3 a)) -> Box a -> f (Box a) Source #

Lens for the dimensions of the box

_center :: forall a f. Functor f => (V3 a -> f (V3 a)) -> Box a -> f (Box a) Source #

Lens for the center of the box

_lcorner :: Fractional a => Lens' (Box a) (V3 a) Source #

Lens for the lower corner of the box

_hcorner :: Fractional a => Lens' (Box a) (V3 a) Source #

Lens for the higher corner of the box

hitin01 :: (Num a, Ord a) => Hit a -> Bool Source #

check if the hit time is in [0, 1]

infhit :: Fractional a => Hit a Source #

a hit at infinity

boxfromcorners Source #

Arguments

:: Fractional a 
=> V3 a

low corner

-> V3 a

high corner

-> Box a

the box

a box from the low and high corners

castshape1 :: Typeable b => SomeShape1 a -> Maybe b Source #

cast a SomeShape1 to a specific type

boxzero :: Num a => Box a Source #

a box with zero dimensions and center

hicorner :: Fractional a => Box a -> V3 a Source #

the location of the higher corner of the box

hicorner' :: Fractional a => Box a -> V3 a Source #

locorner :: Fractional a => Box a -> V3 a Source #

the location of the lower corner of the box

locorner' :: Fractional a => Box a -> V3 a Source #

shicorner :: (Shape s, Fractional a, Ord a) => s a -> V3 a Source #

the upper corner of a shape

slocorner :: (Shape s, Fractional a, Ord a) => s a -> V3 a Source #

the lower corner of a shape