[Haskell-cafe] non-uniform recursive Trie

2012-10-29 Thread 山本和彦
Hello cafe,

I'm now studying Trie in Okasaki's Purely Functional Data Structure.
Attached is the program in its appendix. I cannot understand how to
use empty, look and bind. For instance, if I type 'look  empty',
I got an error:

 look  empty
interactive:2:1:
No instance for (FiniteMap m0 [Char])
  arising from a use of `look'
Possible fix: add an instance declaration for (FiniteMap m0 [Char])
In the expression: look  empty
In an equation for `it': it = look  empty

I have no idea how to determine the parameter 'm'. Suggestions would
be appreciated.

--Kazu

{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}

class FiniteMap m k where
empty :: m k v
look :: k - m k v - Maybe v
bind :: k - v - m k v - m k v

data Trie m ks v = Trie (Maybe v) (m (Trie m ks v))

instance FiniteMap m k = FiniteMap (Trie (m k)) [k] where
empty = Trie Nothing empty

look [] (Trie b _) = b
look (k:ks) (Trie _ m) = look k m = look ks

bind [] x (Trie _ m) = Trie (Just x) m
bind (k:ks) x (Trie b m) = Trie b (bind k t' m)
  where
t = case look k m of
Just a  - a
Nothing - empty
t' = bind ks x t

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] non-uniform recursive Trie

2012-10-29 Thread Andres Löh
Hi Kazu.

 I'm now studying Trie in Okasaki's Purely Functional Data Structure.
 Attached is the program in its appendix. I cannot understand how to
 use empty, look and bind. For instance, if I type 'look  empty',
 I got an error:

 look  empty
 interactive:2:1:
 No instance for (FiniteMap m0 [Char])
   arising from a use of `look'
 Possible fix: add an instance declaration for (FiniteMap m0 [Char])
 In the expression: look  empty
 In an equation for `it': it = look  empty

 I have no idea how to determine the parameter 'm'. Suggestions would
 be appreciated.

The code you've listed shows how to go from an already existing
instance of class FiniteMap to an instance for the same class that
adds a trie structure on top of the underlying finite map
implementation. You have to add a base instance to the code so that
it can work. For example, by importing Data.Map and adding an
instance FiniteMap Data.Map.Map Char with the appropriate
definitions.

You'll also need to add extra type information to empty in your
example expression so that GHC can know which instance you actually
want.

Cheers,
  Andres

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] non-uniform recursive Trie

2012-10-29 Thread 山本和彦
Andres,

 The code you've listed shows how to go from an already existing
 instance of class FiniteMap to an instance for the same class that
 adds a trie structure on top of the underlying finite map
 implementation. You have to add a base instance to the code so that
 it can work. For example, by importing Data.Map and adding an
 instance FiniteMap Data.Map.Map Char with the appropriate
 definitions.

Thank you.

I added the following:

instance FiniteMap Map Char where
empty = M.empty
look = M.lookup
bind = M.insert

 You'll also need to add extra type information to empty in your
 example expression so that GHC can know which instance you actually
 want.

Is the follwing what you mean?

 look bar $ bind bar 1 $ (empty :: Trie (Map Char) String Int)
Just 1

P.S.

FiniteMap uses another finite map, Data.Map in this case. I wonder why
we can call it bootstrapping...

--Kazu

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe