Re: Combining distinct-thread state monads?

2004-01-08 Thread Dr Mark H Phillips
Hi Wolfgang,

Thanks for your informative reply.  At first I didn't
understand it, but a search on StateT lead me to the
paper Monad Transformers and Modular Interpreters by
Liang, Hudak and Jones, which clarified some of the
ideas for me.

The state transformer approach seems to have
advantageous in that it provides a framework for
building new monads from old, and accessing the
components.  One disadvantage is that it lacks 
symmetry in that one monad is arbitrarily chosen
to sit inside the other.  I found another approach
mentioned called stratification, developed by
David Espinosa in his PhD thesis Semantic Lego.  I
am finding it a little hard to read because he codes
in Scheme, not Haskell, but it sounds promising and
seems to preserve symmetry better.

Are you (or others) aware of this kind of approach being
used in Haskell?

Cheers,

Mark.


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Combining distinct-thread state monads?

2004-01-08 Thread Dr Mark H Phillips
On Tue, 2004-01-06 at 22:58, Graham Klyne wrote:
 I'm not an expert in this, but I think what you are proposing is possible, 
 to a point, possibly assuming that your monads have associated functions to 
 combine and separate the monadic parts.

Thanks for the below illustration of how this problem can be
approached.  I think you are right, this approach could solve
my problem.  The other solution seems to be, as you point out, the use
of monadic transformers.  The problem I have with these is that one
would need to arbitrarily define one monad to be inside the other,
whereas your approach seems more symmetric.  David Espinosa, in his
PhD thesis Semantic Lego seems to have a more symmetric transforming
approach which he calls stratification.  This looks promising, but
he uses Scheme not Haskell so it's a bit hard for me to understand
some parts.

Cheers,

Mark.

P.S. I'm not sure if I need to be subscribed to haskell-cafe to reply
on list.  I guess I'll find out!

 Hmmm, let's try something...
 
 Given:
 
combine  :: ma - mb - mab
separate :: mab - (ma,mb)
 
 (where ma, mb, mab are the separate and combined state monads)
 
f :: ma () - mb () - mc ()
f a b =
  do { ma1 - fa1 a  -- process state in a, returning ma1
 -- fa1 :: ma - mc ma
 ; mb1 - fb1 b  -- process state in b, returning mb1
 ; let mab1 = combine ma1 mb1
 ; mab2 = fab mab1
 ; let (ma2,mb2) = separate mab2
 ; ma3 - fa3 ma2  -- process state in ma2
 ; mb3 - fb3 mb2  -- process state in mb2
 ; return (fc ma3 mb3)
 }
 
 (This code is speculative, not tested in any way.)
 
 In this case, a third monad is used to schedule the operations on the 
 separate monads, so in that respect the entire sequence is performed in a 
 composite monad, within which methods defined for the separate monads can 
 be invoked.
 To get the results, Monad 'mc' would need to provide a way to pick them out.
 
 It looks as if the combined monad 'mab' is probably superfluous.  I think 
 the composite monad 'mc' might be avoided, but some of the efficiency 
 advantage of monads would be lost as the single-threading of each monad is 
 potentially broken.
 
 I think that this may be all be achieved more cleanly using the monad 
 transformer libraries and 'lift' methods -- can a state transformer be 
 applied to a state monad?
 
 What I have noticed in my work with monads is that in most respects they 
 can be treated just like any other value.  Although they look different, a 
 do sequence is just a monad-returning function, and any monad-returning 
 function may be a do sequence.
 
 aside
 In my own work, I was pleasantly surprised how easy it was to use a Parsec 
 parser monad (effectively a state monad, I think) to parse some data and 
 return a combined state+IO monad, effectively precompiling a script, which 
 which could then be executed by applying the resulting monad to an initial 
 state, all within an IO monad.  The code which does this can be seen at:
http://www.ninebynine.org/Software/Swish-0.2.0/SwishScript.hs
 
 The main parser declaration is:
script :: N3Parser [SwishStateIO ()]
 where 'script' is a Parsec parser monad which parses a script and returns a 
 list of 'SwishStateIO ()' values, each of which is a combined state+IO monad.
 /aside
 
 #g
 --
 
 Consider two state threads.  The first has each state
 being a non-negative int, thought of as a string of
 binary digits.  The second thread has each state
 being a bool.
 
 Now I want to have a state monad which modifies
 both threads as follows.  Consider input states i (the
 int thought of as binary string) and b (the bool),
 and output states i' and b'.
 
b' = not (b  (i `mod` 2))
i' = i `div` 2
 
 As you can see, both of these should be able to do
 update-in-place provided the above order is adhered to.
 We could achieve this using state monads where state
 is an (Int, Bool) pair.  We would have one monad
 which did the first line, leaving i unchanged and
 a second monad which did the second line, leaving
 b' unchanged.
 
 But... what if before this interaction, the int
 thread and the bool thread were separate monads
 doing their own thing, and we just wanted to
 combine these threads briefly (using the above
 interaction) before letting the threads do their
 own thing again?  Is this possible?
 
 Also, suppose we have previously defined an int thread
 monad which takes i, returns a value of i `mod` 2,
 and changes the state to i' = i `div` 2.  Suppose
 also we have previously defined a bool thread
 monad which takes b, returns a nothing value, and
 changes the state to b' = not b.  Can we use
 these two monads (each acting on different
 threads), to form a combined-interaction monad
 that does (same as before):
 
b' = not (b  (i `mod` 2))
i' = i `div` 2
 
 I hope this is possible.  It would facilitate
 both code reuse and readability.  However I
 fear that it is not, requiring 

Re: Function composition and currying

2003-07-25 Thread Dr Mark H Phillips
Thanks to all the people who responded to my question!

The solution from Wolfgang Jeltsch:

  (f.).g

was what I was after.  But the other responses were
useful also.

Thanks!

Mark.

On Thu, 2003-07-17 at 09:57, Dr Mark H Phillips wrote:
 Hi,
 
 Hopefully this is a simple question.  I am wanting to know good ways
 of using ., the function composition operator, when dealing with
 currying functions.
 
 Suppose I have the following functions defined:
 
   f :: Int - Int
   f x = x*x
 
   g :: Int - Int - Int
   g a b = a + b
 
 If I wish to add 1 and 2 together and then square them I can do:
 
   f (g 1 2) = 9
 
 but what if I wish to use function composition in the process?
 
 I can't do 
 
   (f.g) 1 2
 
 because the 2 doesn't get passed in till too late.
 
 I could do
 
   (f.(g 1)) 2
 
 or even
 
   (f.(uncurry g)) (1,2)
 
 But what I really want is a function with signature Int - Int - Int.
 The answer is probably:
 
   (curry (f.(uncurry g))) 1 2
 
 but this seems awfully messy just to do f (g 1 2).
 
 And what if g were a function with three curried arguments?  Then
 uncurry and curry wouldn't apply.  What then?
 
 Is there a better way?
 
 Thanks,
 
 Mark.
 
 
 -- 
 Dr Mark H Phillips
 Research Analyst (Mathematician)
 
 AUSTRICS - smarter scheduling solutions - www.austrics.com
 
 Level 2, 50 Pirie Street, Adelaide SA 5000, Australia
 Phone +61 8 8226 9850
 Fax   +61 8 8231 4821
 Email [EMAIL PROTECTED]
 
 ___
 Haskell mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell
-- 
Dr Mark H Phillips
Research Analyst (Mathematician)

AUSTRICS - smarter scheduling solutions - www.austrics.com

Level 2, 50 Pirie Street, Adelaide SA 5000, Australia
Phone +61 8 8226 9850
Fax   +61 8 8231 4821
Email [EMAIL PROTECTED]

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Function composition and currying

2003-07-16 Thread Dr Mark H Phillips
Hi,

Hopefully this is a simple question.  I am wanting to know good ways
of using ., the function composition operator, when dealing with
currying functions.

