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

M.Collision.Effectful

Description

Provides the core collision detection and resolution system with effects. Handles block-based collision detection, movement resolution, and ground contact states.

Parts

  1. The GetBlock effect
  2. The Resolve data type and resolve function (the main part)
  3. The NewlyTouchingGround data type and updonground function

Usage

  1. Use getblock to get a block's shape at integer coordinates
  2. Use resolve to detect and resolve collision
  3. Use updonground to update the on-ground status (from #2)
Synopsis

Documentation

data GetBlock (f :: Type -> Type) a (b :: Type -> Type) c where Source #

get a block's shape at integer coordinates (dynamic effect)

Constructors

GetBlock :: forall (f :: Type -> Type) a (b :: Type -> Type). !(V3 Int) -> GetBlock f a b (Maybe (f a))

get a block's shape at integer coordinates

Instances

Instances details
type DispatchOf (GetBlock f a) Source # 
Instance details

Defined in M.Collision.Effectful

type DispatchOf (GetBlock f a) = 'Dynamic

getblock Source #

Arguments

:: forall f a (ef :: [Effect]). (HasCallStack, GetBlock f a :> ef) 
=> V3 Int

integer coordinates

-> Eff ef (Maybe (f a))

if (relevant) block exists, return its shape

what block is "relevant" is up to the implementation

get a block's shape at integer coordinates

data Resolve a Source #

collision resolution data type

Constructors

Resolve 

Fields

Instances

Instances details
Functor Resolve Source # 
Instance details

Defined in M.Collision.Effectful

Methods

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

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

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

Defined in M.Collision.Effectful

Methods

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

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

toConstr :: Resolve a -> Constr #

dataTypeOf :: Resolve a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (Resolve a) Source # 
Instance details

Defined in M.Collision.Effectful

Associated Types

type Rep (Resolve a) 
Instance details

Defined in M.Collision.Effectful

type Rep (Resolve a) = D1 ('MetaData "Resolve" "M.Collision.Effectful" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (C1 ('MetaCons "Resolve" 'PrefixI 'True) (S1 ('MetaSel ('Just "respos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V3 a)) :*: (S1 ('MetaSel ('Just "resdis") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V3 a)) :*: S1 ('MetaSel ('Just "restou") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NewlyTouchingGround))))

Methods

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

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

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

Defined in M.Collision.Effectful

Methods

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

show :: Resolve a -> String #

showList :: [Resolve a] -> ShowS #

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

Defined in M.Collision.Effectful

Methods

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

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

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

Defined in M.Collision.Effectful

Methods

hashWithSalt :: Int -> Resolve a -> Int

hash :: Resolve a -> Int

type Rep (Resolve a) Source # 
Instance details

Defined in M.Collision.Effectful

type Rep (Resolve a) = D1 ('MetaData "Resolve" "M.Collision.Effectful" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'False) (C1 ('MetaCons "Resolve" 'PrefixI 'True) (S1 ('MetaSel ('Just "respos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V3 a)) :*: (S1 ('MetaSel ('Just "resdis") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V3 a)) :*: S1 ('MetaSel ('Just "restou") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NewlyTouchingGround))))

resolve Source #

Arguments

:: forall s n (ef :: [Effect]). (Shape s, RealFloat n, Epsilon n, Typeable n, GetBlock s n :> ef) 
=> s n

shape of the object who is moving

-> V3 n

attempted displacement

-> Eff ef (Resolve n)

new resolution

unless it got stuck, the new displacement should be zero

detect and resolve collision

_respos :: forall a f. Functor f => (V3 a -> f (V3 a)) -> Resolve a -> f (Resolve a) Source #

lens for Resolve position

_resdis :: forall a f. Functor f => (V3 a -> f (V3 a)) -> Resolve a -> f (Resolve a) Source #

lens for Resolve displacement

_restou :: forall a f. Functor f => (NewlyTouchingGround -> f NewlyTouchingGround) -> Resolve a -> f (Resolve a) Source #

lens for Resolve newly touching ground

newtype NewlyTouchingGround Source #

newly touching ground?

  • LT means it taking off from the ground
  • EQ means it should maintain the previous state
  • GT means it landing on the ground

Constructors

NewlyTouchingGround 

Instances

Instances details
Data NewlyTouchingGround Source # 
Instance details

Defined in M.Collision.Effectful

Methods

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

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

toConstr :: NewlyTouchingGround -> Constr #

dataTypeOf :: NewlyTouchingGround -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded NewlyTouchingGround Source # 
Instance details

Defined in M.Collision.Effectful

Enum NewlyTouchingGround Source # 
Instance details

Defined in M.Collision.Effectful

Generic NewlyTouchingGround Source # 
Instance details

Defined in M.Collision.Effectful

Associated Types

type Rep NewlyTouchingGround 
Instance details

Defined in M.Collision.Effectful

type Rep NewlyTouchingGround = D1 ('MetaData "NewlyTouchingGround" "M.Collision.Effectful" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'True) (C1 ('MetaCons "NewlyTouchingGround" 'PrefixI 'True) (S1 ('MetaSel ('Just "newonground") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ordering)))
Show NewlyTouchingGround Source # 
Instance details

Defined in M.Collision.Effectful

Eq NewlyTouchingGround Source # 
Instance details

Defined in M.Collision.Effectful

Ord NewlyTouchingGround Source # 
Instance details

Defined in M.Collision.Effectful

Hashable NewlyTouchingGround Source # 
Instance details

Defined in M.Collision.Effectful

type Rep NewlyTouchingGround Source # 
Instance details

Defined in M.Collision.Effectful

type Rep NewlyTouchingGround = D1 ('MetaData "NewlyTouchingGround" "M.Collision.Effectful" "mmm-0.1.0.0-oCDsNp3EBL2JzoyA6cTai" 'True) (C1 ('MetaCons "NewlyTouchingGround" 'PrefixI 'True) (S1 ('MetaSel ('Just "newonground") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ordering)))

updonground :: NewlyTouchingGround -> Bool -> Bool Source #

'update' the on-ground status