[Haskell-beginners] Re: Re: Converting an imperative program to
haskell
Maciej Piechotka
uzytkownik2 at gmail.com
Thu Apr 29 20:43:47 EDT 2010
On Thu, 2010-04-29 at 14:49 -0700, Hein Hundal wrote:
> --- On Thu, 4/29/10, Maciej Piechotka <uzytkownik2 at gmail.com> wrote:
> > Hein Hundal wrote:
> > >
> > > I figured I should try a larger program
> > in Haskell, so I am
> > > converting one of my Mathematica programs, a simulator
> > for the
> > > card game Dominion, over to Haskell. Most of
> > that is going well
> > > except for one patch of imperative code. My
> > Haskell version of
> > > this code is ugly. I was hoping someone could
> > recommend a better
> > > way to do it. I will paste a simplified version
> > of the code
> > > below. If necessary, I can provide all the other
> > code used for
> >
> > 1. Use strong typing. Or any typing
>
> I simplified the code for the post. In the real version, I use strong typing. The Card type is enumerated. I have been using [Card] instead of calling it a Deck. I could change that.
>
Deck is not important - it's rather eye candy ;) [Card] is as clear as
Deck.
> > 3. Don't use too much variables. 6-8 is probably the
> > maximum you should
> > deal with (human short-term memory holds about 5-10 points
> > of entry.
> > Split functions into smaller functions (even in where).
>
> I do have to get the information into the functions, so the only way I can avoid having lots of variables is by introducing new structures. I can do that.
>
New structures annotates types easily.
data ComplicatedData = ComplicatedData {
turn :: Int,
deck :: [Cards],
...
}
There is syntax sugar:
doSomething :: ComplicatedData -> [Cards]
doSomething cd = drop (turn cd) (deck cd)
-- takes deck drops as meny cards as turns passed and returns it
doSomethingCrazy :: ComplicatedData -> ComplicatedData
doSomethingCrazy cd = cd {deck = drop (turn cd) (deck cd)}
-- creates new ComplicatedData which have everything as
-- the argument except that desk is missing as many cards
-- as turn currently is
> > 6. While Haskell have long tradition of having short
> > namesit is not
> > always good (see 3). Use them only if you are sure it is
> > clear what they
> > mean:
>
> In the original version, I had longer variable names where they seemed necessary.
>
>
> The main sources of ugliness are the long lists of variables. Every time I call doAct or construct a LoopState variable, I am repeating all those variables. I will try changing the type of doAct to
>
> doAct :: LoopState -> LoopState
>
> Cheers,
> Hein
>
See the record syntax. Or refactor it to use a helper functions.
Depending on purpose and advancement you can play with pointless style.
Regards
PS. Consider using helper functions. Even if they are longer:
func n | 128 `mod` n == 0 = 3
| otherwise = 2
vs.
func n | n `divides` 128 = 3
| otherwise = 2
k `divides` n = n `mod` k == 0
In first example you have to think what I meant. In second it is
self-commention (n `divides` 128 - it is just n divides 128 with strange
apostrophes).
doSomething (State (c:cs) t ph ta ...)
| c == Ace `of` Hearths = State cs (t+1) (c:ph) ta ...
| otherwise = State cs (t+1) ph (c:ta) ...
vs.
putOnTable :: Card -> State -> State
putOnTable c s = s {table = c:table s}
putIntoPlayerHand :: Card -> State -> State
putIntoPlayerHand c s = s {playerHand = c:playerHand s}
drawCard :: State -> (Card, State)
drawCard s = let (c:cs) = deck s
in (x, s {deck = s})
nextTurn :: State -> State
nextTurn s = s {turn = turn s + 1}
doSomething s
| c == Ace `of` Hearths = nextTurn $ putIntoPlayerHand c s'
| otherwise = nextTurn $ putOnTable c s'
where (c, s') = drawCard s
or
doSomething s = let (c, s') = drawCard s
s'' | c == Ace `of` Hearths = putIntoPlayerHand c s'
| otherwise = putOnTable c s'
in nextTurn s''
Regards
PS. For 'advanced' only - and many advanced users dislikes this approach
and would recommend not to use it. Anyway - don't bother with it until
later if you don't understands.
data GameState = GameState {
deck :: [Card],
turn :: Int,
playerHand :: [Card],
table :: [Card],
...
}
putOnTable :: Card -> State GameState ()
putOnTable c = modify (\s -> s {table = c:table s})
putIntoPlayerHand :: Card -> State GameState ()
putIntoPlayerHand c = modify (\s -> s {playerHand = c:playerHand s})
drawCard :: State GameState Card
drawCard = do (c:cs) <- gets deck
modify (\s -> s {deck = cs})
return c
nextTurn :: State GameState ()
nextTurn = modify (\s -> s {turn = turn s + 1})
doSomething :: State GameState ()
doSomething = do c <- drawCard
if c == Ace `of` Hearths
then putIntoPlayerHand c
else putOnTable c
nextTurn
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 836 bytes
Desc: This is a digitally signed message part
Url : http://www.haskell.org/pipermail/beginners/attachments/20100429/21d7367b/attachment.bin
More information about the Beginners
mailing list