I have no MonadErr instances

This commit is contained in:
nek0 2019-01-06 03:52:43 +01:00
parent b0faee7a69
commit d107b6f76c
4 changed files with 31 additions and 29 deletions

View File

@ -337,7 +337,7 @@ playerInteract (MsgMouseButton _ _ SDL.Pressed _ SDL.ButtonRight _ m) = do
return $ unchanged return $ unchanged
{ rot = Set $ fromMaybe rot' ndir { rot = Set $ fromMaybe rot' ndir
} }
[(ppos, pdir, pent)] <- efor allEnts $ do pdata <- efor allEnts $ do
with player with player
with pos with pos
with rot with rot
@ -345,6 +345,7 @@ playerInteract (MsgMouseButton _ _ SDL.Pressed _ SDL.ButtonRight _ m) = do
rot' <- query rot rot' <- query rot
ent <- queryEnt ent <- queryEnt
return (pos', rot', ent) return (pos', rot', ent)
let (ppos, pdir, pent) = head pdata
mrelEnts <- efor allEnts $ do mrelEnts <- efor allEnts $ do
with pos with pos
with objAccess with objAccess
@ -376,7 +377,7 @@ playerInteract2 :: ActionMessage -> Affection UserData ()
playerInteract2 (ActionMessage Activate _) = do playerInteract2 (ActionMessage Activate _) = do
ud <- getAffection ud <- getAffection
(nws, _) <- yieldSystemT (worldState ud) $ do (nws, _) <- yieldSystemT (worldState ud) $ do
[(ppos, pdir, pent)] <- efor allEnts $ do pdata <- efor allEnts $ do
with player with player
with pos with pos
with rot with rot
@ -384,6 +385,7 @@ playerInteract2 (ActionMessage Activate _) = do
rot' <- query rot rot' <- query rot
ent <- queryEnt ent <- queryEnt
return (pos', rot', ent) return (pos', rot', ent)
let (ppos, pdir, pent) = head pdata
mrelEnts <- efor allEnts $ do mrelEnts <- efor allEnts $ do
with pos with pos
with objAccess with objAccess
@ -421,7 +423,7 @@ drawMap = do
_ -> do _ -> do
dt <- getDelta dt <- getDelta
(_, (playerPos, posanims, posActions)) <- yieldSystemT (worldState ud) $ do (_, (playerPos, posanims, posActions)) <- yieldSystemT (worldState ud) $ do
[pc] <- efor allEnts $ do pc <- efor allEnts $ do
with player with player
with pos with pos
query pos query pos
@ -445,7 +447,7 @@ drawMap = do
let maxt = actionTime t s let maxt = actionTime t s
ttl <- query objStateTime ttl <- query objStateTime
return (pos', pa, realToFrac (1 - ttl / maxt)) return (pos', pa, realToFrac (1 - ttl / maxt))
return (pc, posanims, posActions) return (head pc, posanims, posActions)
let V2 pr pc = playerPos let V2 pr pc = playerPos
mat = imgMat (stateData ud) mat = imgMat (stateData ud)
cols = fromIntegral (ncols mat) cols = fromIntegral (ncols mat)

View File

@ -82,7 +82,7 @@ buildFloorMap inGraph =
(floor r + 2, floor c + 2) amat (floor r + 2, floor c + 2) amat
) )
emptyFloor emptyFloor
floorGraph (vertexList floorGraph)
, fmap (\n -> n { mmPos = (+ 2) <$> mmPos n} ) floorGraph , fmap (\n -> n { mmPos = (+ 2) <$> mmPos n} ) floorGraph
) )
where where

View File

