[Haskell-cafe] Help me speed up my program... or back to the issue of memoization

Kirill Kuvaldin kirill.kuvaldin at gmail.com
Mon May 5 11:57:51 EDT 2008


Hello,

I wrote a program in haskell that works with lattice finite automata
(the generalization of notion of finite state automata). Let me post
the source code as it is not that long...

The problem is that my algorithm that computes the run (see function
fun) of an automaton on the given word is not very optimal and takes a
loooong time as the input word gets larger... (e.g. try this one "run
m3 "11101101110001010101" ")

Due to the nature of every haskell function being a referentially
transparent, I think I could have speeded up
its performance using memoization.

I've read the page on haskell wiki
(http://www.haskell.org/haskellwiki/Memoization) but it didn't help me
because it looks I have to modify the actual function source code to
make use of memoized values.
What I'm looking for is a kind of a general solution (say, silver
bullet :) ) so that I will be able to use my function like

> new_run = memoize run

and the results of the "new_run" get automatically memoized. Probably
it makes sense to memoize deltaext func as well.

Is that possible to do that in Haskell??

Thanks a lot!
Kirill


======= SOURCE CODE =====

-- data type for lattice
data Lattice l = Lattice
      [l]              -- set of lattice elements
      (l -> l -> l)    -- supremum operation
      (l -> l -> l)    -- infimum operation

-- returns the lowest lattice element
lattice0 (Lattice l s i) = l !! 0
-- returns the greatest lattice element
lattice1 (Lattice l s i) = l !! ((length l)-1)

-- supremum of 2 lattice elements
sup (Lattice l s i) x y = s x y
-- infimum of 2 lattice elements
inf (Lattice l s i) x y = i x y


supremum (Lattice l sup inf) [] = lattice0 (Lattice l sup inf)
supremum (Lattice l sup inf) (x:xs) = sup x (supremum (Lattice l sup inf) xs)

infimum (Lattice l sup inf) [] = lattice1 (Lattice l sup inf)
infimum (Lattice l sup inf) (x:xs) = inf x (infimum (Lattice l sup inf) xs)
inf3 (Lattice l s i) x y z = infimum (Lattice l s i) [x,y,z]

--- data type for Lattice Automata (LA)
data LA l state sym = LA
           (Lattice l)                    -- lattice
           [state]                        -- set of states
           [sym]                          -- alphabet
           (state -> sym -> state -> l)   -- fuzzy transition function
           (state -> l)                   -- fuzzy initial state
           (state -> l)                   -- fuzzy final state

--- extended transition function
deltaext :: (Eq state) => (LA l state sym) -> state -> [sym] -> state -> l
deltaext (LA l states chars delta sigma0 sigma1) x [] y =
        if x == y then (lattice1 l) else (lattice0 l)
deltaext la@(LA l states chars delta sigma0 sigma1) x (a:w) y =
        supremum l
                 [ inf l
                       (delta x a z)
                       (deltaext la z w y)
                         | z <- states]

-- runs the Lattice Automaton on the given word
run la@(LA l states chars delta sigma0 sigma1) w =
   supremum l
            [ inf3 l
                   (sigma0 x)
                   (deltaext la x w y)
                   (sigma1 y) | x <- states, y <- states]

---
--- examples
---

l3 = Lattice [0.0, 0.5, 1.0] max min where
   max x y = if x > y then x else y
   min x y = if x < y then x else y

m3 = LA l3 ['a', 'b'] ['0', '1'] delta sigma0 sigma1 where
    delta 'a' '0' 'a' = 1
    delta 'a' '0' 'b' = 0.5
    delta 'b' '0' 'a' = 0.5
    delta 'b' '0' 'b' = 1
    delta 'a' '1' 'a' = 0
    delta 'a' '1' 'b' = 1
    delta 'b' '1' 'a' = 1
    delta 'b' '1' 'b' = 1
    sigma0 'a' = 1
    sigma0 'b' = 0.5
    sigma1 'a' = 0.5
    sigma1 'b' = 1


More information about the Haskell-Cafe mailing list