Re: Happy and Macros (was Re: ANNOUNCE: Happy 1.10 released)

2001-05-14 Thread Carl R. Witty

Manuel M. T. Chakravarty [EMAIL PROTECTED] writes:

 I didn't say that this works for any kind of parser
 combinator, I merely said that it works Doitse's and mine.
 Both implement SLL(1) parsers for which - as I am sure, you
 know - there exists a decision procedure for testing
 ambiguity.  More precisely, whenever the library can build
 the parse table, the grammar must be non-ambigious.  As the
 parse table construction is lazy, this covers only the
 productions exercised in that particular run, which is why I
 said that you need a file involving all grammar constructs
 of the language.  Nothing magic here.

Wow.  Clearly I haven't spent enough time looking at your parser
systems.  I apologize for my incorrect assumptions and statements.

Carl Witty

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Permutations of a list

2001-05-14 Thread Andy Fugard

Hi all,

I'm currently teaching myself a little Haskell.  This morning I coded the 
following, the main function of which, permutate, returns all the 
permutations of a list.  (Well it seems to at least!)


insertAt :: a - Int - [a] - [a]
insertAt x i xs
 | i  0 || i  length xs  = error invalid position
 | otherwise   = front ++ x:back
   where (front,back) = splitAt i xs

insertAtAll :: a - (Int,Int) - [a] - [[a]]
insertAtAll x (i,j) xs
 | i  j  = error PRE: i = j
 | i == j = [insertAt x i xs]
 | otherwise  = (insertAt x i xs):(insertAtAll x (i+1,j) xs)

buildPermList :: a - [[a]] - [[a]]
buildPermList x xs
 | length xs == 0  = []
 | otherwise   = list ++ buildPermList x (tail xs)
   where list = insertAtAll x (0, length curr) curr;
 curr = head xs

permutate :: [a] - [[a]]
permutate xs
 | length xs == 0 = [[]]
 | otherwise  = buildPermList (last xs) (permutate (init xs))


and some test runs

Main permutate 
[]
Main permutate a
[a]
Main permutate ab
[ba,ab]
Main permutate abc
[cba,bca,bac,cab,acb,abc]


My main question is really what facilities of the language I should be 
looking at to make this code more elegant!  As you can see I currently know 
only the basics of currying, and some list operations.

Also regarding the method of generating the permutations; is there a better 
way?  The current is just Method 1 from Knuth's TAOCP, volume 1 (3rd 
edition), p45-46.


Thanks in advance,

Andy


--
[  Andy Fugard /'andi fju:ga:d/  ]
[  Phone:  +44 (0)7901 603075]


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



Re: Permutations of a list

2001-05-14 Thread Ralf Hinze

Andy Fugard wrote:

 My main question is really what facilities of the language I should be
 looking at to make this code more elegant!  As you can see I currently know
 only the basics of currying, and some list operations.

Definitely list comprehensions! I digged out some old code:

 module Perms where

Permutations.

 perms :: [a] - [[a]]
 perms []  =  [ [] ]
 perms (a : x) =  [ z | y - perms x, z - insertions a y ]

 insertions:: a - [a] - [[a]]
 insertions a []   =  [ [a] ]
 insertions a x@(b : y)=  (a : x) : [ b : z | z - insertions a y ]
 
Using deletions instead of insertions; generates the permutations
in lexicographic order, but is a bit slower.
 
 perms':: [a] - [[a]]
 perms' [] =  [ [] ]
 perms' x  =  [ a : z | (a, y) - deletions x, z - perms' y ]

 deletions :: [a] - [(a, [a])]
 deletions []  =  []
 deletions (a : x) =  (a, x) : [ (b, a : y) | (b, y) - deletions x ]

Cheers, Ralf

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



Re: Permutations of a list

2001-05-14 Thread Andy Fugard

At 13:43 14/05/01 +0200, Ralf Hinze wrote:
Andy Fugard wrote:

  My main question is really what facilities of the language I should be
  looking at to make this code more elegant!  As you can see I currently know
  only the basics of currying, and some list operations.

Definitely list comprehensions! I digged out some old code:

[ ... ]

Thanks for the quick response; that's much nicer!  I think I'll have a look 
at list comprehensions

Cheers,

Andy


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



permutations. Reply

2001-05-14 Thread S.D.Mechveliani

