module Screen.ProcessKeys where -- .Decide, for players import Input import Meeple.Operate import Screen.Check import Screen.Primitives import Terminal.Game import Lens.Micro.Platform processMovKeys :: HasScreen s => Input -> s -> Player -> Player processMovKeys KLeft _ p = agiMov p AGoW processMovKeys KRight _ p = agiMov p AGoE processMovKeys KUp s p | canClimb s (MPlayer p) = agiMov p AClimb & isClimbing .~ True | amGrounded s (MPlayer p) = jumpAct p processMovKeys KDown s p | canClimb s (MPlayer p) || canDescend s (MPlayer p) = agiMov p ADescend & isClimbing .~ True processMovKeys KSpace _ p = stopPlayer p processMovKeys _ _ p = p jumpAct :: Player -> Player jumpAct p | ca == AGoW = p & action .~ AJumpL | ca == AGoE = p & action .~ AJumpR | otherwise = p & action .~ AJumpX where ca = p ^. action ----------------- -- ANCILLARIES -- ----------------- -- ~= Sierra AGI movement, tap once to start moving, tap again to stop. agiMov :: Player -> PAction -> Player agiMov p nc | oc == nc = stop p | otherwise = p & action .~ nc where oc = p ^. action stop :: Player -> Player stop pw = pw & stopSpeed -- xxx [refactor] questo andrebbe in -- Decide & action .~ ANoAction stopSpeed | elem nc [AClimb, ADescend] = speed . _1 .~ 0 | otherwise = speed . _2 .~ 0 -- stop him in any case stopPlayer :: Player -> Player stopPlayer p = agiMov p (p ^. action)