Suppose I have the following functions defined:

  f :: Int - Int
  f x = x*x

  g :: Int - Int - Int
  g a b = a + b

If I wish to add 1 and 2 together and then square them I can do:

  f (g 1 2) = 9

but what if I wish to use function composition in the process?

I can't do 

  (f.g) 1 2

because the 2 doesn't get passed in till too late.

I could do

  (f.(g 1)) 2

or even

  (f.(uncurry g)) (1,2)

But what I really want is a function with signature Int - Int - Int.
The answer is probably:

  (curry (f.(uncurry g))) 1 2

but this seems awfully messy just to do f (g 1 2).

And what if g were a function with three curried arguments?  Then
uncurry and curry wouldn't apply.  What then?

Is there a better way?

Thanks,

Mark.


-- 
Dr Mark H Phillips
Research Analyst (Mathematician)

AUSTRICS - smarter scheduling solutions - www.austrics.com

Level 2, 50 Pirie Street, Adelaide SA 5000, Australia
Phone +61 8 8226 9850
Fax   +61 8 8231 4821
Email [EMAIL PROTECTED]

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: Best recursion choice for penultimax

2002-11-25 Thread Dr Mark H Phillips
Thanks for your alternative solutions.  (I also take
Mark Jones' point that there was an error with some of my
initial solutions.)

On Mon, 2002-11-25 at 16:36, Mark P Jones wrote:
 To your three implementations, let me add another two.  If you are
 looking
 for the smallest possible definition, consider the following:
 
   import List
 
   penultimax1 :: Ord a = [a] - a
   penultimax1  = head . tail . sortBy (flip compare)
 
 A little more algorithmic sophistication leads to the following
 alternative that can find the penultimax with only  n + log2 n
 comparisons (approx), where n is the length of the list.

Is this n + log(2n) or n + (log n)^2 or perhaps n + log_base_2 n?

Also, how did you calculate this?  (I am new to O(.) calculations
involving lots of recursion (ie in functional languages))

 
   penultimax :: Ord a = [a] - (a, a)
   penultimax  = tournament . map enter
where enter x = (x, [])
 
  tournament [(x, xds)] = (x, maximum xds)
  tournament others = tournament (round others)
 
  round ((x,xds):(y,yds):others)
| x=y  = (x, y:xds) : rest
| otherwise = (y, x:yds) : rest
  where rest = round others
  round xs  = xs
 
 
 Neat algorithm eh?  But be careful ...

It is interesting!

 
 | How do I work out which is best to use?  Is there
 | one clear winner, or will they each have pros and
 | cons?
 
 Some quick tests with Hugs +s on a example list that I constructed
 with 576 elements give food for thought:

Thanks for the idea of using hugs +s.  I haven't seen this
before.

 
   reductions cells
my one liner  403511483
tournament705312288
your penultimax  1671520180
your penultimax2  746610344
your penultimax3  860513782

 Hope this helps (or at least, is entertaining :-)

Yes.  Thanks!

Mark.

-- 
Dr Mark H Phillips
Research Analyst (Mathematician)

AUSTRICS - smarter scheduling solutions - www.austrics.com

Level 2, 50 Pirie Street, Adelaide SA 5000, Australia
Phone +61 8 8226 9850
Fax   +61 8 8231 4821
Email [EMAIL PROTECTED]

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Best recursion choice for penultimax

2002-11-25 Thread Dr Mark H Phillips
On Tue, 2002-11-26 at 02:38, Richard Braakman wrote:
 penultimax1' :: Ord a = [a] - a
 penultimax1' = head . tail . sortBy (flip compare) . nub