Andy Fugard [EMAIL PROTECTED]  writes

 Hi all,

 I'm currently teaching myself a little Haskell.  This morning I coded the 
 following, the main function of which, permutate, returns all the 
 permutations of a list.  (Well it seems to at least!)

 [..]

The BAL library implements several operations with permutations.
In particular, it can list permutations by applying  nextPermutation.
You may look into the source and demonstration example:

  http://www.botik.ru/pub/local/Mechveliani/basAlgPropos/

-
Serge Mechveliani
[EMAIL PROTECTED]

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



CA proposal by D.Thurston

2001-05-14 Thread S.D.Mechveliani

I was said that there exists an algebraic library proposal for 
Haskell
(version 0.02) dated by February (2001?), by Dylan Thurston.

Who could, please, tell me where to download this document from?
For I could not find it from  http://haskell.org

Thanks in advance for the help.

-
Serge Mechveliani
[EMAIL PROTECTED]









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



Re: CA proposal by D.Thurston

2001-05-14 Thread Ch. A. Herrmann

Hi Haskellers,

 S == S D Mechveliani S.D.Mechveliani writes:

S I was said that there exists an algebraic library proposal for
S Haskell (version 0.02) dated by February (2001?), by Dylan
S Thurston.

that sounds interesting for me. Sorry, that I don't have an answer to your 
question, but I like to state some points about an algebraic library.

A standard algebraic library has several advantages to many different
tools developed by individual programmers:

(1) One can benefit from the knowledge and experience of others
(and of their work also, of course)
(2) An open discussion process will help to avoid
errors or difficulties in use
(3) Programs written by others that use the library functions
are more comprehensible

I've got no impression of how such a library may look like
and if the library is meant to be updated from time to time.
Anyway, an algebraic library is important:
it is nice that Haskell has the rational numbers but recently, it
appeared useful for me also to have the algebraic numbers, e.g.,
to evaluate expressions containing roots exactly. The problem is
that I'm not an expert in this stuff and thus, be very glad if
such things are added by an expert.

On the other hand, I'd like to add things like a linear equation solver
for a non-invertible system which may help to convince people that
Haskell provides more features than other programming languages do.

Cheers
Christoph

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



Re: CA proposal by D.Thurston

2001-05-14 Thread Fergus Henderson

On 14-May-2001, S.D.Mechveliani [EMAIL PROTECTED] wrote:
 I was said that there exists an algebraic library proposal for 
 Haskell (version 0.02) dated by February (2001?), by Dylan Thurston.
 
 Who could, please, tell me where to download this document from?
 For I could not find it from  http://haskell.org

It was posted to the haskell-cafe list,
and is available from the archives of that list:
http://haskell.org/pipermail/haskell-cafe/2001-February/000331.html.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  I have always known that the pursuit
|  of excellence is a lethal habit
WWW: http://www.cs.mu.oz.au/~fjh  | -- the last words of T. S. Garp.

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



Re: Happy and Macros (was Re: ANNOUNCE: Happy 1.10 released)

2001-05-14 Thread Carl R. Witty

Manuel M. T. Chakravarty [EMAIL PROTECTED] writes:

 I didn't say that this works for any kind of parser
 combinator, I merely said that it works Doitse's and mine.
 Both implement SLL(1) parsers for which - as I am sure, you
 know - there exists a decision procedure for testing
 ambiguity.  More precisely, whenever the library can build
 the parse table, the grammar must be non-ambigious.  As the
 parse table construction is lazy, this covers only the
 productions exercised in that particular run, which is why I
 said that you need a file involving all grammar constructs
 of the language.  Nothing magic here.

Wow.  Clearly I haven't spent enough time looking at your parser
systems.  I apologize for my incorrect assumptions and statements.

Carl Witty

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



standard library. Reply

2001-05-14 Thread S.D.Mechveliani

Ch. A. Herrmann [EMAIL PROTECTED]
writes

 [..]
 Anyway, an algebraic library is important:
 it is nice that Haskell has the rational numbers but recently, it
 appeared useful for me also to have the algebraic numbers, e.g.,
 to evaluate expressions containing roots exactly. The problem is
 that I'm not an expert in this stuff and thus, be very glad if
 such things are added by an expert.

 On the other hand, I'd like to add things like a linear equation solver
 for a non-invertible system which may help to convince people that
 Haskell provides more features than other programming languages do.


The BAL library
http://www.botik.ru/pub/local/Mechveliani/basAlgPropos/

provides such linear solver, as well as operations with roots.
For example, the root of 
 x^5 - x + 1 

