[Haskell-cafe] Tying the recursive knot

Joshua Ball joshbball at gmail.com
Thu Mar 24 23:02:01 CET 2011


Never mind. I figured it out on my own. Here's my solution for
posterity. There's probably a "fix" hiding in there somewhere - notice
the new type of reduce.

module Recursion where

import Data.Map ((!))
import qualified Data.Map as M
import Debug.Trace

newtype Key = Key { unKey :: String }
  deriving (Eq, Ord, Show)

data Chain = Link Int Chain | Trace String Chain | Ref Key
  deriving (Show)

force :: M.Map Key Chain -> M.Map Key [Int]
force mp = ret where
  ret = M.fromList (map (\k -> (k, reduce mp (ret !) k)) (M.keys mp))

reduce :: M.Map Key Chain -> (Key -> [Int]) -> Key -> [Int]
reduce mp lookup key = follow (mp ! key) where
  follow (Link i c) = i : follow c
  follow (Ref k) = lookup k
  follow (Trace message c) = trace message (follow c)

example = M.fromList [(Key "ones", Link 1 . Trace "expensive
computation here" . Ref . Key $ "ones")]

main = print $ take 10 $ (force example ! Key "ones")

On Thu, Mar 24, 2011 at 12:35 PM, Joshua Ball <joshbball at gmail.com> wrote:
> {-
>  - Hi all,
>  -
>  - I'm having trouble tying the recursive knot in one of my programs.
>  -
>  - Suppose I have the following data structures and functions:
>  -}
> module Recursion where
>
> import Control.Monad.Fix
> import Data.Map ((!))
> import qualified Data.Map as M
> import Debug.Trace
>
> newtype Key = Key { unKey :: String }
>  deriving (Eq, Ord, Show)
>
> data Chain = Link Int Chain | Trace String Chain | Ref Key
>  deriving (Show)
>
> reduce :: M.Map Key Chain -> Key -> [Int]
> reduce env k = follow (env ! k) where
>  follow (Link i c) = i : follow c
>  follow (Ref k) = reduce env k
>  follow (Trace message c) = trace message (follow c)
>
> -- Now I want a "force" function that expands all of the chains into
> int sequences.
> force1, force2 :: M.Map Key Chain -> M.Map Key [Int]
>
> -- This is pretty easy to do:
> force1 mp = M.fromList (map (\k -> (k, reduce mp k)) (M.keys mp))
>
> -- But I want the int sequences to be lazy. The following example
> illustrates that they are not:
> example = M.fromList [(Key "ones", Link 1 . Trace "expensive
> computation here" . Ref . Key $ "ones")]
> -- Run "force1 example" in ghci, and you will see the "expensive
> computation here" messages interleaved with an infinite
> -- list of ones. I would prefer for the "expensive computation" to
> happen only once.
>
> -- Here was my first attempt at regaining laziness:
> fixpointee :: M.Map Key Chain -> M.Map Key [Int] -> M.Map Key [Int]
> fixpointee env mp = M.fromList (map (\k -> (k, reduce env k)) (M.keys mp))
>
> force2 env = fix (fixpointee env)
>
> main = print $ force2 example
>
> {-
>  - However, this gets stuck in an infinite loop and doesn't make it
> past printing "fromList ".
>  - (It was not difficult for me to see why, once I thought about it.)
>  -
>  - How do I recover laziness? A pure solution would be nice, but in
> the actual program
>  - I am working on, I am in the IO monad, so I am ok with an impure solution.
>  - It's also perfectly ok for me to modify the reduce function.
>  -
>  - Thanks in advance for you help,
>  - Josh "Ua" Ball
>  -}
>



More information about the Haskell-Cafe mailing list