How do I handle the Maybe result of at in Control.Lens.Indexed without a Monoid instance

对着背影说爱祢 提交于 2019-12-22 01:50:38

问题


I recently discovered the lens package on Hackage and have been trying to make use of it now in a small test project that might turn into a MUD/MUSH server one very distant day if I keep working on it.

Here is a minimized version of my code illustrating the problem I am facing right now with the at lenses used to access Key/Value containers (Data.Map.Strict in my case)

{-# LANGUAGE OverloadedStrings, GeneralizedNewtypeDeriving, TemplateHaskell #-}
module World where
import Control.Applicative ((<$>),(<*>), pure)
import Control.Lens
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as DM
import Data.Maybe
import Data.UUID
import Data.Text (Text)
import qualified Data.Text as T
import System.Random (Random, randomIO)

newtype RoomId = RoomId UUID deriving (Eq, Ord, Show, Read, Random)
newtype PlayerId = PlayerId UUID deriving (Eq, Ord, Show, Read, Random)

data Room =
  Room { _roomId :: RoomId 
       , _roomName :: Text
       , _roomDescription :: Text
       , _roomPlayers :: [PlayerId]
       } deriving (Eq, Ord, Show, Read)

makeLenses ''Room

data Player =
  Player { _playerId :: PlayerId
         , _playerDisplayName :: Text
         , _playerLocation :: RoomId
         } deriving (Eq, Ord, Show, Read)

makeLenses ''Player

data World =
  World { _worldRooms :: Map RoomId Room
        , _worldPlayers :: Map PlayerId Player
        } deriving (Eq, Ord, Show, Read)

makeLenses ''World

mkWorld :: IO World
mkWorld = do
  r1 <- Room <$> randomIO <*> (pure "The Singularity") <*> (pure "You are standing in the only place in the whole world") <*> (pure [])
  p1 <- Player <$> randomIO <*> (pure "testplayer1") <*> (pure $ r1^.roomId)
  let rooms = at (r1^.roomId) ?~ (set roomPlayers [p1^.playerId] r1) $ DM.empty
      players = at (p1^.playerId) ?~ p1 $ DM.empty in do
    return $ World rooms players

viewPlayerLocation :: World -> PlayerId -> RoomId
viewPlayerLocation world playerId=
  view (worldPlayers.at playerId.traverse.playerLocation) world  

Since rooms, players and similar objects are referenced all over the code I store them in my World state type as maps of Ids (newtyped UUIDs) to their data objects.

To retrieve those with lenses I need to handle the Maybe returned by the at lens (in case the key is not in the map this is Nothing) somehow. In my last line I tried to do this via traverse which does typecheck as long as the final result is an instance of Monoid but this is not generally the case. Right here it is not because playerLocation returns a RoomId which has no Monoid instance.

No instance for (Data.Monoid.Monoid RoomId)
  arising from a use of `traverse'
Possible fix:
  add an instance declaration for (Data.Monoid.Monoid RoomId)
In the first argument of `(.)', namely `traverse'
In the second argument of `(.)', namely `traverse . playerLocation'
In the second argument of `(.)', namely
  `at playerId . traverse . playerLocation'

Since the Monoid is required by traverse only because traverse generalizes to containers of sizes greater than one I was now wondering if there is a better way to handle this that does not require semantically nonsensical Monoid instances on all types possibly contained in one my objects I want to store in the map.

Or maybe I misunderstood the issue here completely and I need to use a completely different bit of the rather large lens package?


回答1:


If you have a Traversal and you want to get a Maybe for the first element, you can just use headOf instead of view, i.e.

viewPlayerLocation :: World -> PlayerId -> Maybe RoomId
viewPlayerLocation world playerId =
  headOf (worldPlayers.at playerId.traverse.playerLocation) world  

The infix version of headOf is called ^?. You can also use toListOf to get a list of all elements, and other functions depending on what you want to do. See the Control.Lens.Fold documentation.

A quick heuristic for which module to look for your functions in:

  • A Getter is a read-only view of exactly one value
  • A Lens is a read-write view of exactly one value
  • A Traversal is a read-write view of zero-or-more values
  • A Fold is a read-only view of zero-or-more values
  • A Setter is a write-only (well, modify-only) view of zero-or-more values (possibly uncountably many values, in fact)
  • An Iso is, well, an isomorphism -- a Lens that can go in either direction
  • Presumably you know when you're using an Indexed function, so you can look in the corresponding Indexed module

Think about what you're trying to do and what the most general module to put it in would be. :-) In this case you have a Traversal, but you're only trying to view, not modify, so the function you want is in .Fold. If you also had the guarantee that it was referring to exactly one value, it would be in .Getter.




回答2:


Short answer: the lens package is not magic.

Without telling me what the error or default is, you want to make:

viewPlayerLocation :: World -> PlayerId -> RoomId

You know two things, that

To retrieve those with lenses I need to handle the Maybe returned by the at lens

and

traverse which does typecheck as long as the final result is an instance of Monoid

With a Monoid you get mempty :: Monoid m => m as the default when the lookup fails.

What can fail: The PlayerId can not be in the _worldPlayers and the _playerLocation can not be in the _worldRooms.

So what should your code do if a lookup fails? Is this "impossible" ? If so, then use fromMaybe (error "impossible") :: Maybe a -> a to crash.

If it possible for the lookup to fail then is there a sane default? Perhaps return Maybe RoomId and let the caller decide?




回答3:


There is ^?! which frees you from calling fromMaybe.



来源:https://stackoverflow.com/questions/13434568/how-do-i-handle-the-maybe-result-of-at-in-control-lens-indexed-without-a-monoid

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!