can be handled (in many respects) in BAL as only a residue of 
polynomials modulo this equation - a data like  (Rse ...(x^5-x+1))).
 
But BAL is not a standard library.

And there is another point:

 [..] for a non-invertible system which may help to convince people that
 Haskell provides more features than other programming languages do.

In any case, we have to distinguish between a standard library and 
an application. A standard library should be small. 
I think, for Haskell, it should be something that you mention now. 
But, for example, the true algebraic number theory algorithms are too
complex, it is for the non-standard application writers.

And if a language is good, there should come many special applications
(non-standard ones). Haskell's www page does reveal some. 

Regards,

-
Serge Mechveliani
[EMAIL PROTECTED]



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



Things and limitations...

2001-05-14 Thread Tom Pledger

Juan Carlos Arevalo Baeza writes:
 :
 | First, about classes of heavily parametric types. Can't be done, I 
 | believe. At least, I haven't been able to. What I was trying to do (as an 
 | exercise to myself) was reconverting Graham Hutton and Erik Meijer's 
 | monadic parser library into a class. Basically, I was trying to convert the 
 | static:
 | 
 | ---
 | newtype Parser a = P (String - [(a,String)])
 | item :: Parser Char
 | force :: Parser a - Parser a
 | first :: Parser a - Parser a
 | papply :: Parser a - String - [(a,String)]
 | ---
 | 
 | ---
 | class (MonadPlus (p s v)) = Parser p where
 |  item :: p s v v
 |  force :: p s v a - p s v a
 |  first :: p s v a - p s v a
 |  papply :: p s v a - s - [(a,s)]
 | ---
 | 
 | I have at home the actual code I tried to make work, so I can't just 
 | copy/paste it, but it looked something like this. Anyway, this class would 
 | allow me to define parsers that parse any kind of thing ('s', which was 
 | 'String' in the original lib), from which you can extract any kind of 
 | element ('v', which was 'Char') and parse it into arbitrary types (the 
 | original parameter 'a'). For example, with this you could parse, say, a 
 | recursive algebraic data structure into something else.
 | 
 | Nhc98 wouldn't take it. I assume this is NOT proper Haskell. The 
 | questions are: Is this doable? If so, how? Is this not recommendable? If 
 | not, why?

I did something similar recently, but took the approach of adding more
parameters to newtype Parser, rather than converting it into a class.
Here's how it begins:

typeIndent  = Int
typeIL a= [(a, Indent)]
newtype Parser a m b= P (Indent - IL a - m (b, Indent, IL a))

instance Monad m = Monad (Parser a m) where
return v= P (\ind inp - return (v, ind, inp))
(P p) = f = P (\ind inp - do (v, ind', inp') - p ind inp
let (P p') = f v
p' ind' inp')
fail s  = P (\ind inp - fail s)

instance MonadPlus m = MonadPlus (Parser a m) where
mzero   = P (\ind inp - mzero)
(P p) `mplus` (P q) = P (\ind inp - (p ind inp `mplus` q ind inp))

item   :: MonadPlus m = Parser a m a
item= P p
where
p ind []= mzero
p ind ((x, i):inp)
| i  ind   = mzero
| otherwise = return (x, ind, inp)

This differs from Hutton's and Meijer's original in these regards:

  - It's generalised over the input token type: the `a' in
`Parser a m b' is not necessarily Char.

  - It's generalised over the MonadPlus type in which the result is
given: the `m' in `Parser a m b' is not necessarily [].

  - It's specialised for parsing with a layout rule: there's an
indentation level in the state, and each input token is expected
to be accompanied by an indentation level.

You could try something similar for your generalisations:

newtype Parser ct r = P (ct - [(r, ct)])
-- ct: collection of tokens, r: result

instance SuitableCollection ct = Monad (Parser ct)
where ...

instance SuitableCollection ct = MonadPlus (Parser ct)
where ...

item   :: Collects ct t = Parser ct t
force  :: Parser ct r - Parser ct r
first  :: Parser ct r - Parser ct r
papply :: Parser ct r - ct - [(r, ct)]

The `SuitableCollection' class is pretty hard to define, though.
Either it constrains its members to be list-shaped, or it prevents you
from reusing functions like `item'.  Hmmm... I think I've just
stumbled across your reason for treating Parser as a class.

When the input isn't list-shaped, is the activity still called
parsing?  Or is it a generalised fold (of the input type) and unfold
(of the result type)?

Regards,
Tom

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