[Haskell-beginners] Memoization

abdullah abdul Khadir abdullah.ak2002 at gmail.com
Sat Nov 29 07:45:55 EST 2008


Hi,
      I am a student and we had an assignment in Haskell. The question, was
given a string of the form  "1-2+3*5-7+4-6+3" i.e., any sequence of integers
as well as some operators between them we had to find a maximum possible
value for the expression as well as the expression itself . So for maxval
"1-2+3*5-7+4-6+3" it is (76,"(1-((2+3)*((5-(7+4))-(6+3))))"). The function
we had to write was maxval :: String -> (Int,String). For further details on
the question, have a look at our sir's web page
here<http://www.cmi.ac.in/%7Emadhavan/courses/programming08/assignment6.txt>.
I solved the question, we had to use memoization, and submitted the
solution. It is given below. Now the problem is I am just wondering if it
can be solved in a better manner. Translation : Is there some way in Haskell
to do it in a more simpler way and as well as to reduce the number of lines
of the program.

> {-
>
> ---------------------------------------------------------------------------------------------------------------------------
> *********************** module Memo.hs
> ******************************************************
>
> ---------------------------------------------------------------------------------------------------------------------------
> -}
> module
> Memo(Table,emptytable,memofind,memolookup,memoupdate,memoupdateArray) where
>
> data (Eq a) => Table a b c = T [(a,a,(b,c),(b,c))]
>     deriving (Eq,Show)
>
> emptytable :: (Eq a) => (Table a b c)
> emptytable = T []
>
> memofind ::  (Eq a) => (Table a b c) ->(a,a)-> Bool
> memofind (T []) _  = False
> memofind (T ((y,z,(v1,s1),(v2,s2)):l)) x
>     | x  == (y,z)     = True
>     | otherwise     = memofind (T l) x
>
> memolookup :: (Eq a) => (Table a b c) -> (a,a) -> ((b,c),(b,c))
> memolookup (T ((y,z,(v1,s1),(v2,s2)):l)) x
>     | x == (y,z)    = ((v1,s1),(v2,s2))
>     | otherwise = memolookup (T l) x
>
> memoupdate :: (Eq a) => (Table a b c) -> (a,a,(b,c),(b,c)) -> (Table a b c)
> memoupdate (T l) x =  T (x:l)
>
> memoupdateArray :: (Eq a) => (Table a b c) -> [(a,a,(b,c),(b,c))] -> (Table
> a b c)
> memoupdateArray t [] = t
> memoupdateArray t (x:xs) =  memoupdate (memoupdateArray t xs) x
>
> {-
>
> ---------------------------------------------------------------------------------------------------------------------------
> ***********************End of module
> Memo.hs***********************************************
>
> ---------------------------------------------------------------------------------------------------------------------------
> -}
>
>
> {-
>
> ---------------------------------------------------------------------------------------------------------------------------
> ******************The actual program ,
> assign-6.hs******************************************
>
> ---------------------------------------------------------------------------------------------------------------------------
> -}
>
> minArray :: [(Int,String)] -> (Int,String)
> minArray ((x,expr):[])  = (x,expr)
> minArray ((x,expr):l)   |((min x (fst (minArray l))) ==x) = (x,expr)
>                         |otherwise      =  (minArray l)
>
> maxArray :: [(Int,String)] -> (Int,String)
> maxArray ((x,expr):[])  = (x,expr)
> maxArray ((x,expr):l)   |((max x (fst (minArray l))) ==x) = (x,expr)
>                         |otherwise      =  (minArray l)
>
> import Memo
> import Char
>
> type Tuple = (Int,Int,(Int,String),(Int,String))
>
> maxval :: String ->(Int, String)
> maxval expr = snd (memolookup (buildmemo expr 1 emptytable) (1,length
> expr))
>
> initmemo :: (String) -> (Table Int Int String)
> initmemo expr    = (memoupdateArray (emptytable)
>                             [(i,i,(toInt(expr!!(i-1)),[expr!!(i-1)]),
>                      (toInt(expr!!(i-1)),[expr!!(i-1)]))|i<-[1..length
> expr],j<-[0,1],i `mod` 2 ==1])
>
> buildmemo :: (String)->Int -> (Table Int Int String)-> (Table Int Int
> String)
> buildmemo expr col memo        | (col > length expr)    =  memo
>                 | (col == 1)    = buildmemo expr 3 (memoupdateArray
> (emptytable)
>                                [(i,i,(toInt(expr!!(i-1)),[expr!!(i-1)]),
>
> (toInt(expr!!(i-1)),[expr!!(i-1)]))|i<-[1..length expr],i `mod` 2 ==1])
>                 | otherwise      = buildmemo expr (col+2) (memoupdateArray
> (memo) (createList expr memo (1,col)))
>
> createList :: String-> (Table Int Int String) -> (Int,Int) -> [Tuple]
> createList expr memo (i,j)     | j > (length expr) = []
>                 | otherwise    = (i,j,min_expr,max_expr):(createList expr
> memo (i+2,j+2))
>                 where
>                 min_expr = minArray [x | (x,y) <- list]
>                 max_expr = maxArray [y | (x,y) <- list]
>                 list      = [(compute memo (i,k) (k+2,j)
> (expr!!k))|k<-[i..j-2],k `mod` 2 ==1]
>
> compute :: (Table Int Int
> String)->(Int,Int)->(Int,Int)->Char->((Int,String),(Int,String))
> compute memo (x1,x2) (y1,y2)     op     |op == '+' =
> ((min1+min2,"("++min1_expr++"+"++min2_expr++")"),
>
> (max1+max2,"("++max1_expr++"+"++max2_expr++")"))
>                     |op == '-' =
> ((min1-max2,"("++min1_expr++"-"++max2_expr++")"),
>
> (max1-min2,"("++max1_expr++"-"++min2_expr++")"))
>                     |op == '*' = (minArray xs,maxArray xs)
>                     where
>                     xs = [(min1*min2,"("++min1_expr++"*"++min2_expr++")"),
>                         (min1*max2,"("++min1_expr++"*"++max2_expr++")"),
>                           (max1*min2,"("++max1_expr++"*"++min2_expr++")"),
>
> (max1*max2,"("++max1_expr++"*"++max2_expr++")")]
>                     ((min1,min1_expr),(max1,max1_expr)) = (memolookup memo
> (x1,x2))
>                     ((min2,min2_expr),(max2,max2_expr)) = (memolookup memo
> (y1,y2))
>
> minArray :: [(Int,String)] -> (Int,String)
> minArray ((x,expr):[])     = (x,expr)
> minArray ((x,expr):l)     |((min x (fst (minArray l))) ==x) = (x,expr)
>             |otherwise    =  (minArray l)
>
> maxArray :: [(Int,String)] -> (Int,String)
> maxArray ((x,expr):[])  = (x,expr)
> maxArray ((x,expr):l)   |((max x (fst (maxArray l))) ==x) = (x,expr)
>                         |otherwise      =  (maxArray l)
>
> toInt :: Char -> Int
> toInt x = ord x - ord '0'
>
> {-
>
> ---------------------------------------------------------------------------------------------------------------------------
> ***********************End of program
> assign-6.hs*******************************************
>
> ---------------------------------------------------------------------------------------------------------------------------
> -}
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20081129/a402cc23/attachment-0001.htm


More information about the Beginners mailing list