[Haskell-beginners] Very little (golfing) question...

David McBride toad3k at gmail.com
Thu Jul 26 00:27:11 CEST 2012


This is marginally clearer, but not all that great.

import Data.List as L
import Control.Monad.State
import Data.Maybe (isJust)

data PlayerInfo = PlayerInfo {
  playerNumber :: Integer
}

instance Eq PlayerInfo where
  p1 == p2 = playerNumber p1 == playerNumber p2

data Game = Game {
  players :: [PlayerInfo]
}

addPlayer newPlayer = do
  exists <- fmap (isJust . find (==newPlayer)) $ gets players
  when exists $ gets players >>= \oldPlayers -> modify (\game -> game
{ players = newPlayer:oldPlayers })
  return exists

So, add an Eq instance to players so that you can just compare them
simply without deconstructing them all the time.

However, if you were to give an Ord instance to players, you could
replace lists with sets, which will allow you to insert without caring
whether the player is already in the set.  If you are dead set on
getting back a boolean, then you'll still have to check for existence
with member, so you won't gain much in brevity.  But if you weren't,
you could shorten it considerably to:

import Control.Monad.State
import Data.Set as S

data PlayerInfo = PlayerInfo {
  playerNumber :: Integer
} deriving Ord

instance Eq PlayerInfo where
  p1 == p2 = playerNumber p1 == playerNumber p2

data Game = Game {
  players :: Set PlayerInfo
}

addPlayer newPlayer = modify $
  \game@(Game { players = oldPlayers }) -> game { players = S.insert
newPlayer oldPlayers }




On Wed, Jul 25, 2012 at 5:02 PM, Corentin Dupont
<corentin.dupont at gmail.com> wrote:
>
> Hi,
> I always write functions like this:
>
> addPlayer :: PlayerInfo -> State Game Bool
> addPlayer pi@(PlayerInfo {playerNumber = pn}) = do
>     pls <- gets players
>     case find (\(PlayerInfo {playerNumber = myPn}) -> pn == myPn) pls of
>         Nothing -> do
>             modify (\game -> game { players = pi : pls})
>             return True
>         otherwise -> return False
>
> It simply adds a new PlayerInfo to a list contained in Game, with the
> condition that it doesn't exists already.
> Do you see a more elegant way to do this?
>
> Best,
> Corentin
>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



More information about the Beginners mailing list