@ -166,7 +166,7 @@ updateNPCs imgmat ws rp dt = do
, vel = Set $ V2 0 0 , vel = Set $ V2 0 0
})) }))
mapM_ (\(oent, npcent, future) -> do mapM_ (\(oent, npcent, future) -> do
[mts] <- efor (anEnt oent) $ do mts <- efor (anEnt oent) $ do
with objType with objType
with objState with objState
moub <- queryMaybe objUsedBy moub <- queryMaybe objUsedBy
@ -182,8 +182,8 @@ updateNPCs imgmat ws rp dt = do
(\(t, s) -> (\(t, s) ->
setEntity oent =<< objectTransition t s False oent (Just npcent) setEntity oent =<< objectTransition t s False oent (Just npcent)
) )
mts (head mts)
[mntns] <- efor (anEnt oent) $ do mntns <- efor (anEnt oent) $ do
with objType with objType
with objState with objState
moub <- queryMaybe objUsedBy moub <- queryMaybe objUsedBy
@ -195,7 +195,7 @@ updateNPCs imgmat ws rp dt = do
then return $ Just (otyp, ostat) then return $ Just (otyp, ostat)
else return Nothing else return Nothing
emap (anEnt npcent) $ do emap (anEnt npcent) $ do
let ttl = case mntns of let ttl = case head mntns of
Just (nt, ns) -> actionTime nt ns Just (nt, ns) -> actionTime nt ns
Nothing -> 1 Nothing -> 1
return unchanged return unchanged

View File

@ -29,18 +29,18 @@ instance ObjectAction ObjType ObjState where
return unchanged return unchanged
{ objStateTime = Set (ttl - dt) { objStateTime = Set (ttl - dt)
} }
[trans] <- efor (anEnt ent) $ do trans <- efor (anEnt ent) $ do
mttl <- queryMaybe objStateTime mttl <- queryMaybe objStateTime
case mttl of case mttl of
Nothing -> return False Nothing -> return False
Just ttl -> return (ttl < 0) Just ttl -> return (ttl < 0)
when trans (setEntity ent =<< objectTransition t s False ent Nothing) when (head trans) (setEntity ent =<< objectTransition t s False ent Nothing)
objectAction dt t@ObjComputer s@"on" ent = do objectAction dt t@ObjComputer s@"on" ent = do
[pent] <- efor (anEnt ent) $ do pent <- efor (anEnt ent) $ do
with objUsedBy with objUsedBy
query objUsedBy query objUsedBy
vls <- efor (anEnt pent) $ do vls <- efor (anEnt $ head pent) $ do
with player with player
with vel with vel
query vel query vel
@ -57,7 +57,7 @@ instance ObjectAction ObjType ObjState where
return unchanged return unchanged
{ objStateTime = Set (ttl - dt) { objStateTime = Set (ttl - dt)
} }
[trans] <- efor (anEnt ent) $ do trans <- efor (anEnt ent) $ do
mttl <- queryMaybe objStateTime mttl <- queryMaybe objStateTime
case mttl of case mttl of
Nothing -> return Nothing Nothing -> return Nothing
@ -72,13 +72,13 @@ instance ObjectAction ObjType ObjState where
maybe maybe
(return ()) (return ())
(\tpa -> setEntity ent =<< objectTransition t s tpa ent Nothing) (\tpa -> setEntity ent =<< objectTransition t s tpa ent Nothing)
trans (head trans)
objectAction dt t@ObjComputer s@"hack" ent = do objectAction dt t@ObjComputer s@"hack" ent = do
[aent] <- efor (anEnt ent) $ do aent <- efor (anEnt ent) $ do
with objUsedBy with objUsedBy
query objUsedBy query objUsedBy
vls <- efor (anEnt aent) $ do vls <- efor (anEnt $ head aent) $ do
with player with player
with vel with vel
query vel query vel
@ -94,7 +94,7 @@ instance ObjectAction ObjType ObjState where
return unchanged return unchanged
{ objStateTime = Set (ttl - dt) { objStateTime = Set (ttl - dt)
} }
[trans] <- efor (anEnt ent) $ do trans <- efor (anEnt ent) $ do
mttl <- queryMaybe objStateTime mttl <- queryMaybe objStateTime
case mttl of case mttl of
Nothing -> return Nothing Nothing -> return Nothing
@ -107,12 +107,12 @@ instance ObjectAction ObjType ObjState where
maybe maybe
(return ()) (return ())
(\tpa -> setEntity ent =<< objectTransition t s tpa ent Nothing) (\tpa -> setEntity ent =<< objectTransition t s tpa ent Nothing)
trans (head trans)
objectAction _ _ _ _ = return () objectAction _ _ _ _ = return ()
objectTransition ObjCopier "idle" playerActivated ent (Just aent) = do objectTransition ObjCopier "idle" playerActivated ent (Just aent) = do
[e] <- efor (anEnt ent) $ do e <- efor (anEnt ent) $ do
let nstat = AnimState let nstat = AnimState
(AnimId "copier" "copy" N) (AnimId "copier" "copy" N)
0 0
@ -123,10 +123,10 @@ instance ObjectAction ObjType ObjState where
, objPlayerActivated = Set playerActivated , objPlayerActivated = Set playerActivated
, anim = Set nstat , anim = Set nstat
} }
return e return (head e)
objectTransition ObjCopier "copying" _ ent _ = do objectTransition ObjCopier "copying" _ ent _ = do
[e] <- efor (anEnt ent) $ do e <- efor (anEnt ent) $ do
ttl <- query objStateTime ttl <- query objStateTime
if ttl < 0 if ttl < 0
then do then do
@ -142,10 +142,10 @@ instance ObjectAction ObjType ObjState where
, objUsedBy = Unset , objUsedBy = Unset
} }
else return unchanged else return unchanged
return e return (head e)
objectTransition ObjComputer "off" pa ent (Just aent) = do objectTransition ObjComputer "off" pa ent (Just aent) = do
[e] <- efor (anEnt ent) $ do e <- efor (anEnt ent) $ do
solved <- queryMaybe objSolved solved <- queryMaybe objSolved
if pa if pa
then if not (fromMaybe False solved) then if not (fromMaybe False solved)
@ -182,10 +182,10 @@ instance ObjectAction ObjType ObjState where
, objPlayerActivated = Set False , objPlayerActivated = Set False
, objUsedBy = Set aent , objUsedBy = Set aent
} }
return e return (head e)
objectTransition ObjComputer "on" _ ent _ = do objectTransition ObjComputer "on" _ ent _ = do
[e] <- efor (anEnt ent) $ do e <- efor (anEnt ent) $ do
let nstat = AnimState let nstat = AnimState
(AnimId "computer" "off" N) (AnimId "computer" "off" N)
0 0
@ -197,12 +197,12 @@ instance ObjectAction ObjType ObjState where
, objStateTime = Unset , objStateTime = Unset
, objUsedBy = Unset , objUsedBy = Unset
} }
return e return (head e)
objectTransition ObjComputer "hack" pa ent _ = objectTransition ObjComputer "hack" pa ent _ =
if pa if pa
then do then do
[e] <- efor (anEnt ent) $ do e <- efor (anEnt ent) $ do
let nstat = AnimState let nstat = AnimState
(AnimId "computer" "off" N) (AnimId "computer" "off" N)
0 0
@ -216,7 +216,7 @@ instance ObjectAction ObjType ObjState where
, objUsedBy = Unset , objUsedBy = Unset
, objSolved = if pa then Set (ost < 0) else Keep , objSolved = if pa then Set (ost < 0) else Keep
} }
return e return (head e)
else return unchanged else return unchanged
objectTransition _ _ _ _ _ = return unchanged objectTransition _ _ _ _ _ = return unchanged