[Haskell-cafe] Apache HTTP Server And Haskell

2006-07-31 Thread Kaveh Shahbazian

Is there a mod_haskell (like mod_perl and mod_python) for Apache HTTP
server? Does anyone know about it?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] [Parsec] Backtracking with try does not work for me?

2006-07-31 Thread Stephane Bortzmeyer
I'm trying to write a Parsec parser for a language which authorizes
(this is a simplified example) a or a,b,c or a,c or a,b. (I
can change the grammar but not the language.)

The first attempt was:

* CUT HERE 

import Text.ParserCombinators.Parsec
import System (getArgs)

comma = char ','

minilang = do
   char 'a'
   optional (do {comma ; char 'b'})
   optional (do {comma ; char 'c'})
   eof
   return OK

run parser input
= case (parse parser  input) of
Left err - putStr (parse error at  ++ (show err) ++ \n)
Right x  - putStr (x ++ \n)

main = do
  args - getArgs
  run minilang (head args)

* CUT HERE 

Of course, it fails for a,c:

parse error at (line 1, column 3):
unexpected c
expecting b

for a reason explained in Parsec's documentation (the parser optional
(do {comma ; char 'b'}) already consumed the input, do note the
column number).

What puzzles me is that the solution suggested in Parsec's
documentation does not work either:

* CUT HERE ***

minilang = do
   char 'a'
   try (optional (do {comma ; char 'b'}))
   optional (do {comma ; char 'c'})
   eof
   return OK

* CUT HERE ***

parse error at (line 1, column 2):
unexpected c
expecting b

Apparently, try was used (do note that the column number indicates
that there was backtracking) but the parser still fails for
a,c. Why?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Fwd: [Haskell-cafe] Apache HTTP Server And Haskell

2006-07-31 Thread Kaveh Shahbazian

Thanks, But it seems to be dead! (Last news on 18 Apr 2002). Is there
a more mature one?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Apache HTTP Server And Haskell

2006-07-31 Thread minh thu

2006/7/31, Kaveh Shahbazian [EMAIL PROTECTED]:

Thanks, But it seems to be dead! (Last news on 18 Apr 2002). Is there
a more mature one?


it seems the answer (to which you say thanks) was not posted on the
mailing list...
what was it ?
mt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Apache HTTP Server And Haskell

2006-07-31 Thread Lemmih

On 7/31/06, Kaveh Shahbazian [EMAIL PROTECTED] wrote:

Is there a mod_haskell (like mod_perl and mod_python) for Apache HTTP
server? Does anyone know about it?


There is. However, you're way better off using FastCGI.
http://www.cs.chalmers.se/~bringert/darcs/haskell-fastcgi/doc/

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


Re: [Haskell-cafe] Apache HTTP Server And Haskell

2006-07-31 Thread Jason Dagit

On 7/31/06, Lemmih [EMAIL PROTECTED] wrote:

On 7/31/06, Kaveh Shahbazian [EMAIL PROTECTED] wrote:
 Is there a mod_haskell (like mod_perl and mod_python) for Apache HTTP
 server? Does anyone know about it?

There is. However, you're way better off using FastCGI.
http://www.cs.chalmers.se/~bringert/darcs/haskell-fastcgi/doc/


And perhaps one of these will also be useful:
HSP http://www.cs.chalmers.se/~d00nibro/hsp/
Wash http://www.informatik.uni-freiburg.de/~thiemann/WASH/

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


Re: [Haskell-cafe] [Parsec] Backtracking with try does not work for me?

2006-07-31 Thread Matthias Fischmann


On Mon, Jul 31, 2006 at 09:04:32AM +0200, Stephane Bortzmeyer wrote:
 
 minilang = do
char 'a'
try (optional (do {comma ; char 'b'}))
optional (do {comma ; char 'c'})
eof
return OK
 
 parse error at (line 1, column 2):
 unexpected c
 expecting b
 
 Apparently, try was used (do note that the column number indicates
 that there was backtracking) but the parser still fails for
 a,c. Why?

minilang = do
   char 'a'
   try b | (return '-')
   optional c
   eof
   return OK
  where
  b = do { comma ; char 'b' }
  c = do { comma ; char 'c' }


The (return 'x') is needed for type consistency.  The (try) combinator
doesn't spare you the error, it merely resets the cursor on the input
stream.  To catch the parse error, you need to name a throwaway
alternative.

cheers,
matthias



-- 
Institute of Information Systems, Humboldt-Universitaet zu Berlin

web:  http://www.wiwi.hu-berlin.de/~fis/
e-mail:   [EMAIL PROTECTED]
tel:  +49 30 2093-5742
fax:  +49 30 2093-5741
office:   Spandauer Strasse 1, R.324, 10178 Berlin, Germany
pgp:  AD67 CF64 7BB4 3B9A 6F25  0996 4D73 F1FD 8D32 9BAA


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


[Haskell-cafe] Re: [Parsec] Backtracking with try does not work for me?

2006-07-31 Thread Stephane Bortzmeyer
On Mon, Jul 31, 2006 at 10:59:14AM +0200,
 Matthias Fischmann [EMAIL PROTECTED] wrote 
 a message of 89 lines which said:

try b | (return '-')
...
 The (return 'x') is needed for type consistency. 

OK, it works. Many thanks for the solution and the explanations.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] What is the state if Unicode in Haskell implementations?

2006-07-31 Thread Olof Bjarnason
Hi there!I'm trying to user Haskell as a code-generating language, specifically generating C# code files. The wish list is1) reading UTF-8 coded text files into unicode-enabled Strings, lets call them UString
2) writing UStrings to UTF-8 coded text files3) using unicode strings in-code, that is in my .hs filesI can live without 3), and with a little good will also 2), but 1) is harder since I cannot really hope my input files (meta-data-files) are coded in anything else than UTF-8.
I've searchedbrowser the web for information on the current state of unicode in GHC/Hugs but the latest discussion I could find on the topic leaves me less than happy. BUT it is from january 2005 so I thought maybe you guys have more up-to-date answers to these questions.
The discussion I found:http://groups.google.se/group/fa.haskell/browse_thread/thread/ccf1c6f32dbea873/a5ede2bc64ae8be4?lnk=stq=rnum=1#a5ede2bc64ae8be4
Thanks!/Olof
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What is the state if Unicode in Haskell implementations?

2006-07-31 Thread Piotr Kalinowski
On 31/07/06, Olof Bjarnason [EMAIL PROTECTED] wrote:
1) reading UTF-8 coded text files into unicode-enabled Strings, lets call them UString
2) writing UStrings to UTF-8 coded text files3) using unicode strings in-code, that is in my .hs filesIn case of GHC:String (Char actually) is unicode enabled. The current stable version cannot read UTF-8 encoded source files though (I've written a converter to workaround it - it escapes the national characters). The development version however is capable of reading UTF-8 encoded source files and does encode read strings using unicode.
However - the IO is not aware of Unicode. So in order to do 1) and 2) you have to- read/write stream of bytes encoding text in UTF-8 from/to a file- convert it to/from Unicode encoding.The first one is just about reading/writing using normal IO operations. The second can be done with the following module:
http://repetae.net/john/repos/jhc/UTF8.hsNote also that the same procedure would apply to simply printing/reading to/from the screen.Does that help?
Regards,Piotr Kalinowski-- Intelligence is like a river: the deeper it is, the less noise it makes
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What is the state if Unicode in Haskell implementations?

2006-07-31 Thread Duncan Coutts
On Mon, 2006-07-31 at 13:56 +0200, Olof Bjarnason wrote:
 Hi there!

 I'm trying to user Haskell as a code-generating language, specifically
 generating C# code files. The wish list is

 1) reading UTF-8 coded text files into unicode-enabled Strings, lets
 call them UString 

The ordinary Haskell String type is unicode-enabled.

 2) writing UStrings to UTF-8 coded text files
 3) using unicode strings in-code, that is in my .hs files
 
 I can live without 3), and with a little good will also 2), but 1) is
 harder since I cannot really hope my input files (meta-data-files) are
 coded in anything else than UTF-8. 

You can do 1 and 2 now with a little extra code for decoding and
encoding UTF8. You will be able to do 3) in GHC 6.6.

For 1  2, grab some UTF8 code from somewhere:

encode, decode :: String - String

and define

readFileUTF8 fname = fmap decode (readFile fname)
writeFileUTF8 fname content = writeFile fname (encode content)

So all internal processing happens as String which is Unicode and you
encode and decode when you read/write UTF8 encoded files.

Duncan

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


Re: [Haskell-cafe] What is the state if Unicode in Haskell implementations?

2006-07-31 Thread Bulat Ziganshin
Hello Olof,

Monday, July 31, 2006, 3:56:45 PM, you wrote:

 1) reading UTF-8 coded text files into unicode-enabled Strings, lets call 
 them UString
 2) writing UStrings to UTF-8 coded text files
 3) using unicode strings in-code, that is in my .hs files

first solution: http://haskell.org/haskellwiki/Library/Streams

another solution: darcs get --partial http://repetae.net/john/repos/jhc/
and use UTF8 and CharIO modules from jhc


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] What is the state if Unicode in Haskell implementations?

2006-07-31 Thread Piotr Kalinowski

On 31/07/06, Bulat Ziganshin [EMAIL PROTECTED] wrote:

first solution: http://haskell.org/haskellwiki/Library/Streams


Looks nice. Just a quick question - does it have an equivalent of
read(write)File?

Regards,
--
Intelligence is like a river: the deeper it is, the less noise it makes
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Parsec] Backtracking with try does not work for me?

2006-07-31 Thread Udo Stenzel
Stephane Bortzmeyer wrote:
 minilang = do
char 'a'
try (optional (do {comma ; char 'b'}))
optional (do {comma ; char 'c'})
eof
return OK
 
 * CUT HERE ***
 
 parse error at (line 1, column 2):
 unexpected c
 expecting b
 
 Apparently, try was used (do note that the column number indicates
 that there was backtracking) but the parser still fails for
 a,c. Why?

Because 'try' can only help you if its argument fails.  If the argument to
'try' succeeds, then it behaves as if it wasn't there.  Now 'optional x'
always succeeds, so the 'try' is useless where you placed it.  You need
to 'try' the argument to 'optional':

 minilang = do
char 'a'
optional (try (do {comma ; char 'b'}))
optional (do {comma ; char 'c'})
eof
return OK

You could also factor your grammar or use ReadP, where backtracking is not
an issue.


Udo.
-- 
Ours is a world where people don't know what they want and are willing
to go through hell to get it. -- Don Marquis


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


Re[2]: [Haskell-cafe] What is the state if Unicode in Haskell implementations?

2006-07-31 Thread Bulat Ziganshin
Hello Piotr,

Monday, July 31, 2006, 4:23:16 PM, you wrote:

 first solution: http://haskell.org/haskellwiki/Library/Streams

 Looks nice. Just a quick question - does it have an equivalent of
 read(write)File?

no, but you can borrow this code from ghc's System.IO module, see
below. actually, if you need only these two functions, borrowing jhc's
code will be enough


-- | The 'interact' function takes a function of type @String-String@
-- as its argument.  The entire input from the standard input device is
-- passed to this function as its argument, and the resulting string is
-- output on the standard output device.

interact::  (String - String) - IO ()
interact f  =   do s - getContents
   putStr (f s)

-- | The 'readFile' function reads a file and
-- returns the contents of the file as a string.
-- The file is read lazily, on demand, as with 'getContents'.

readFile:: FilePath - IO String
readFile name   =  openFile name ReadMode = hGetContents

