More suitable data structure needed

Hal Daume III hdaume@ISI.EDU
Wed, 21 Aug 2002 23:45:28 -0700 (PDT)


Hi,

> On Wed, 2002-08-21 at 16:52, Hal Daume III wrote:
> > I would consider using a prefix trie.  Unfortunately, such a structure is
> > not built in to Haskell.
> 
> Thanks for this!  It seems that this kind of data structure is what I
> am looking for.  

Excellent.

>          [(a, (Bool, *))]
> to be the "raw" version of PreTrie.  This would mean you also did not
> need to worry about using "helper" functions like insert' and elem'.

I snipped most of the aside :).  The main problem with structures without
names is that it would be very difficult for the typechecker to do its job
(as I understand it, though certainly typechecking is not my forte).  But
basically, this amounts to the same thing as trying to say:

    type MyList a = (a, MyList a)

First of all, there's no base case (like "[]" in lists or "Nothing" in
Maybe, etc.).  So we can sort of fix that by saying:

    type MyList a = (a, Maybe (MyList a))

So the list ends when we get to 'Nothing'.  The problem here is on the
type inference.  Suppose I write:

    ('a', Just ('b', Just ('c', Nothing)))

Now, for a human point of view, this doesn't pose a problem.  This is of
type MyList Char.  The problem is that haskell uses types eagerly, so when
it gets down to 'Nothing', it will say, "okay, what type does this
have?  ah, it must by 'MyList a'.  What does MyList a mean?  Oh, it means
'(a, Maybe (MyList a))'.  Let me substitute."  It will then continue ad
infinitum.  Of course, it's not that stupid and will simply reject the
type at the very begginning for having a loop.

Someone else will have to say a word or two about what would happen if
type inference were done lazily, though presumably "bad things" would
happen (and it's not even clear this would help).

> Why did you call it "PreTrie" and not just "Trie"?  Any particular
> reason?

No reason.  Only because you can have suffix tries too and I would call
those SufTrie...

> Using just "elem" as you had before, caused hugs to give me
> this error:
> 
> Reading file "PreTrie.hs":
> ERROR PreTrie.hs:23 - Definition of variable "elem" clashes with import
> 
> any idea why?

Yeah, I was sloppy.  'elem' is a prelude function for working on
lists.  as you found, you need another name.

> When I wanted to test this stuff in hugs, I had to do things like:
> 
> Main> varElem (insert (insert (insert empty "a") "b") "ab") "b"
> True
> 
> The way I would do things in an imperative language would be something
> like:
>   x = insert empty "a"
>   x = insert x "b"
>   x = insert x "ab"
>   ...
>   varElem x "b"

*eww* :).  you could use a fold, something like:

  foldl insert empty ["a","b","ab"]

foldr is also possible:

  foldr (flip insert) empty ["a","b","ab"]

another thing to do would be to use the infix notation:

   x = empty `insert` "a"
             `insert` "b"
             `insert` "ab"

> Main> insert (insert (insert empty "a") "b") "ab"
> ERROR - Cannot find "show" function for:
> *** Expression : insert (insert (insert empty "a") "b") "ab"
> *** Of type    : PreTrie Char
> 
> I tried to define
>   show :: (PreTrie a) -> String
>   show (PreTrie l) = show l
> but got
> ERROR PreTrie.hs:35 - Definition of variable "show" clashes with import
> 
> Am I on the right track?

Yes.  So 'show' is a class method for the class Show, which means you need
to define PreTrie to be an instance of show.  The easy way to do this is
to put "deriving (Show)" after the data type declaration.  If you want to
learn more about how to write your own instances, here's an example one
for PreTrie:

  instance Show a => Show (PreTrie a) where
    show (PreTrie l) = show l

You could write sometime more complex than that, but that hsould do what
you want...

 - Hal