
[moved to haskell-cafe] While I largely agree with what Nils said, it does seem that arrays are a good match for your application. It is true, unfortunately, as you're discovering, that mutable arrays are awkward in a pure functional language. I think the most appropriate way to deal with them would depend on the larger perspective of your application's control structure. If the array manipulation is necessarily intermixed with input/output, for example, you might consider an essentially imperative approach using `IOArray`s in the `IO` monad. If the input/ouput and array manipulation tend to alternate, `STArray`s in the `ST` monad might offer a more functional approach. If the amount of array manipulation is small, then the approach you've shown so far might be entirely adequate. Dean "Mike T. Machenry" wrote:
I guess I figured that Arrays were the natural data type for the tickets since it has a fixed size and the elements all have a specific player associated with them. I am coming from a Scheme background so I am already very fluent in list manipulation. I'm not an imperative programer, so that's not really the problem. I just think that Arrays represent this data much better.
-mike
On Fri, Feb 21, 2003 at 01:00:30PM +0100, Nils Decker wrote:
"Mike T. Machenry"
wrote: Hey Everyone,
I am having a hard time making a data structure that I can incrimentally update. Mostly because dealing with arrays is so tough. Does anyone think I'm going about this completely the wrong way? This is what I have. IMO there is normally no need to use arrays in haskell. You should use lists instead, because it is much more easy to use recursion over lists. Once you got the pattern, it feels like the natural way in haskell. It also helps to define more types than just one large type for everything.
data GameState = GameState { dTickets :: Array Player (Array Ticket Int), fTickets :: Array FugitiveTicket Int, history :: [Move], dLocations :: Array Player Stop, fLocations :: Set Stop }
removeTicket :: GameState -> Detective -> Ticket -> GameState removeTicket s d t = s { tickets = (tickets s) // [(d,[(t,((tickets s)!d!t - 1))])] }
why not use
data Ticket = Ticket Int {-value-} deriving (Eq, Show) type Tickets = [Ticket]
removeTicket :: Ticket -> Tickets -> Tickets removeTicket _ [] = fail "not there" removeTicket x (t:ts) | x == t = ts | otherwise = t : (removeTicket x ts)
Is there a reason, to have different fields and types for detectives? data PlayerNames = MrX | Red | Green | Blue deriving (Eq,Show) If MrX needs special treatment ( computed move or information shown to the player ) you can patternmatch for MrX. For the usage of tickets and the history of moves there should be no difference.
There might even be no reason to have PlayerNames as instance of enum. As i understand, you want to use succ(player) to find the next player to move. It can be easier to have a function that recurses over a list of players to run one round.
This remove ticket function is just terrible and it's common for me to have to do operations like this. It's been hard to make this a function that I can pattern match on, because which piece of data is manipulated depends on the parmeter d (Detective) Just split up the huge record and have tiny functions to deal with every specific part of it
Summary in a few words: Use many small functions instead of a few big ones. Use lists instead of arrays. If you use arrays, first understand why you can not use lists in that specific case. Learn to recurse over lists! Learn to use map, foldl and foldr. They save you a lot of typing and make most functions dealing with lists short and clear.
You should derive Show for all your types and test every new function in hugs or ghci.
Regards Nils Decker
PS: I have learned haskell a year ago after using imperative languages all of my life. At first it is hard to get used to some concepts, but then they are wonderful.
PPS: There is another list called haskell-cafe. It is used for discussion of problems while this list is meant for short threads and announcements. You might want to subscribe to it.
-- Freedom of speech is wonderful - right up there with the freedom not to listen.
Nils Decker

Eh, state is not possible. This is a recursive state space search. I need to branch the state of the game and not allow branches to effect others. Though I'd really like to represent them as arrays like such: data Player = Red | Green | Blue deriving (Enum,Eq,Ix) data Ticket = Taxi | Bus | Underground deriving (Enum,Eq,Ix) type Tickets = Array Player (Array Ticket Int) Arrays in Haskell just might be too painful to to this with and I'll have to use lists. They'er easier to use, but I don't believe they match the data as closly. -mike On Fri, Feb 21, 2003 at 12:50:11PM -0500, Dean Herington wrote:
[moved to haskell-cafe]
While I largely agree with what Nils said, it does seem that arrays are a good match for your application. It is true, unfortunately, as you're discovering, that mutable arrays are awkward in a pure functional language. I think the most appropriate way to deal with them would depend on the larger perspective of your application's control structure. If the array manipulation is necessarily intermixed with input/output, for example, you might consider an essentially imperative approach using `IOArray`s in the `IO` monad. If the input/ouput and array manipulation tend to alternate, `STArray`s in the `ST` monad might offer a more functional approach. If the amount of array manipulation is small, then the approach you've shown so far might be entirely adequate.
Dean
"Mike T. Machenry" wrote:
I guess I figured that Arrays were the natural data type for the tickets since it has a fixed size and the elements all have a specific player associated with them. I am coming from a Scheme background so I am already very fluent in list manipulation. I'm not an imperative programer, so that's not really the problem. I just think that Arrays represent this data much better.
-mike
On Fri, Feb 21, 2003 at 01:00:30PM +0100, Nils Decker wrote:
"Mike T. Machenry"
wrote: Hey Everyone,
I am having a hard time making a data structure that I can incrimentally update. Mostly because dealing with arrays is so tough. Does anyone think I'm going about this completely the wrong way? This is what I have. IMO there is normally no need to use arrays in haskell. You should use lists instead, because it is much more easy to use recursion over lists. Once you got the pattern, it feels like the natural way in haskell. It also helps to define more types than just one large type for everything.
data GameState = GameState { dTickets :: Array Player (Array Ticket Int), fTickets :: Array FugitiveTicket Int, history :: [Move], dLocations :: Array Player Stop, fLocations :: Set Stop }
removeTicket :: GameState -> Detective -> Ticket -> GameState removeTicket s d t = s { tickets = (tickets s) // [(d,[(t,((tickets s)!d!t - 1))])] }
why not use
data Ticket = Ticket Int {-value-} deriving (Eq, Show) type Tickets = [Ticket]
removeTicket :: Ticket -> Tickets -> Tickets removeTicket _ [] = fail "not there" removeTicket x (t:ts) | x == t = ts | otherwise = t : (removeTicket x ts)
Is there a reason, to have different fields and types for detectives? data PlayerNames = MrX | Red | Green | Blue deriving (Eq,Show) If MrX needs special treatment ( computed move or information shown to the player ) you can patternmatch for MrX. For the usage of tickets and the history of moves there should be no difference.
There might even be no reason to have PlayerNames as instance of enum. As i understand, you want to use succ(player) to find the next player to move. It can be easier to have a function that recurses over a list of players to run one round.
This remove ticket function is just terrible and it's common for me to have to do operations like this. It's been hard to make this a function that I can pattern match on, because which piece of data is manipulated depends on the parmeter d (Detective) Just split up the huge record and have tiny functions to deal with every specific part of it
Summary in a few words: Use many small functions instead of a few big ones. Use lists instead of arrays. If you use arrays, first understand why you can not use lists in that specific case. Learn to recurse over lists! Learn to use map, foldl and foldr. They save you a lot of typing and make most functions dealing with lists short and clear.
You should derive Show for all your types and test every new function in hugs or ghci.
Regards Nils Decker
PS: I have learned haskell a year ago after using imperative languages all of my life. At first it is hard to get used to some concepts, but then they are wonderful.
PPS: There is another list called haskell-cafe. It is used for discussion of problems while this list is meant for short threads and announcements. You might want to subscribe to it.
-- Freedom of speech is wonderful - right up there with the freedom not to listen.
Nils Decker
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Ah, I see. Finite maps might be appropriate, then. Here's a sketch of how you might implement arraylike objects with finite maps. -- Array-like objects built from FiniteMaps -- Dean Herington, Feb. 22, 2003 module FMArray (FMArray, fmArray, get, set, update) where import Array import FiniteMap import Maybe data FMArray i e = FMArray (i,i) (FiniteMap i e) fmArray :: (Ix i) => (i,i) -> [(i,e)] -> FMArray i e fmArray bs as = if all (inRange bs . fst) as then FMArray bs $ listToFM [ (i, elemAt i) | i <- range bs ] else outOfRange "fmArray" where elemAt i = case [ e | (j,e) <- as, i == j ] of [e] -> e [] -> error "FMArray: undefined element" _ -> error "FMArray: multiply defined element" get :: (Ix i) => FMArray i e -> i -> e get (FMArray bs fm) i = if inRange bs i then fromJust (lookupFM fm i) else outOfRange "get" set :: (Ix i) => FMArray i e -> i -> e -> FMArray i e set (FMArray bs fm) i e = if inRange bs i then FMArray bs (addToFM fm i e) else outOfRange "set" update :: (Ix i) => FMArray i e -> i -> (e -> e) -> FMArray i e update (FMArray bs fm) i f = if inRange bs i then FMArray bs (addToFM_C (\ e _ -> f e) fm i undefined) else outOfRange "update" outOfRange who = error $ "FMArray." ++ who ++ ": index out of range" instance (Ix i, Show i, Show e) => Show (FMArray i e) where showsPrec p (FMArray bs fm) = showParen (p >= 11) (showString "FMArray " . shows bs . showChar ' ' . shows (fmToList fm)) -- Dean On Fri, 21 Feb 2003, Mike T. Machenry wrote:
Eh, state is not possible. This is a recursive state space search. I need to branch the state of the game and not allow branches to effect others. Though I'd really like to represent them as arrays like such:
data Player = Red | Green | Blue deriving (Enum,Eq,Ix) data Ticket = Taxi | Bus | Underground deriving (Enum,Eq,Ix) type Tickets = Array Player (Array Ticket Int)
Arrays in Haskell just might be too painful to to this with and I'll have to use lists. They'er easier to use, but I don't believe they match the data as closly.
-mike
On Fri, Feb 21, 2003 at 12:50:11PM -0500, Dean Herington wrote:
[moved to haskell-cafe]
While I largely agree with what Nils said, it does seem that arrays are a good match for your application. It is true, unfortunately, as you're discovering, that mutable arrays are awkward in a pure functional language. I think the most appropriate way to deal with them would depend on the larger perspective of your application's control structure. If the array manipulation is necessarily intermixed with input/output, for example, you might consider an essentially imperative approach using `IOArray`s in the `IO` monad. If the input/ouput and array manipulation tend to alternate, `STArray`s in the `ST` monad might offer a more functional approach. If the amount of array manipulation is small, then the approach you've shown so far might be entirely adequate.
Dean
"Mike T. Machenry" wrote:
I guess I figured that Arrays were the natural data type for the tickets since it has a fixed size and the elements all have a specific player associated with them. I am coming from a Scheme background so I am already very fluent in list manipulation. I'm not an imperative programer, so that's not really the problem. I just think that Arrays represent this data much better.
-mike
On Fri, Feb 21, 2003 at 01:00:30PM +0100, Nils Decker wrote:
"Mike T. Machenry"
wrote: Hey Everyone,
I am having a hard time making a data structure that I can incrimentally update. Mostly because dealing with arrays is so tough. Does anyone think I'm going about this completely the wrong way? This is what I have. IMO there is normally no need to use arrays in haskell. You should use lists instead, because it is much more easy to use recursion over lists. Once you got the pattern, it feels like the natural way in haskell. It also helps to define more types than just one large type for everything.
data GameState = GameState { dTickets :: Array Player (Array Ticket Int), fTickets :: Array FugitiveTicket Int, history :: [Move], dLocations :: Array Player Stop, fLocations :: Set Stop }
removeTicket :: GameState -> Detective -> Ticket -> GameState removeTicket s d t = s { tickets = (tickets s) // [(d,[(t,((tickets s)!d!t - 1))])] }
why not use
data Ticket = Ticket Int {-value-} deriving (Eq, Show) type Tickets = [Ticket]
removeTicket :: Ticket -> Tickets -> Tickets removeTicket _ [] = fail "not there" removeTicket x (t:ts) | x == t = ts | otherwise = t : (removeTicket x ts)
Is there a reason, to have different fields and types for detectives? data PlayerNames = MrX | Red | Green | Blue deriving (Eq,Show) If MrX needs special treatment ( computed move or information shown to the player ) you can patternmatch for MrX. For the usage of tickets and the history of moves there should be no difference.
There might even be no reason to have PlayerNames as instance of enum. As i understand, you want to use succ(player) to find the next player to move. It can be easier to have a function that recurses over a list of players to run one round.
This remove ticket function is just terrible and it's common for me to have to do operations like this. It's been hard to make this a function that I can pattern match on, because which piece of data is manipulated depends on the parmeter d (Detective) Just split up the huge record and have tiny functions to deal with every specific part of it
Summary in a few words: Use many small functions instead of a few big ones. Use lists instead of arrays. If you use arrays, first understand why you can not use lists in that specific case. Learn to recurse over lists! Learn to use map, foldl and foldr. They save you a lot of typing and make most functions dealing with lists short and clear.
You should derive Show for all your types and test every new function in hugs or ghci.
Regards Nils Decker
PS: I have learned haskell a year ago after using imperative languages all of my life. At first it is hard to get used to some concepts, but then they are wonderful.
PPS: There is another list called haskell-cafe. It is used for discussion of problems while this list is meant for short threads and announcements. You might want to subscribe to it.
-- Freedom of speech is wonderful - right up there with the freedom not to listen.
Nils Decker
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 2003-02-21T13:37:26-0500, Mike T. Machenry wrote:
Eh, state is not possible. This is a recursive state space search. I need to branch the state of the game and not allow branches to effect others.
I see-- so you don't care about performing array updates in place, because you will be copying arrays from parent nodes in the state space to child nodes anyway. Is that correct? From what you originally wrote, it seems to me that you are forced to write awkward code because very often you need to reach into a data structure and perform some manipulation on a part of it without affecting anything else. This seems like a common pattern that deserves abstraction. If you have a function from a to a, and you have an Array of a's, you can apply that function to update a certain element of that Array: atIndex :: (Ix i) => i -> (a -> a) -> (Array i a -> Array i a) atIndex i f a = a // [(i, f (a!i))] Similarly, whenever you have a tickets-to-tickets function (by the way, it seems that you renamed tickets to dTickets or vice versa while composing your message), you can turn it into a GameState transformer: atTickets :: (Array Player (Array Ticket Int) -> Array Player (Array Ticket Int)) -> (GameState -> GameState) atTickets f s = s { tickets = f (tickets s) } Your removeTicket function can now be written removeTicket s d t = (atTickets $ atIndex d $ atIndex t $ pred) s This technique generalizes from arrays and records to other container data structures like lists and finite maps. -- Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig Is it because of problems at school that you say you hope the eurythmics'' practice birth control?
participants (3)
-
Dean Herington
-
Ken Shan
-
Mike T. Machenry