Converting an imperative program to haskell

Hi, I am new to Haskell. I programmed in imperative languages for many years and I have been using Mathematica for the last 15 years which mixes functional and imperative programming. I started learning Haskell about 2 months ago mostly by reading the first 13.5 chapters of Real World Haskell and doing about 50 of the Euler Problems. "The Evolution of a Haskell Programmer", the Haskell Wiki, and this listserv have also been helpful. 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 this simplified example (about 30 more lines of Haskell code, or an equivalent program in C++ (130 lines of code). Cheers, Hein -----------------Ugly Haskell Code------------------------- data LoopState = LSt GameState Strat Int Int Int [Int] Int Int Bool proc :: GameState -> Strat -> (Int, Int, GameState) proc gs' strat = let iA = 1 iTh = 0 i = 0 aA = replicate 20 0 iB = 1 iC = 0 bDone = False gs = apps ("<<<"++show(gs')++">>>") gs' lst = LSt gs strat iA iTh i aA iB iC bDone lst2 = until isDone procloop lst isDone (LSt gs strat iA iTh i aA iB iC bDone) = bDone output (LSt gs strat iA iTh i aA iB iC bDone) = (iB, iC, appd aA gs) in output lst2 procloop :: LoopState -> LoopState procloop (LSt gs' strat iA iTh i aA iB iC bDone) = do let iCd = stratchoose strat gs' iA iTh iB aA let gs = apps ("iB "++show iB++ "\n" ) gs' if iA<=0 || i>=20 || actcd gs <=0 || iCd == -1 then LSt gs strat iA iTh (i+1) aA iB iC True else if iCd == 1 then LSt gs strat iA (iTh+1) (i+1) aA iB iC False else let gs2 = delh iCd gs aA2 = append aA iCd (iA3, iC3, iB3, gs3, aA3) = doAct iA iC iB gs2 aA2 strat iCd (iA4, iC4, iB4, gs4, aA4) = doAct iA3 iC3 iB3 gs3 aA3 strat iCd in if iTh>0 then LSt gs4 strat iA4 (iTh-1) (i+1) aA4 iB4 iC4 False else LSt gs3 strat iA3 (iTh-1) (i+1) aA3 iB3 iC3 False ---------------end of Haskell code-------------------------------

On Thu, 2010-04-29 at 13:29 -0700, 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 this simplified example (about 30 more lines of Haskell code, or an equivalent program in C++ (130 lines of code).
1. Use strong typing. Or any typing data Card = Value `Of` Color data Color = Spades | Hearts | Diamonds | Clubs data Value = A | V2 | V3 | V4 | V5 | V6 | V7 | V8 | V9 | V10 | J | Q | K type Deck = [Card] Now saying K `Of` Spades is nicer then 32 or anything. Also It allows to have it much nicer: check (A `Of` Clubs) = "You guessed my card!" check _ = "Try again!" You won't get invalid card (as 53) - it is guaranteed by the system. 2. User guards instead of nested if's: test a b c | a == b = "Hello" | a == c = "Hi" | b == c' = "Howdy" | otherwise = "Goodbye" where c' = c + 1 vs. test a b c = if a == b then "Hello" else if a == c then "Hi" else if b == c' then "Howdy" else "Goodbye" where c' = c + 1 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). 4. Discard result you don't need: isDone (LSt gs strat iA iTh i aA iB iC bDone) = bDone isDone (LSt _ _ _ _ _ _ _ _ _ bDone) = bDone 5. Don't reuse the same name in the same scope (like iA as 1 and iA as parameter to isDone). 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: map f (x:xs) = f x:map f xs -- Good - take something x from list of somethins map _ [] = [] Regards PS. Sorry - I haven't had time to look into code very deeply.

--- On Thu, 4/29/10, Maciej Piechotka
Hein Hundal wrote:
I figured I should try a larger program
converting one of my Mathematica programs, a simulator for the card game Dominion, over to Haskell. Most of
in Haskell, so I am 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.
2. User guards instead of nested if's:
In the "procloop" function, I have if's nested quite deeply. I could easily use guards. I will try that.
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.
4. Discard result you don't need:
isDone (LSt gs strat iA iTh i aA iB iC bDone) = bDone isDone (LSt _ _ _ _ _ _ _ _ _ bDone) = bDone
Yes, that's much better. proc gs' strat = let iA = 1 iTh = 0 i = 0 aA = replicate 20 0 iB = 1 iC = 0 bDone = False gs = apps ("<<<"++show(gs')++">>>") gs' lst = LSt gs strat iA iTh i aA iB iC bDone lst2 = until isDone procloop lst isDone (LSt _ _ _ _ _ _ _ _ bDone) = bDone output (LSt gs _ _ _ _ aA iB iC _) = (iB, iC, appd aA gs) in output lst2
5. Don't reuse the same name in the same scope (like iA as 1 and iA as parameter to isDone).
I did hesitate to use the same parameter name twice.
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

Am Donnerstag 29 April 2010 23:49:16 schrieb Hein Hundal:
--- On Thu, 4/29/10, Maciej Piechotka
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.
Whether you use [Card], type Deck = [Card] or newtype Deck = D [Card] is not important. Using enumerations for suite and value instead of Ints is.
2. User guards instead of nested if's:
In the "procloop" function, I have if's nested quite deeply.
Nested ifs (beyond, say, three levels) are a pain to decipher. Using guards (and maybe 'case's) will probably be a great improvement.
I could easily use guards. I will try that.
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.
As long as they're meaningful. Just smashing a couple of values together into a structure to reduce the variable count isn't good.
4. Discard result you don't need:
isDone (LSt gs strat iA iTh i aA iB iC bDone) = bDone isDone (LSt _ _ _ _ _ _ _ _ _ bDone) = bDone
Yes, that's much better.
Perhaps use named field syntax, data LoopState = LSt { gameState :: GameState , strat :: Strategy , ... , isDone :: Bool } Then in procloop, where you just update one or two fields, procloop lst@(LSt gs' strat iA iTh i aA iB iC bDone) | iA<=0 || i>=20 || actcd gs <=0 || iCd == -1 = lst{ idx = idx lst + 1, isDone = True } | iCd == 1 = lst{ idx = idx lst + 1, iThFld = iThFld lst + 1, isDone = False } | iThFld lst > 0 = lst{ ... } | otherwise = lst{ ... } where iCd = stratchoose ... -- other let-bindings, only those needed will be evaluated
proc gs' strat = let iA = 1 iTh = 0 i = 0 aA = replicate 20 0 iB = 1 iC = 0 bDone = False gs = apps ("<<<"++show(gs')++">>>") gs' lst = LSt gs strat iA iTh i aA iB iC bDone lst2 = until isDone procloop lst isDone (LSt _ _ _ _ _ _ _ _ bDone) = bDone output (LSt gs _ _ _ _ aA iB iC _) = (iB, iC, appd aA gs) in output lst2
5. Don't reuse the same name in the same scope (like iA as 1 and iA as parameter to isDone).
I did hesitate to use the same parameter name twice.
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
That looks promising.
Cheers, Hein

On Thu, 2010-04-29 at 14:49 -0700, Hein Hundal wrote:
--- On Thu, 4/29/10, Maciej Piechotka
wrote: Hein Hundal wrote:
I figured I should try a larger program
converting one of my Mathematica programs, a simulator for the card game Dominion, over to Haskell. Most of
in Haskell, so I am 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
participants (3)
-
Daniel Fischer
-
Hein Hundal
-
Maciej Piechotka