-- | The computation 'writeFile' @file str@ function writes the string @str@,
-- to the file @[EMAIL PROTECTED]
writeFile :: FilePath - String - IO ()
writeFile f txt = bracket (openFile f WriteMode) hClose
  (\hdl - hPutStr hdl txt) 

-- | The computation 'appendFile' @file str@ function appends the string @str@,
-- to the file @[EMAIL PROTECTED]
--
-- Note that 'writeFile' and 'appendFile' write a literal string
-- to a file.  To write a value of any printable type, as with 'print',
-- use the 'show' function to convert the value to a string first.
--
--  main = appendFile squares (show [(x,x*x) | x - [0,0.1..2]])

appendFile  :: FilePath - String - IO ()
appendFile f txt = bracket (openFile f AppendMode) hClose
   (\hdl - hPutStr hdl txt)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Re: [Parsec] Backtracking with try does not work for me?

2006-07-31 Thread Stephane Bortzmeyer
On Mon, Jul 31, 2006 at 12:57:04PM +0200,
 Udo Stenzel [EMAIL PROTECTED] wrote 
 a message of 59 lines which said:

 Now 'optional x' always succeeds, so the 'try' is useless where you
 placed it.  You need to 'try' the argument to 'optional':

It works, too. Many thanks for the code and the explanation.
 
 You could also factor your grammar 

It is a language I do not control, so I prefer to keep the grammar as
close as possible from the official specification.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread Robert Dockins

On Jul 30, 2006, at 5:28 PM, Brian Hulley wrote:

Robert Dockins wrote:

On Sunday 30 July 2006 07:47, Brian Hulley wrote:

Another option, is the Edison library which uses:

 class (Functor s, MonadPlus s) = Sequence s where

so here MonadPlus is used instead of Monoid to provide empty and
append. So I've got three main questions:



1) Did Edison choose MonadPlus just because this fitted in with the
lack of multi-parameter typeclasses in H98?

Edison's design hails from a time when MPTCs were not only
non-standard (as they still are), but also not widely used, and
before fundeps were avaliable (I think).  So the answer to this one
is pretty much yes.

[snip]

Hi - Thanks for the answers to this and my other questions. One  
thing I just realised is that there doesn't seem to be any instance  
declarations anywhere in the standard libs relating Monoid to  
MonadPlus so it's a bit unsettling to have to make a random  
choice on the question of what kind of object a Sequence is...


I tried:

   class (forall a. Monoid s a) = Sequence s where ...

but of course that doesn't work, so I suppose MonadPlus is the only  
option when 'a' doesn't appear as a type variable arg of the class  
being defined.



BTW, for what purpose are you desiging a new sequence class?  You are
clearly aware of other efforts in this area; in what ways to they not
meet your needs?


The existing sequence and collection classes I've looked at don't  
do enough.


For example, when I tried to represent the text in an edit widget,  
I realised I needed a sequence of characters that could also be  
considered to be a sequence of lines, and it is necessary to be  
able to index the sequence by character position as well as by line  
position, as well as keeping track of the total number of  
characters, the total number of lines, and the maximum number of  
characters on any one line (so as to be able to calculate the x,y  
extents when laying out the widget, assuming a fixed width font  
(tabs ignored!)), with very efficient split and append operations.


So, what you want is a sequence of sequences that can be  
transparently converted to a flattened sequence and vice versa? And  
you also want to keep track of the total number of lines and  
characters within each line.  Additionally, you want to keep track of  
the maximum number of characters in any one line.


I managed to get a good representation by using a FingerTree of  
lines where each line uses a ByteString.
I made my own FingerTree class based on the one referenced in the  
paper at http://www.soi.city.ac.uk/~ross/papers/FingerTree.html but  
without the symbolic names which I find totally unreadable and  
confusing, and also so I could get full control of the strictness  
of the implementation, and also as a way of understanding them  
since I'd never come across such a complicated data structure  
before. (I highly recommend this paper to anyone who wants to learn  
about FingerTrees, Monoids and other very useful concepts.)


So one thing existing sequence classes don't have (apart from  
FingerTree) is the concept of measurement which is essential when  
you want efficient updates. Eg in my text buffer, the measurement  
maintained for a sequence is the number of chars and number of  
lines and maximum line length.


Edison has support for transparently keeping track of the size of a  
sequence.


http://www.eecs.tufts.edu/~rdocki01/docs/edison/Data-Edison-Seq- 
SizedSeq.html


It may well be possible to create a slightly generalized wrapper that  
keeps track of arbitrary measures.  (If they can be computed by a  
function which is associative, commutative and has a unit).

Humm, sort of an incremental fold I like it.

Then I needed a structure for a Trie widget a bit like (details  
omitted):


 data Node = Expanded Value T | Collapsed Value T | Leaf Value
 newtype T = T (FingerTree (Key, Node))

where objects of type T could be regarded as a finite map (eg from  
hierarchical module names to modules) as well as a flattened linear  
sequence indexed by line number (for display on the screen in a  
widget given the current scroll bar position), and which also  
needed to keep track of the total horizontal and vertical extent of  
the Trie as it would appear in the widget's font.


There are several different kinds of measurement going on in this  
data structure, as well as the complexity of the extra recursion  
through the leaf to a new level. Existing sequence abstractions  
don't seem to provide the operations needed to treat a nested data  
structure as a single sequence.


In summary:

1) Often a complex data structure must be able to be simultaneously  
regarded as a single flattened sequence
2) Measurements are needed for efficient updates (may need to keep  
track of several at once)
3) Indexing and size are sometimes needed relative to the flattened  
sequence not just the top level
4) It is useful to have a finite map that can also be 

Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread Brian Hulley

Robert Dockins wrote:

On Jul 30, 2006, at 5:28 PM, Brian Hulley wrote:

Robert Dockins wrote:

So, what you want is a sequence of sequences that can be
transparently converted to a flattened sequence and vice versa?


Yes as long as the conversion between them takes no time at all - the 
sequence of sequences and flattened sequence must coexist simultaneously. 
The concrete data structure is a sequence of sequences and the flattened 
sequence is a particular view of it.



And you also want to keep track of the total number of lines and
characters within each line.  Additionally, you want to keep track of
the maximum number of characters in any one line.

Edison has support for transparently keeping track of the size of a
sequence.

http://www.eecs.tufts.edu/~rdocki01/docs/edison/Data-Edison-Seq-
SizedSeq.html


I used this in an initial version of an edit buffer when I just used a 
SizedSeq wrapping a BinaryRandList to store the text as a sequence of chars. 
But the lack of ability to also index by line number and keep track of max 
line length was the problem that led me to use a finger tree instead.


Of course I could have used a sequence of chars, a sequence of line lengths, 
and a bag of line lengths to keep track of everything, and kept them in 
sync, but after reading the FingerTree paper I was seduced by the idea of 
being able to represent all this stuff at once in a single data structure.




It may well be possible to create a slightly generalized wrapper that
keeps track of arbitrary measures.  (If they can be computed by a
function which is associative, commutative and has a unit).
Humm, sort of an incremental fold I like it.


I got this from the FingerTree paper. A finger tree supports any measurement 
that is a Monoid (so it needs to be associative but not commutative (if it 
had to be commutative it would be impossible to use a sequence as a set or 
map, which I needed for my Trie structure)).



Well, I guess I'd suggest you attempt to identify specific problems
with already existing packages and attempt to work with those who
maintain such packages before reinventing something as basic (and
difficult to get right!) as data structure abstractions.


The problem is that some people will be using Data.Edison.Seq at the moment 
and will naturally not want it to change. However I'd suggest that all the 
common operations be factored out into separate classes eg:


   class Foldable f  where
fold :: (a - b - b) - b - f a - b
foldL :: ...

   class Reduce f where -- based on FingerTree paper
   reduceR :: (a - b - b) - (f a - b - b)
   reduceL :: (b - a - b) - (b - f a - b)

   class TakeDrop f where
   take :: Int - f a - f a
   takeWhile :: (a - Bool) - f a - f a
   drop ...

   class Filter f where
   filter :: (a - Bool) - f a - f a
   partition :: (a - Bool) - f a - (f a, f a)

   class Indexable f where
  length :: f a - Int
  at :: Int - f a - f a -- (*)
  splitAt :: Int - f a - (f a, f a)

(*) Data.ByteString.index puts the Int arg second. It's not at all clear to 
me which is best, because I often wish that the Int arg of take and drop was 
second also so I could write take g $! x+1 instead of (take $! x + 1) g 
though it's consistent with the arg order for takeWhile etc.


I know you don't agree with the no-exception-camel-case idea, but I still 
would argue that this is essential if you want to have a consistent naming 
convention. I find it extremely confusing that a word like reducer is 
supposed to be read as reduceR because the word reducer means to me 
something which reduces. It seems to me that a restructuring of the usual 
fold, reduce ops into classes is a great opportunity to perfect the naming 
of these functions to make life easier for generations to come... :-)




Such maintainers may be willing to accept patches and/or implement
requested features in order to reduce fragmentation in this space
*hint, hint*  :-)



Point taken, although in the case of the above refactoring idea, I think it 
really is a Haskell-wide task because although there appears to be a defacto 
standard use of names like take, drop, splitAt etc, it's not nearly so clear 
which ops belong together and which should be separated out, and I 
personally don't have enough experience of Haskell yet to be able to 
recommend a solution.




soapbox type=Edison plug
I personally think that Edison is a great piece of work, and I took
up maintainership because I felt it was a great shame that no one was
using it.  My ultimate goal is to make Edison the package that
everyone thinks of first when they discover they need a Haskell
datastructure for some purpose.  Even if Edison does not fill that
need, I want every Haskeller to compare his needs against what Edison
provides before striking out on his own, and I want that to be a
decision made with some hesitation.  Over time I hope to make the
cases where Edison doesn't cut the mustard fewer and 

Re: [Haskell-cafe] [Parsec] Backtracking with try does not work for me?

2006-07-31 Thread Chris Kuklewicz

The semantics of Parsec's optional operation are what is causing the problem.

optional foo can have 3 results:
  1) foo can succeed, optional succeeds, proceed to next command
  2) foo can fail without consuming any input, optional succeeds proceed to 
next command

  3) foo can fail after consuming some input, optional fails, do not proceed

 minilang = do
char 'a'
optional (do {comma ; char 'b'})

The comma in the above line consumes input even in the a,c case.  When c is 
seen the char 'b' fails and then the optional fails, and you get the error 
message you posted.


optional (do {comma ; char 'c'})
eof
return OK

 Apparently, try was used (do note that the column number indicates
 that there was backtracking) but the parser still fails for
 a,c. Why?

Your next attempt does not fix the problem, since the try is in the wrong place 
( http://www.cs.uu.nl/~daan/download/parsec/parsec.html#try may help)



minilang = do
   char 'a'
   try (optional (do {comma ; char 'b'}))


In the above line, the ,c causes (char 'b') to fail, which causes 'optional' 
to fail, and then try also fails.  The try alters the stream so that the 
comma was not consumed, but the try still passes along the failure.


In neither the original or the modified minilang does the 'char c' line ever 
get reached in the a,c input case.


The working solution is a small tweak:


minilang = do
   char 'a'
   optional (try (do {comma ; char 'b'}))
   optional (do {comma ; char 'c'})
   eof
   return OK


Now the a,c case causes the (char 'b') to fail, and then the try also fails, 
but also acts as if the comma had not been consumed.  Thus we are in case #2 of 
the semantics of optional and so optional succeeds instead of failing, 
allowing the next line to parse ,c then eof then return OK.


There is a very very important difference to Parsec between failing with and 
without having consumed input.  It means Parsec can be more efficient, since any 
branch that consumes input cannot backtrack.  The try command is a way to 
override this optimization and allow more backtracking.


The other solution presented on this list was:


minilang = do
   char 'a'
   try b | (return '-')
   optional c
   eof
   return OK
  where
  b = do { comma ; char 'b' }
  c = do { comma ; char 'c' }


In this case, the optional was replace by (| (return '-')). In fact you 
could define optional this way:



optional :: GenParser tok st a - GenParser tok st ()
optional foo = (foo  return ()) | (return ())


Thus optional (try b) is actually the same as (b  return ()) | (return 
()).  So you can see my suggestion is really identical the previous one.


I could not help generalizing your toy problem to an ordered list of comma 
separated Char.  Note that try is not actually needed in listlang, but it 
would be if (char x) were replaced by something that can consume more than a 
single character:



listlang :: [Char] - GenParser Char st [Char]
listlang [] = eof  return []
listlang (x:xs) = useX | listlang xs
  where useX = do try (char x)
  rest - end | more
  return (x:rest)
end = (eof  return [])
more = comma  listlang xs


Now minilang (the fixed version) is the same as (listlang ['a','b','c']) or 
(listlang abc).  This is a good example:



*Main run (listlang abcd) c,b
parse error at (line 1, column 3):
unexpected b
expecting d or end of input


--
Chris

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


[Haskell-cafe] Re: [Parsec] Backtracking with try does not work for me?

2006-07-31 Thread Stephane Bortzmeyer
On Mon, Jul 31, 2006 at 06:51:27PM +0100,
 Chris Kuklewicz [EMAIL PROTECTED] wrote 
 a message of 102 lines which said:

minilang = do
   char 'a'
   optional (try (do {comma ; char 'b'}))
   optional (do {comma ; char 'c'})
   eof
   return OK

I now have a new problem which was hidden beneath. If the language
authorizes a,bb and a,bbc, a,bbc is not accepted by my parser
since it already accepted a,bb and the c which is left triggers a
syntax error.

This time, try believes it succeeded but should not. I need more
look-ahead but I'm not sure how?

(Again, I do not control the language so I cannot make it more
deterministic.)

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


Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread ajb
G'day all.

Quoting Robert Dockins [EMAIL PROTECTED]:

 Edison's design hails from a time when MPTCs were not only non-standard (as
 they still are), but also not widely used, and before fundeps were avaliable
 (I think).

Yes.  Chris Okasaki's original version of Edison was standard H98.

 I've considered
 reformulating the Sequence class to be more similar to the Collection classes
 (which use MPTCs, fundeps and mention the element type),

The redesign of the Collection hierarchy was from my tree.  The main
reason why I changed it was that ternary tries couldn't really be typed
properly.  (Chris' implementation of Patricia trees used a phantom key
type along with a stern warning to only define the Int instance.  That
didn't work for ternary tries, since the key type is polymorphic.)

I didn't get around to fixing Sequence because there wasn't a need for
it yet, but yes, it should be done.

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


Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread ajb
G'day all.

Quoting Brian Hulley [EMAIL PROTECTED]:

 The problem is that some people will be using Data.Edison.Seq at the moment
 and will naturally not want it to change. However I'd suggest that all the
 common operations be factored out into separate classes eg:

While I think the huge typeclass is unfortunate, one of Edison's
greatest strengths is that every sequence supports every sequence
operation.  (The catch, of course, is that the operation may be
inefficient.)

This was a deliberate design decision, and I'd be sorry to see it go.
Many is the time in C++ when I started, say, with a std::stack, then
discovered soon after that I needed to peer at the top few elements
on the stack, only to find that std::stack doesn't support that.

Supporting all operations supports exploratory/agile programming.  You
don't have to decide up front what operations you need to be fast.  You
can discover this as you go.

Yes, this is orthogonal to breaking up the huge typeclass, but I thought
I'd just mention it.

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


Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread David Menendez
[EMAIL PROTECTED] writes:

 G'day all.
 
 Quoting Robert Dockins [EMAIL PROTECTED]:
 
  I've considered reformulating the Sequence class to be more similar
  to the Collection classes (which use MPTCs, fundeps and mention the
  element type),
 
 The redesign of the Collection hierarchy was from my tree.  The main
 reason why I changed it was that ternary tries couldn't really be
 typed properly.  (Chris' implementation of Patricia trees used a
 phantom key type along with a stern warning to only define the Int
 instance.  That didn't work for ternary tries, since the key type is
 polymorphic.)
 
 I didn't get around to fixing Sequence because there wasn't a need for
 it yet, but yes, it should be done.

That's a tough call to make. Changing the kind of Sequence to * from *
- * means losing the Functor, Monad, and MonadPlus superclasses and all
the various maps and zips.

I guess you could separate those into an auxiliary class,

class (Functor s, MonadPlus s) = SeqFunctor s where
mapWithIndex :: (Int - a - b) - s a - s b
zip :: s a - s b - s (a,b)
...

and require that any instance of SeqFunctor also be an instance of
Sequence.

A pity we can't do something like,

class (Functor s, MonadPlus s, forall a. Sequence (s a) a) =
SeqFunctor s where
...

-- 
David Menendez [EMAIL PROTECTED] | In this house, we obey the laws
http://www.eyrie.org/~zednenem  |of thermodynamics!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Trouble compiling wxhaskell

2006-07-31 Thread David F. Place

Hi:

I'm having trouble compiling wxhaskell 0.9.4 under both ghc 6.4.2 and  
ghc 6.5.   Does anyone know where I should direct my queries?


Thanks.


David F. Place
mailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Trouble compiling wxhaskell

2006-07-31 Thread Jason Dagit

I've done this recently.  I put my notes on the wiki:
http://www.haskell.org/haskellwiki/WxHaskell/Install#Windows

Do you have a particular error message?

Jason

On 7/31/06, David F. Place [EMAIL PROTECTED] wrote:

Hi:

I'm having trouble compiling wxhaskell 0.9.4 under both ghc 6.4.2 and
ghc 6.5.   Does anyone know where I should direct my queries?

Thanks.


David F. Place
mailto:[EMAIL PROTECTED]

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



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


Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread David Menendez
Brian Hulley writes:

 1) Did Edison choose MonadPlus just because this fitted in with the
 lack of multi-parameter typeclasses in H98?

Instances of Monoid (and your ISeq) have kind *. Instances of MonadPlus
(and Edison's Sequence) have kind * - *.

Functions like map, zip, and their variants are best defined in terms of
type constructors.

With Sequence, you have

zipWith :: (Sequence s) = (a - b - c) - s a - s b - s c

With ISeq, you'd have to do something like

zipWith :: (ISeq s1 a, ISeq s2 b, ISeq s3 c) = 
(a - b - c) - s1 - s2 - s3

which isn't able to make any assumptions about s1, s2, and s3 having the
same structure.


 3) Is it worth bothering to derive ISeq from Monoid (with the
 possible extra inefficiency of the indirection through the
 definitions for append = mappend etc or does the compiler completely
 optimize this out)?

I would expect the compiler to inline append.

 4) Would it be worth reconsidering the rules for top level names so
 that class methods could always be local to their class (ditto for
 value constructors and field names being local to their type
 constructor).

Qualified module imports are the way to go, here. Do you really want to
start writing if x Eq/== y Num/+ 1 then ... ?
-- 
David Menendez [EMAIL PROTECTED] | In this house, we obey the laws
http://www.eyrie.org/~zednenem  |of thermodynamics!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble compiling wxhaskell

2006-07-31 Thread Jared Updike

Hmmm I found

 http://www.haskell.org/haskellwiki/WxHaskell/Installation_tips

so there are two such pages, the other being:

 http://www.haskell.org/haskellwiki/WxHaskell/Install

so perhaps these pages can be merged? and a redirect placed from one
to the other?

Cheers,

 Jared.

On 7/31/06, Jason Dagit [EMAIL PROTECTED] wrote:

I've done this recently.  I put my notes on the wiki:
http://www.haskell.org/haskellwiki/WxHaskell/Install#Windows

Do you have a particular error message?

Jason

On 7/31/06, David F. Place [EMAIL PROTECTED] wrote:
 Hi:

 I'm having trouble compiling wxhaskell 0.9.4 under both ghc 6.4.2 and
 ghc 6.5.   Does anyone know where I should direct my queries?

 Thanks.

 
 David F. Place
 mailto:[EMAIL PROTECTED]

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


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




--
http://www.updike.org/~jared/
reverse )-:
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble compiling wxhaskell

2006-07-31 Thread Duncan Coutts
On Mon, 2006-07-31 at 19:11 -0400, David F. Place wrote:
 Hi:
 
 I'm having trouble compiling wxhaskell 0.9.4 under both ghc 6.4.2 and  
 ghc 6.5.   Does anyone know where I should direct my queries?

Assuming you're using wxHaskell on linux with wxGTK then the usual
problem with compiling wxHaskell is that it's sensitive to how wxGTK was
built.

I was trying various combinations for the Gentoo ebuild. I found that
the only combination that works is when wxGTK is built against Gtk+ 2.x
and without Unicode support and without ODBC support. If either of those
two wxGTK features are turned on then it leads to compile failures.

Hope that helps.

Duncan

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


Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread ajb
G'day all.

Quoting David Menendez [EMAIL PROTECTED]:

 That's a tough call to make. Changing the kind of Sequence to * from *
 - * means losing the Functor, Monad, and MonadPlus superclasses and all
 the various maps and zips.

And on the other hand, containers that need extra constraints (e.g.
sets, which need their members to be Eq at the very least) can't be
Functors or Monads anyway.

Perhaps Functor/Monad/etc are the culprits here.

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


Fw: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread Brian Hulley

David Menendez wrote:

Brian Hulley writes:


1) Did Edison choose MonadPlus just because this fitted in with the
lack of multi-parameter typeclasses in H98?


Instances of Monoid (and your ISeq) have kind *. Instances of
MonadPlus (and Edison's Sequence) have kind * - *.

Functions like map, zip, and their variants are best defined in terms
of type constructors.

With Sequence, you have

zipWith :: (Sequence s) = (a - b - c) - s a - s b - s c

With ISeq, you'd have to do something like

zipWith :: (ISeq s1 a, ISeq s2 b, ISeq s3 c) =
(a - b - c) - s1 - s2 - s3

which isn't able to make any assumptions about s1, s2, and s3 having
the same structure.


On the other hand it's more powerful because they can now have different 
structures ie was there any reason not to have:


zipWith ::
 (Sequence s1, Sequence s2, Sequence s3) =
 (a - b - c) - s1 a - s2 b - s3 c



3) Is it worth bothering to derive ISeq from Monoid (with the
possible extra inefficiency of the indirection through the
definitions for append = mappend etc or does the compiler completely
optimize this out)?


I would expect the compiler to inline append.


Thanks - that's good news. I' probably still too much in C++ mode.


4) Would it be worth reconsidering the rules for top level names so
that class methods could always be local to their class (ditto for
value constructors and field names being local to their type
constructor).


Qualified module imports are the way to go, here. Do you really want
to start writing if x Eq/== y Num/+ 1 then ... ?


I'm beginning to see that qualified module imports are indeed the only way 
to go, because the methods in a type class are only the virtual methods - 
often there are many other methods which are put outside the class to save 
space in the dictionary but which conceptually belong to the class thus 
putting the class + these extra functions in a single module wraps 
everything up into a conceptual unit.


eg:
 module Foldable
 ( Foldable(..)
 , reduceR
 ) where

 class Foldable c a | c - a where
foldR :: (a - b - b) - b - [a] - b
-- ...

 reduceR :: Foldable c a = (a - b - b) - (c - b - b)
 reduceR f xs y = foldR f y xs

forms the single conceptual unit to use Foldable.foldR,  Foldable.reduceR 
etc so I'll have to retract my suggestion as regards classes... (Although 
I'm still concerned about value constructors and field names being in the 
top level instead of local to their type but changing this would require 
some changes to type inference (so that the constructors and field names 
could be used unqualified when the type at the given position is known eg by 
a top level type signature for the function or value) so that's more of a 
long term idea.)


Regards, Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread Brian Hulley

David Menendez wrote:

[EMAIL PROTECTED] writes:

I didn't get around to fixing Sequence because there wasn't a need
for it yet, but yes, it should be done.


That's a tough call to make. Changing the kind of Sequence to * from *
- * means losing the Functor, Monad, and MonadPlus superclasses and
all the various maps and zips.


But there's no option if you want to be able to support non-polymorphic 
sequences like Data.ByteString etc. I think the Functor class is just 
fundamentally too limited - it assumes the whole world is polymorphic and it 
isn't.


Also, MPTC's mean we would gain Monoid.

Regards, Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread Brian Hulley

[EMAIL PROTECTED] wrote:

G'day all.

Quoting Brian Hulley [EMAIL PROTECTED]:


The problem is that some people will be using Data.Edison.Seq at the
moment and will naturally not want it to change. However I'd suggest
that all the common operations be factored out into separate classes
eg:


While I think the huge typeclass is unfortunate, one of Edison's
greatest strengths is that every sequence supports every sequence
operation.  (The catch, of course, is that the operation may be
inefficient.)

This was a deliberate design decision, and I'd be sorry to see it go.
Many is the time in C++ when I started, say, with a std::stack, then
discovered soon after that I needed to peer at the top few elements
on the stack, only to find that std::stack doesn't support that.


As an aside, if I was needing any kind of sequence in C++ I'd use a 
std::vector because it supplies all the ops you need (and is usually fast 
enough for exploratory programming). I've never seen any point in stack or 
deque etc because they're far too limited.




Supporting all operations supports exploratory/agile programming.  You
don't have to decide up front what operations you need to be fast.
You can discover this as you go.

Yes, this is orthogonal to breaking up the huge typeclass, but I
thought I'd just mention it.


As you've pointed out, there are 2 separate issues that are in danger of 
being confused:

1) Forcing all sequence instances to support all operations
2) Bundling all the ops into a single huge class

I'd suggest that while 1) may be useful for the classes that are there at 
present, there are many ops that they don't yet support and also some ops 
that are never needed. Also, surely as long as there is one concrete type 
that supports everything that should be good enough for exploratory 
programming (I'm thinking of FingerTrees which seem to be able to do 
absolutely anything in logarithmic time!!! :-) )


For 2), you could still have a Sequence class to gather all the separate 
functionality together but I'd make it inherit from all the separate pieces 
of functionality rather than being the place where all the functionality is 
defined eg:


class Viewable c a | c - a where
viewL :: Monad m = c - m (a, c)
viewR :: Monad m = c - m (c, a)
atL :: c - a  -- must be called on non-empty sequence
atR :: c - a

class Indexable c a | c - a where
length :: c - Int
at :: Int - c - a -- index must be in range
splitAt :: Int - c - (c, c)

-- in same module as Indexable
take :: Indexable c a = Int - c - c
take i c = let (l, _) = splitAt i c in l

class (Monoid c, Foldable c a, Indexable c a, Filterable c a, Viewable 
c a) = Sequence c a


This way, we'd get the advantages of being able to write (Sequence c a) as 
well as the advantages of being able to supply a sequence to a function that 
needed a Foldable - at the moment the fold methods of sequence are invisible 
to the rest of Haskell because they're trapped inside the Sequence class.


Regards, Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread Brian Hulley

Brian Hulley wrote:

David Menendez wrote:

Brian Hulley writes:

4) Would it be worth reconsidering the rules for top level names so
that class methods could always be local to their class (ditto for
value constructors and field names being local to their type
constructor).


Qualified module imports are the way to go, here. Do you really want
to start writing if x Eq/== y Num/+ 1 then ... ?


I'm beginning to see that qualified module imports are indeed the
only way to go,


One reason I forgot: Suppose person A writes ClassA which uses foo as a 
method name, and somewhere else, person B writes ClassB which also uses 
foo as a method name, and both classes become widely used for several 
years.


Now the problem is that person C may come along and notice that there is a 
useful abstraction to be made by inheriting both from ClassA and ClassB. But 
both of these define foo and there is no mechanism in the language to 
resolve this.


The language C#, which was designed from the outset for programming in the 
large, already had a solution in the very first release of C#, namely that 
the interface name could be used to qualify a method name in cases of 
ambiguity, so transposing this to Haskell, you'd have something like:


class ClassA a where
foo :: a - Int

class classB a where
foo :: a - String

class (ClassA a, ClassB a) = ClassC a where
bar :: a - (Int, String)
bar x = (ClassA#foo x, ClassB#foo x)

As I see it, Haskell, great and innovative as it is, is still stuck in 
programming in the small and some of the mechanisms needed for programming 
in the large are not yet available - it is as impossible to ensure that 
there will never be conflicts between names of class methods as it is to 
ensure that there will never be conflicts between module names in packages 
written by different groups of people, and languages like Java and C# solved 
these problems right at the beginning but Haskell for some reason has 
ignored the issues, only recently just starting to address the package 
module name conflict problem for example even though the language has been 
around for more than a decade.


I'm also wondering if it would be a good idea to be able to declare some 
class methods as final, so they don't clutter up the dictionary at runtime, 
and so that we could end the dubious practice of declaring some functions 
which are conceptually part of a class as top level functions outside the 
class just to save space/time in the dictionary and therefore needing the 
physical module to create the conceptual grouping instead of using the 
language level grouping provided by the class name.


Anyway these are probably more long term ideas but I mentioned them now just 
to hopefully start the ball rolling (the above should not be taken as a 
criticism of Haskell, I'm just saying that at some point we need all the 
normal mechanisms that everyone else (Java, C#) takes for granted because 
there's no point waiting till we encounter the same well-known software 
engineering problems that already have well established good solutions).


Regards, Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread Jim Apple

On 7/31/06, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:

G'day all.

Quoting David Menendez [EMAIL PROTECTED]:

 That's a tough call to make. Changing the kind of Sequence to * from *
 - * means losing the Functor, Monad, and MonadPlus superclasses and all
 the various maps and zips.

Perhaps Functor/Monad/etc are the culprits here.


Indeed. See Oleg's message from a few months back where he shows that
we can get John Hughes Restricted Data Types (Set is a Monad) by
adding parameters to type classes:

http://www.haskell.org//pipermail/haskell-prime/2006-February/000498.html
http://hackage.haskell.org/trac/haskell-prime/ticket/98

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


Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread John Meacham
On Tue, Aug 01, 2006 at 02:56:21AM +0100, Brian Hulley wrote:
 Now the problem is that person C may come along and notice that there is a 
 useful abstraction to be made by inheriting both from ClassA and ClassB. 
 But both of these define foo and there is no mechanism in the language to 
 resolve this.

This is not true at all. every name in haskell can be uniquely
specified.

 module ClassA where
 class ClassA a where
 foo :: a - Int
 
 module ClassB where
 class classB a where
 foo :: a - String
 
 import ClassA
 import ClassB
 class (ClassA a, ClassB a) = ClassC a where
 bar :: a - (Int, String)
 bar x = (ClassA.foo x, ClassB.foo x)


 I'm also wondering if it would be a good idea to be able to declare some 
 class methods as final, so they don't clutter up the dictionary at runtime, 
 and so that we could end the dubious practice of declaring some functions 
 which are conceptually part of a class as top level functions outside the 
 class just to save space/time in the dictionary and therefore needing the 
 physical module to create the conceptual grouping instead of using the 
 language level grouping provided by the class name.


I think a fundamental thing you are missing is that Haskell classes are
not like C# or Java or other OO classes. Not because of implementation,
but rather they are actually fundamentally different things.

The reasons people don't place certain functions in classes has nothing
to do with the size of class dicionaries. Heck, jhc doesn't even use
dictionaries at all, there is no cost for adding methods to a class.
People place them in top level functions because it makes more sense. of
course, sometimes it is gotten wrong, and something would have been
better off as a class method, but in general there are different
concerns when dealing with haskell classes than OO classes.

An OO class could be considered equivalent to a triplet of a Haskell
data type, a Haskell existential with a class constraint, and a class
with the resriction the class type can _only_ appear as the first
argument to each method. In haskell all of these things are separate
independent tools and are much more general and powerful than the
limited and conjoined form that OO programming provides.

 Anyway these are probably more long term ideas but I mentioned them now 
 just to hopefully start the ball rolling (the above should not be taken as 
 a criticism of Haskell, I'm just saying that at some point we need all the 
 normal mechanisms that everyone else (Java, C#) takes for granted because 
 there's no point waiting till we encounter the same well-known software 
 engineering problems that already have well established good solutions).

It is best to think of haskell primitives as something completely new,
they reuse some naming conventions from OO programming, but that doesn't
mean they suffer from the same limitations. It took me a few trys to
wrap my brain around it. I liken learning haskell to tipping over a
vending machine. you can't just push it, you gotta rock it back and
forth a few times building up momentum until bam! suddenly the flash of
insight hits and it all makes sense.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble compiling wxhaskell

2006-07-31 Thread shelarcy

On 7/31/06, David F. Place [EMAIL PROTECTED] wrote:

Hi:

I'm having trouble compiling wxhaskell 0.9.4 under both ghc 6.4.2 and
ghc 6.5.   Does anyone know where I should direct my queries?


If you use ghc 6,4,2 under Windows platform, you
can use my patched version of wxHaskell.

And you can get my patch from Kamiariduki's source.

http://www.haskell.org/pipermail/haskell/2006-June/018043.html
https://sourceforge.net/project/showfiles.php?group_id=168626


I also know Eric Y. Kow's unicode patch doesn't
include db problems fix. These problems has not
only wxWidgets 2.6.x change, but also unicode
change.

I try to fix latter case, use attached after unicode
patch, this fixes compile problem ... but it has
another problem that can't use non-ascii characters
correctly. So, if want to accesss DB by wxHaskell's
ODBC, data is garbled and cause problems.

I don't know how to fix that.

Attached is already sent wxhaskell-user's list, but
you can't get this file. So I send again.
http://sourceforge.net/mailarchive/message.php?msg_id=16222530


My patch where I put Kamiariduki's project page doesn't
include unicode support that I noticed above Mailng-List's
log.

Don't worry about this. You can use both my patch and
unicode patch, if you want. These cause conflict message
but this is not problem.


On Tue, 01 Aug 2006 08:18:27 +0900, Jason Dagit  
[EMAIL PROTECTED] wrote:

I've done this recently.  I put my notes on the wiki:
http://www.haskell.org/haskellwiki/WxHaskell/Install#Windows


I don't know this problem when I made patch.
So, my patch doesn't fix this problem.


--
shelarcy shelarcycapella.freemail.ne.jp
http://page.freett.com/shelarcy/

bugfix_for_08.tgz
Description: GNU Zip compressed data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe