[Haskell-cafe] data structures question

Chris Kuklewicz haskell at list.mightyreason.com
Wed Aug 30 09:31:28 EDT 2006


Tamas K Papp wrote:
> Hi,
> 
> Having read some tutorials, I would like to start using Haskell "for
> real", but I have some questions about data structures.
> 
> The mathematical description of the problem is the following: assume
> there is a function V(a,b,theta), where a and b can have two values,
> High or Low, and theta is a number between zero and n (n is given).
> The range of V is the real numbers.
> 
> Then there is an algorithm (called value iteration, but that's not
> important) that takes V and produces a function of the same type,
> called V'.  The algorithm uses a mapping that is not elementwise, ie
> more than the corresponding values of V are needed to compute a
> particular V'(a,b,theta) -- things like V(other a,b,theta) and
> V(a,b,theta+1), where
> 
> data State = Low | High
> other :: State -> State
> other High = Low
> other Low = High
> 
> Question 1: V can be represented as a 3-dimensional array, where the
> first two indices are of type State, the third is Int (<= n).  What
> data structure do you suggest in Haskell to store V?  Is there a
> multidimensional array or something like this?
> 

Read http://haskell.org/haskellwiki/Modern_array_libraries

It sounds like you need Data.Array (lazy) or Data.Array.Unboxed (strict)

> Let's call this structure TypeV.
> 
> Question 2: I would like to write
> 
> valueit :: TypeV -> TypeV
> valueit V = mapondescartesproduct [Low,High] [Low,High] [0..n] mapV where
> 	    -- mapV would calculate the new V' using V
> 	    -- mapV :: State -> State -> Int -> Double
> 
> to fill the new data structure.  How to do this sensibly?
> 

Your definition is almost clear.

mapV takes the i :: (State,State,Int) index of an entry in V' and takes the 
whole old array V and computes the value at location i in V'.

data State = Low | High deriving (Eq,Ord,Ix) -- assuming Ix is derivable...

type TypeV = Array (State,State,Int) Double  -- or UArray instead of Array

mapV :: TypeV -> (State,State,Int) -> Double
mapV = undefined

valueit :: TypeV -> TypeV
valueit oldV = listArray (minI,maxI) [ mapV oldV i | i <- range (minI,maxI) ]
   where minI = (Low,Low,0)
         maxI = (High,High,n)

-- or move mapV to where clause; it can still use oldV

valueit :: TypeV -> TypeV
valueit oldV = listArray (minI,maxI) [ mapV i | i <- range (minI,maxI) ]
   where minI = (Low,Low,0)
         maxI = (High,High,n)
         mapV :: (State,State,Int) -> Double
         mapV = undefined

> Thanks,
> 
> Tamas


More information about the Haskell-Cafe mailing list