What does nub stand for?  (This is the first I've heard of it.)
From the definition in List.hs it seems to remove repeats, keeping
only the first.  Is there documentation on List.hs, along the lines
of the A Tour of the Haskell Prelude?

Thanks,

Mark.

-- 
Dr Mark H Phillips
Research Analyst (Mathematician)

AUSTRICS - smarter scheduling solutions - www.austrics.com

Level 2, 50 Pirie Street, Adelaide SA 5000, Australia
Phone +61 8 8226 9850
Fax   +61 8 8231 4821
Email [EMAIL PROTECTED]

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Best recursion choice for penultimax

2002-11-24 Thread Dr Mark H Phillips
Hi,

I have just implemented the function penultimax which takes a list
of positive integers and produces the penultimate maximum, that is,
the next biggest integer in the list after the maximum.  Eg:

penultimax [15,7,3,11,5] = 11

One implementation is:

penultimax :: [Int] - Int
penultimax ms = foldr max 0 (filter (msMax) ms)
  where
  msMax = foldr max 0 ms

But I can think of two variations which might be more efficient:

penultimax2 :: [Int] - Int
penultimax2 ms = penultimax2' ms 0 0
  where
  penultimax2' :: [Int] - Int - Int - Int
  penultimax2' [] p q = q
  penultimax2' (m:ms) p q
| mp   = penultimax2' ms m p
| mq   = penultimax2' ms p m
| otherwise = penultimax2' ms p q

penultimax3 :: [Int] - Int
penultimax3 ms = snd (maxpenmax ms)
  where
  maxpenmax :: [Int] - (Int,Int)
  maxpenmax [] = (0,0)
  maxpenmax [m] = (m,0)
  maxpenmax (m:ms)
| mp   = (m,p)
| mq   = (p,m)
| otherwise = (p,q)
where
(p,q) = maxpenmax ms

How do I work out which is best to use?  Is there
one clear winner, or will they each have pros and
cons?

Thanks,

Mark.

-- 
Dr Mark H Phillips
Research Analyst (Mathematician)

AUSTRICS - smarter scheduling solutions - www.austrics.com

Level 2, 50 Pirie Street, Adelaide SA 5000, Australia
Phone +61 8 8226 9850
Fax   +61 8 8231 4821
Email [EMAIL PROTECTED]

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Behaviour of div mod with negative arguments?

2002-09-25 Thread Dr Mark H Phillips

Hi,

Does Haskell specify how div and mod should behave when
given one or both arguments negative?

Eg, in hugs we get:

div   13  = 0
div (-1)   3  = -1
div   1  (-3) = -1
div (-1) (-3) = 0

and so on.

I've had a bit of a look for where div and mod are
specified exactly, but I can only find a definition of
their type.  Are they defined anywhere?  And what is
the rational behind the negative arguments part of
the definition?

Thanks,

Mark.

P.S.  I notice in hugs if I type -1 `div` 3 the `div`
binds to the 1 and 3 first, and only applies the -
at the end.  Is there a reason why the unary - has
weak binding?

-- 
Dr Mark H Phillips
Research Analyst (Mathematician)

AUSTRICS - smarter scheduling solutions - www.austrics.com

Level 2, 50 Pirie Street, Adelaide SA 5000, Australia
Phone +61 8 8226 9850
Fax   +61 8 8231 4821
Email [EMAIL PROTECTED]

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: where block local to a guard?

2002-09-17 Thread Dr Mark H Phillips

Thanks for the explanation!

On Tue, 2002-09-17 at 19:07, Brian Boutel wrote:
 You can't do this because where clauses are not part of the expression 
 syntax. If they were, expressions like
 
   let a=b in c where d=e
 or
   if a then b else c where d=e
 
 whould be ambiguous, unless you adopt arbitrary rules about the 
 prededences, and such arbitrary rules are considered a bad thing.

I'm trying to see how ambiguity might arise.  Do you mean something
like:

let a=1 in a+a where a=3

or have you something different in mind?

And I can't yet think of a situation where

if a then b else c where d=e

would cause problems.

Cheers,

Mark.


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Good layout style? (was: Re: where block local to a guard?)

2002-09-17 Thread Dr Mark H Phillips

On Wed, 2002-09-18 at 01:26, Hamilton Richards wrote:
 You can get the effect you're after by using let-expressions:
 
   functn :: Int - Int
   functn i
   | i5   = let t = functn (i-2) in t * i
   | i0   = let t = functn (i-1) in t * i
   | otherwise = 1
 
 'where' is part of the syntax of definitions, not expressions. This 
 enables a name defined in a where-clause to be used in more than one 
 guarded expression.

Thanks for this!  It would seem let ... in ... is what I want.

But I'm a bit confused about how to use the off-side rule in
conjunction with let.  Do I do:

let a=1
b=2
c=3
in a*b*c

or do I do:

let
a=1
b=2
c=3
in
a*b*c

or, in the context of a guard, do I do:

| i5  = let a=1; b=2; c=3
  in a*b*c

Basically I'm a bit confused about how the offside rule
works in various situations.

With if ... then ... else ... I don't know whether I should be doing

  f x = if x5 
then x*x 
else 2*x

or

  f x = if x5
then x*x
else 2*x

or

  f x = if x5
  then x*x
else 2*x

or what!

Hugs seems to think they are all legal.  Is there any rational as to
how to do layout?  Any tips would be greatly appreciated!

Thanks,

Mark.


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



where block local to a guard?

2002-09-16 Thread Dr Mark H Phillips

Hi,

Suppose you have some function

functn :: Int - Int
functn i
| i5   = t  * i
| i0   = t_ * i
| otherwise = 1
where
t  = functn (i-2)
t_ = functn (i-1)

Notice that t and t_ are really local to a guard, rather
than to the whole guard section.  Why then, can't you write:

functn :: Int - Int
functn i
| i5   = t * i
where
t = functn (i-2)
| i0   = t * i
where
t = functn (i-1)
| otherwise = 1

In particular, the above would mean you wouldn't need two names 
t and t_, you could just use t for both!

Am I doing something wrongly, or is there a good reason why
where isn't allowed to be used in this way?

Thanks,

Mark.


-- 
Dr Mark H Phillips
Research Analyst (Mathematician)

AUSTRICS - smarter scheduling solutions - www.austrics.com

Level 2, 50 Pirie Street, Adelaide SA 5000, Australia
Phone +61 8 8226 9850
Fax   +61 8 8231 4821
Email [EMAIL PROTECTED]

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: More suitable data structure needed

2002-08-22 Thread Dr Mark H Phillips

On Wed, 2002-08-21 at 17:50, Dylan Thurston wrote:
 This is the same as one way of representing search trees, called a
 trie.  Two representations in Haskell are:
 
  data Trie a = Trie [(a, Trie a)]

I touched on the following in my response to Hal Daume's email, but it's
probably worth asking properly...

Am I right in thinking there is no way of doing this using an
essential type?  What I mean is, 

  data Age = Age Int
  data Names = Names [String]
  data Person = Person (Age,Names)

can be used to represent the details of a person, but the essential
type corresponding to Person, is

  (Int,[String])

Having the type Person is useful in that, basically it is a duplicate
of the essential type, to be used for a specialized purpose.  But there
is always the option of converting it to the essential type, thereby
allowing higher order functions to be applied to it.

But for the Trie type you have above, I am not aware of any way of
converting this to an essential type.  What I am thinking, is
something like
[(a, *)]
where '*' means to recursively refer to yourself.

 or, using the FiniteMap module, if you only care about the set of
 lists,
 
  data Trie a = Trie (FiniteMap a (Trie a))

Am I right in thinking that FiniteMap is like a list, but that it is
more efficient with random access use than a normal list?

Thanks for your help,

Mark.



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



More suitable data structure needed

2002-08-21 Thread Dr Mark H Phillips

Hi,

Consider the following data structure, effectively
of type [[(Int,Int)]]:

(2,5) (1,3) (2,0)
(2,5) (1,2) (1,1) (1,0)
(2,5) (3,1)
(1,5) (2,4) (2,0)
(1,5) (1,4) (1,3) (1,1) (1,0)
(1,5) (1,4) (2,2) (1,0)
(1,5) (1,4) (1,2) (2,1)
(1,5) (2,3) (1,2) (1,0)
(1,5) (2,3) (2,1)
(1,5) (1,3) (2,2) (1,1)
(1,5) (4,2)

Notice that the some of the inner lists start off the same.
If we delete the repetitions, we can more clearly see an
emerging structure.

(2,5) (1,3) (2,0)
  (1,2) (1,1) (1,0)
  (3,1)
(1,5) (2,4) (2,0)
  (1,4) (1,3) (1,1) (1,0)
(2,2) (1,0)
(1,2) (2,1)
  (2,3) (1,2) (1,0)
(2,1)
  (1,3) (2,2) (1,1)
  (4,2)

I would like to represent this structure in Haskell, but 
am not sure quite the best way of doing it.  (I am relatively
new to Haskell.)  I think I want to do something like:

[
[(2,5),[(1,3),[(2,0)]],
   [(1,2),[(1,1),[(1,0)]]],
   [(3,1)]],
[(1,5),[(2,4),[(2,0)]],
   [(1,4),[(1,3),[(1,1),[(1,0)]]],
  [(2,2),[(1,0)]],
  [(1,2),[(2,1)]]],
   [(2,3),[(1,2),[(1,0)]],
  [(2,1)]],
   [(1,3),[(2,2),[(1,1)]]],
   [(4,2)]]
]

But what is the best way to represent this in Haskell?  (Clearly
I can't do exactly this, because Haskell requires all list elements
to be of the same type.)

Thanks,

Mark.


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: More suitable data structure needed

2002-08-21 Thread Dr Mark H Phillips

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.  

[begin aside]

It seems a pity that one needs to give the data type
a special name in order for it to be recursive.  What I mean, is that
other types can be expressed using built in manipulators, eg
[(Int,[Char])]
Of course you can use data to create specialized types which are
essentially the same in structure, but earmarked for specialized use,
but there is always the raw type to use as a default...  But the
same is not true (so it seems) for recursive types.  Ie, it would
be nice to represent what you call PreTrie as a raw type.  Imagine
you used the '*' symbol to mean recursively refer to yourself, then
you could write
 [(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'.

Anyway, that's just a few thoughts I've had --- perhaps they are
naive?  After all, I am fairly new to Haskell :-)

[end aside]

 A naive implementation would be something like (I haven't tested/compiled
 this code, so there are 'bugs'...consider it 'psuedo-haskell'):

I've taken your code and fixed the 'bugs' (I think).  I've got a few
questions.

Here's the fixed version, along with my questions:

  data PreTrie a = PreTrie [(a, (Bool, PreTrie a))]
-- (element, is-element-in-trie, children)
  
Why did you call it PreTrie and not just Trie?  Any particular
reason?

  empty :: PreTrie a
  empty = PreTrie []
  
  insert :: Eq a = PreTrie a - [a] - PreTrie a  
  insert (PreTrie l) a = PreTrie (insert' l a)
  
  insert' [] [x] = [(x, (True, empty))]
  insert' [] (x:xs) = [(x, (False, insert empty xs))]
  insert' ((a,(b,c)):ls) [x]
| a == x= (a,(True,c)) : ls
| otherwise = (a,(b,c)) : insert' ls [x]
  insert' ((a,(b,c)):ls) (x:xs)
| a == x= (a,(b,insert c xs)) : ls
| otherwise = (a,(b,c)) : insert' ls (x:xs)
  
  varElem :: Eq a = PreTrie a - [a] - Bool
  varElem (PreTrie l) a = varElem' l a

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?
  
  varElem' [] _ = False
  varElem' ((a,(b,c)):ls) [x] 
| a == x = b
| otherwise = varElem' ls [x]
  varElem' ((a,(b,c)):ls) (x:xs)
| a == x = varElem c xs
| otherwise = varElem' ls (x:xs)

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
Now obviously I can't do this, but is there some different technique
for building up a data structure like this, or is it just a case of
me getting used to long lines and lots of brackets?

One more thing... when I did:

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?

Thanks for your help!

Cheers,

Mark.


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell