RE: stgSyn/CoreToStg.lhs:1112: Couldn't match `#' against `*'

2002-05-14 Thread Simon Peyton-Jones
Title: Message



maybe 
you need to rebuild the compiler you are compiling *with*?

  
  -Original Message-From: Mike Thomas 
  [mailto:[EMAIL PROTECTED]] Sent: 13 May 2002 22:19To: 
  Simon Peyton-Jones; [EMAIL PROTECTED]Subject: Re: 
  stgSyn/CoreToStg.lhs:1112: Couldn't match `#' against `*'
  Hi 
  Simon.
  
  
   
  Yes, I fixed this a week or two ago. You need to 'cvs update'. 
  
  
  Iam using the latest CVS(updated daily) to no avail. 
  I'll look at the commit logs and try to find out why.
  
  Cheers
  
  Mike 
  Thomas
  
  
The cvs commit logs should show which commit fixed it if you 
want
to 
just grab the patch.



Re: stgSyn/CoreToStg.lhs:1112: Couldn't match `#' against `*'

2002-05-14 Thread Mike Thomas

MessageHi Simon.

 maybe you need to rebuild the compiler you are compiling *with*?

That's exactly what I'm trying to do with the latest CVS Head, so I assume
you mean to try switching back to the Glasgow team's 5.02 or  5.03 releases
to build.  As the compiler I am using was built with the GHC team 5.03
snapshot and using CVS head of about 26 April, I guess I'll try the most
recent GHC 5.02 this time.

As an aside, building GHC from scratch on a 300 Mhz 192 MB PC takes all day
unfortunately.

I am also accumulating trivial but numerous changes to the HDirect tree to
get it to build with 5.03, so I wouild like to get CVS write access to fold
that stuff back in (if you trust me after the above fiasco!)

Thanks

Mike Thomas

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



RE: Prelude.catch vs. Exception.catch

2002-05-14 Thread Ashley Yakeley

At 2002-05-14 02:24, Simon Marlow wrote:

This is bizarre: the definition of evaluate in Exception is exactly the
one you gave above, yet they behave differently.  You may have uncovered
a compiler bug, I'll look into it.

I might ask which is correct: according to the rules for seq, evaluate' 
undefined should be bottom, but we want Expression.evaluate undefined 
to be a failing IO action.

I think the compiler is correct but the definition given in the 
documentation is wrong.

-- 
Ashley Yakeley, Seattle WA

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



RE: Prelude.catch vs. Exception.catch

2002-05-14 Thread Simon Marlow

 This is bizarre: the definition of evaluate in Exception is 
 exactly the
 one you gave above, yet they behave differently.  You may 
 have uncovered
 a compiler bug, I'll look into it.
 
 I might ask which is correct: according to the rules for seq, 
 evaluate' 
 undefined should be bottom, but we want Expression.evaluate 
 undefined 
 to be a failing IO action.
 
 I think the compiler is correct but the definition given in the 
 documentation is wrong.

Well, given the compiler is compiling the definition from the
documentation and giving the wrong semantics, I'd say the compiler is
definitely wrong :-)

But the question of whether Exception.evaluate should have a different
semantics is interesting.  So to be clear about this, there are three
possible definitions of evaluate:

  evaluate a = return a-- not strict enough
  evaluate a = a `seq` return a-- too strict (?)
  evaluate a = IO $ \s - a `seq` (# s, a #)   -- just right :)

I had to write out the third one in full, because we don't have any
combinators that provide this functionality elsewhere (at least, I can't
think of any).

I must admit I can't think of any compelling reasons for the change,
other than the fact that this is functionality that we don't have at the
moment, and therefore might be useful.  Opinions?

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



RE: Prelude.catch vs. Exception.catch

2002-05-14 Thread Simon Marlow

 At 2002-05-14 02:58, Simon Marlow wrote:
 
 I must admit I can't think of any compelling reasons for the change,
 other than the fact that this is functionality that we don't 
 have at the
 moment, and therefore might be useful.  Opinions?
 
 I need a function that does this:
 
 evaluate :: a - IO a
 evaluate _|_ = fail something
 evaluate a = return a
 
 The idea is that you can take something that might be bottom 
 and safely 
 handle it in the IO monad, with the bottomness gone. This is what 
 Exception.evaluate currently does, and I think that's correct.

Ok, I'll change the definition of evaluate to reflect the slightly
different semantics.  

It turns out that the compiler bug is really just the compiler being a
bit loose with the IO monad - it freely translates the original
definition of evaluate using 'seq' into the slightly less strict version
by pushing the 'seq' through the state lambda of the IO monad (this only
happens for the IO monad, and strictly speaking it's a deviation from
the semantics but it has important performance benefits for IO code).

 I think the behaviour of Exception.catch is wrong. I think it should 
 behave like this:
 
 catch _|_ cc = _|_
 catch (failure ex) cc = cc ex
 catch (success a) cc = success a
 
 ...whereas it actually behaves like this:
 
 catch _|_ cc = cc something
 catch (failure ex) cc = cc ex
 catch (success a) cc = success a

so your catch can be defined in terms of the current catch like so:

catch' a h = a `seq` (catch a h)

what's the motivation for this change?

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



Re: Replacing the Prelude

2002-05-14 Thread Dylan Thurston

On Sun, May 12, 2002 at 09:31:38PM -0700, Ashley Yakeley wrote:
 I have recently been experimenting writing code that replaces large 
 chunks of the Prelude, compiling with -fno-implicit-prelude. I notice 
 that I can happily redefine numeric literals simply by creating functions 
 called 'fromInteger' and 'fromRational': GHC will use whatever is in 
 scope for those names.
 
 I was hoping to do something similar for 'do' notation by redefining 
 (), (=) etc., but unfortunately GHC is quite insistent that 'do' 
 notation quite specifically refers to GHC.Base.Monad (i.e. Prelude.Monad, 
 as the Report seems to require). I don't suppose there's any way of 
 fooling it, is there? I was rather hoping 'do' notation would work like a 
 macro in rewriting its block, and not worry about types at all.
 
 I accept that this might be a slightly bizarre request. There are a 
 number of things I don't like about the way the Prelude.Monad class and 
 'do' notation are set up, and it would be nice to be able to experiment 
 with alternatives.

A while ago, there were extensive discussions about replacing the
Prelude on this list.  (Search for Prelude shenanigans.)  I started
to write up a design document for how to enable replacing the Prelude.
This boiled down to taking most of the syntactic sugar defined in
the report seriously, ignoring the types (as you say).

I'm surprised that ghc uses the fromInteger and fromRational that are
in scope; I thought there was general agreement that it should use the
Prelude.from{Integer,Rational} in scope.

As I recall, there were several relevant bits of syntactic sugar:

- Numeric types, including 'fromInteger', 'fromRational', and
  'negate'.  This all works fine, except that the defaulting mechanism
  is completely broken, causing a number of headaches.

- Monads.  The translation given in the report is clean, and it seems
  like it can be used without problems.

- Bools.  There was a slight problem here: the expansion of
  'if ... then ... else ...' uses a case construct referring to the
  constructors of the Bool type, which prevents any useful
  redefinition of Bool.  I would propose using a new function,
  'Prelude.ifThenElse', if there is one in scope.

- Enumerations.  Clean syntactic sugar.

- List comprehensions.  The report gives one translation, but I think
  I might prefer a translation into monads.

- Lists and tuples more generally.  At some point the translations
  start getting too hairy; I think I decided that lists and tuples
  were too deeply intertwined into the language to change cleanly.

I'll dig up my old notes and write more, and then maybe write a
complete design document and get someone to implement it.

--Dylan Thurston


msg03485/pgp0.pgp
Description: PGP signature


RE: Replacing the Prelude

2002-05-14 Thread Simon Peyton-Jones

Ashley writes

|  I was hoping to do something similar for 'do' notation by redefining
|  (), (=) etc., but unfortunately GHC is quite insistent 
| that 'do' notation quite specifically refers to GHC.Base.Monad 

Dylan replies

| I'm surprised that ghc uses the fromInteger and fromRational 
| that are in scope; I thought there was general agreement that 
| it should use the Prelude.from{Integer,Rational} in scope.

Ashley is referring to a GHC extension.  Normally, GHC uses
Prelude.fromInteger etc, regardless of what is in scope.  But if you
say -fno-implicit-prelude, GHC will instead use whatver fromInteger
is in scope.  (This is documented in the manual.)

Ashley's question, as I understand is whether something similar
could be done for monads. 

Answer: I think so, without much bother.   I'm beavering away on
a Haskell workshop paper at the moment, but ping me in a fortnight
to do it.

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



Re: preprocessing printf/regex strings (like ocaml)

2002-05-14 Thread Martin Norbäck

tis 2002-05-14 klockan 06.37 skrev anatoli:
 Brian Huffman [EMAIL PROTECTED] wrote:
  Here is a printf-style function that I hacked up this morning; it uses type

  classes but it doesn't need functional dependencies:
 [snip]

 It's very nice and even extendable, though `class Printf String'
 is unfortunately not Haskell 98. But the bigger question is, how
 to support Posix-style positional arguments? They are essential for
 i18n.

 For instance,

  printf %1$s %2$s foo bar -- == foo bar
  printf %2$s %1$s foo bar -- == bar foo

 Naturally, such format strings cannot be pre-processed by the
 compiler since they are typically loaded from some message database
 at run time.

I agree that i18n needs positional arguments.
What's wrong with simply doing like this:

printf I have %. %. %..[trained, show 1, Jedi]
printf %2. %3. %1. I have. [trained, show 1, Jedi]

with printf would look something like this:

printf ('%':'%':rest) xs = '%' : printf rest xs
printf ('%':'.':rest) (x:xs) = x ++ printf rest xs
printf ('%':d:rest)   xs | isDigit d =
  let (ds, rest') = span isDigit rest
  index = read (d:ds)
  in if null rest' || head rest' /= '.' || index  length xs then
   '%':printf (d:ds:rest') xs
 else
   xs!!(index - 1) ++ printf (tail rest') xs
printf (r:rest) xs = r:printf rest xs 
printf [] _ = []

Note that there are no errors if the format string is wrong in any way, it's
just unchanged. Also, behaviour with both positional and normal
formatters is not considered.

Feel free to use this code snippet however you like.

Regards,

Martin

--
Martin Norbäck  [EMAIL PROTECTED]
Kapplandsgatan 40   +46 (0)708 26 33 60
S-414 78  GÖTEBORG  http://www.dtek.chalmers.se/~d95mback/
SWEDEN  OpenPGP ID: 3FA8580B



signature.asc
Description: PGP signature


Re: preprocessing printf/regex strings (like ocaml)

2002-05-14 Thread Sebastien Carlier


On Tuesday, May 14, 2002, at 06:37 AM, anatoli wrote:

 Brian Huffman [EMAIL PROTECTED] wrote:
 Here is a printf-style function that I hacked up this morning; it uses 
 type
 classes but it doesn't need functional dependencies:
 [snip]

 It's very nice and even extendable, though `class Printf String'
 is unfortunately not Haskell 98.

I agree that it is a very nice use of type classes.  But all type 
checking
is done at runtime, because the code which is generated depends not
on the string itself, but on the types of the arguments which are applied
to (printf format string).
For example,
putStrLn $ printf %s (1 :: Integer)
gives no error at compilation, but fails at runtime with:
Program error: printf: extra integer argument

 But the bigger question is, how  to support Posix-style positional
 arguments? They are essential for i18n.

I hacked Brian's code to add this feature, see the attachment.




Printf.hs
Description: Binary data



 For instance,

 printf %1$s %2$s foo bar -- == foo bar
 printf %2$s %1$s foo bar -- == bar foo

 Naturally, such format strings cannot be pre-processed by the
 compiler since they are typically loaded from some message
 database at run time.

Then you give up static type checking for format strings...
Why not let the compiler pre-process this database, and generate
some type-safe dynamically loadable object ?
Or, you could embed a very restricted version of the compiler in
the program, to pre-process and type-check the format strings at runtime
(Yes, you would need to keep some type information in the executable
program).

--
Sébastien



State monads don't respect the monad laws in Haskell

2002-05-14 Thread Simon Marlow

An interesting revelation just occurred to Simon P.J. and myself while
wondering about issues to do with exceptions in the IO monad (see
discussion on [EMAIL PROTECTED] if you're interested).

The question we were considering was whether the following should hold
in the IO monad:

(return () = \_ - undefined) `seq` 42   ==  undefined

as we understand the IO monad it certainly shouldn't be the case.  But
according to the monad laws:

(law)  return a = k  ==  k a
so (return () = \_ - undefined) `seq` 42
  = ((\_ - undefined) ()) `seq` 42
  = undefined `seq` 42
= undefined

So the IO monad in Haskell, at least as we understand it, doesn't
satisfy the monad laws (or, depending on your point of view, seq breaks
the monad laws).  

This discrepancy applies to any state monad.  Suppose we define

return a = \s - (s, a)
m = k = \s - case m s of (s', a) - k a s'

now
   return a = k
  = \s - case (return a) s of (s', a') - k a' s'
= \s - case (s, a) of (s', a') - k a' s'
= \s - k a s

but (\s - k a s) /= (k a) in Haskell, because seq can
tell the difference.

What should the report say about this?

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



Re: State monads don't respect the monad laws in Haskell

2002-05-14 Thread David Feuer

On Tue, May 14, 2002, Simon Marlow wrote:
 An interesting revelation just occurred to Simon P.J. and myself while
 wondering about issues to do with exceptions in the IO monad (see
 discussion on [EMAIL PROTECTED] if you're interested).
 
 The question we were considering was whether the following should hold
 in the IO monad:
 
   (return () = \_ - undefined) `seq` 42   ==  undefined
 
 as we understand the IO monad it certainly shouldn't be the case.  But

Why shouldn't this be the case?  It seems kind of obvious.

 So the IO monad in Haskell, at least as we understand it, doesn't
 satisfy the monad laws (or, depending on your point of view, seq breaks
 the monad laws).  
 
 This discrepancy applies to any state monad.  Suppose we define
 
   return a = \s - (s, a)
   m = k = \s - case m s of (s', a) - k a s'
 
 now
  return a = k
   = \s - case (return a) s of (s', a') - k a' s'
   = \s - case (s, a) of (s', a') - k a' s'
   = \s - k a s
 
   but (\s - k a s) /= (k a) in Haskell, because seq can
   tell the difference.
 
 What should the report say about this?

Changes from Haskell 98: removed the seq primitive.

Well, maybe not.  But it would be really nice to find an alternative
that didn't screw up so many different things.  It seems that general
cleanliness is more important for understanding programs than being able
to use functions in all the same ways as datatypes (yes, I am aware that
there are loads of issues regarding this that I don't understand, but
the whole seq thing smells really funny.  \a-\b-e should really equal
\a b-e, \x-f x should equal f, etc. etc.  Sometimes it seems as though
every rule in Haskell has a list of exceptions relating to seq, and that
sucks.)

-- 
Night.  An owl flies o'er rooftops.  The moon sheds its soft light upon
the trees.
David Feuer
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: State monads don't respect the monad laws in Haskell

2002-05-14 Thread Ross Paterson

On Tue, May 14, 2002 at 12:14:02PM +0100, Simon Marlow wrote:
 The question we were considering was whether the following should hold
 in the IO monad:
 
   (return () = \_ - undefined) `seq` 42   ==  undefined
 
 [as implied by the left-identity monad law]

 This discrepancy applies to any state monad.

It also fails for the reader, writer and continuation monads, also thanks
to lifted functions and tuples.  The right-identity law also fails for
these monads:

(undefined = return) `seq` 42   /=   undefined `seq` 42
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Apparel Helmet Links - Super sales Savings

2002-05-14 Thread PlanetMoto.com
MILLIONS of dollars in brand name high quality motorcycle
accessories featured on this month’s sites. Some products are being liquidated
at unbelievable blowout prices! Most products are being sold for significant
discounts off of retail pricing. In some cases prices have been slashed
up to 70% off! 

TO CHECK OUT THESE UNBELIEVABLE DEALS AT
PLANETMOTO.COM CLICK HERE NOW! 

Just some of the many products available:
Street Helmets
MX Helmets
Gloves
Boots
Leather suits
Leather jackets
Textile jackets


TO CHECK OUT THESE UNBELIEVABLE DEALS AT
PLANETMOTO.COM CLICK HERE NOW! 





If you would like to be removed from this mailing list, please email
[EMAIL PROTECTED] with the word "remove" in the subject line.



Re: preprocessing printf/regex strings (like ocaml)

2002-05-14 Thread anatoli

Martin Norbäck [EMAIL PROTECTED] wrote:
 I agree that i18n needs positional arguments.
 What's wrong with simply doing like this:
 
 printf I have %. %. %..[trained, show 1, Jedi]
 printf %2. %3. %1. I have. [trained, show 1, Jedi]

Nothing is exceptionally wrong with it, except it's not
as flexible. Since everything is show'n, how would you
handle things like %5.2f or %*d? In Brian Huffman's
version it's almost trivial to add. I know I can use 
formatDouble and whatnot, but the code looks cluttered
this way. C printf has many pitfalls, but I like its
terseness.

-- 
anatoli

__
Do You Yahoo!?
LAUNCH - Your Yahoo! Music Experience
http://launch.yahoo.com
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: preprocessing printf/regex strings (like ocaml)

2002-05-14 Thread Robert Ennals

 Martin Norbäck [EMAIL PROTECTED] wrote:
  I agree that i18n needs positional arguments.
  What's wrong with simply doing like this:
  
  printf I have %. %. %..[trained, show 1, Jedi]
  printf %2. %3. %1. I have. [trained, show 1, Jedi]
 
 Nothing is exceptionally wrong with it, except it's not
 as flexible. Since everything is show'n, how would you
 handle things like %5.2f or %*d? In Brian Huffman's
 version it's almost trivial to add. I know I can use 
 formatDouble and whatnot, but the code looks cluttered
 this way. C printf has many pitfalls, but I like its
 terseness.

Just thought I would jump in and say that, unlike (it seems) everyone else, I 
hate printf in C. It is a horrible horrible inextensible hack of a function 
that I find extremely awkward to use.

In the C version, it is completely hardcoded and inextensible. Even in the 
version presented on this list, one can't add new ways to format an existing 
datatype.

I personally much prefer the syntax currently used in Haskell, which is also 
essentially what is used in most other recent languages, including Java, C++, 
and (god help me) Perl.

In the example given, I could write:

I have  ++ action ++   ++ number ++   ++ whatas
where
action = trained
number = show 1
whatas = Jedi

Which is IMHO rather more readable than a load of weird control codes hidden 
in a text string that one then has to match against a list.

+ If I want to use a weird formatting approach, I just write my own function, 
and use it instead of show. No need to faff around extending someone else's 
printf.

[end rant]


-Rob





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



Re: State monads don't respect the monad laws in Haskell

2002-05-14 Thread George Russell

Simon Marlow wrote
[snip]
 So the IO monad in Haskell, at least as we understand it, doesn't
 satisfy the monad laws (or, depending on your point of view, seq breaks
 the monad laws).
[snip]

Cheers Simon.  One of the awkward things about the Haskell events I implemented
is that although I make them an instance of Monad, they don't actually satisfy
left identity.  Now I can say that Yes, Event isn't really a Monad, but neither is 
IO.

According to the report
 Instances of Monad should satisfy the following laws:
 
return a = k  = k a
m = return= m  
m = (\x - k x = h) = (m = k) = h  
so neither IO nor my events satisfy this.  Up to now I haven't had any problems
with this.

Does GHC or any other Haskell compiler actually rely on instances of Monad
satisfying left identity?  If not, I would suggest dropping the requirement, if it
can be done without upsetting category theorists.  (What the hell, they stole the
term Monad from philosophy and changed its meaning, so why shouldn't we?)

I presume it would not in fact be difficult to synthesise a left identity at
the cost of making things slower, thus (forgive any syntax errors, I'm not going to
test this).

data MonadIO a = Action (IO a) | Return a
instance Monad (MonadIO a) where
   return a = Return a
   (=) (Return a) k = k a
   (=) (Action act) f = 
  Action (act = (\ a - case f a of {Return a - return a;Action act - act}))

(I considered doing something similar to turn Events into a real monad, but decided to
choose efficiency over category theory.  For events its slightly more complicated as
you need to handle the choice operator as well.)
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: preprocessing printf/regex strings (like ocaml)

2002-05-14 Thread Martin Norbäck

tis 2002-05-14 klockan 16.45 skrev Robert Ennals:
  Martin Norbäck [EMAIL PROTECTED] wrote:
   I agree that i18n needs positional arguments.
   What's wrong with simply doing like this:
   
   printf I have %. %. %..[trained, show 1, Jedi]
   printf %2. %3. %1. I have. [trained, show 1, Jedi]
  
  Nothing is exceptionally wrong with it, except it's not
  as flexible. Since everything is show'n, how would you
  handle things like %5.2f or %*d? In Brian Huffman's
  version it's almost trivial to add. I know I can use 
  formatDouble and whatnot, but the code looks cluttered
  this way. C printf has many pitfalls, but I like its
  terseness.

Changing format specifiers normally doesn't happen during translation.
Word order changes happen.

 I personally much prefer the syntax currently used in Haskell, which is also 
 essentially what is used in most other recent languages, including Java, C++, 
 and (god help me) Perl.
 
 In the example given, I could write:
 
 I have  ++ action ++   ++ number ++   ++ whatas
 where
 action = trained
 number = show 1
 whatas = Jedi

How do you internationalize this code snippet?

The issue here was with i18n. When doing i18n, you need to give the
translator the possibility to change the word order, hence the Yoda
example.

 Which is IMHO rather more readable than a load of weird control codes hidden 
 in a text string that one then has to match against a list.

The point with hiding them in a control string is that you can have the
translator translate the control string, and not have to change the
source code, like with gettext. Very nice system.

Regards,

Martin

-- 
Martin Norbäck  [EMAIL PROTECTED]  
Kapplandsgatan 40   +46 (0)708 26 33 60
S-414 78  GÖTEBORG  http://www.dtek.chalmers.se/~d95mback/
SWEDEN  OpenPGP ID: 3FA8580B



signature.asc
Description: PGP signature


Re: preprocessing printf/regex strings (like ocaml)

2002-05-14 Thread Dylan Thurston

On Tue, May 14, 2002 at 03:45:36PM +0100, Robert Ennals wrote:
 Just thought I would jump in and say that, unlike (it seems)
 everyone else, I hate printf in C. It is a horrible horrible
 inextensible hack of a function that I find extremely awkward to
 use.
 ...
 I personally much prefer the syntax currently used in Haskell, which
 is also essentially what is used in most other recent languages,
 including Java, C++, and (god help me) Perl.
  
 In the example given, I could write:
 
 I have  ++ action ++   ++ number ++   ++ whatas
 where
 action = trained
 number = show 1
 whatas = Jedi
 
 Which is IMHO rather more readable than a load of weird control codes hidden 
 in a text string that one then has to match against a list.

How would you deal with internationalisation issues?

--Dylan


msg10875/pgp0.pgp
Description: PGP signature


Re: State monads don't respect the monad laws in Haskell

2002-05-14 Thread Dylan Thurston

On Tue, May 14, 2002 at 04:57:12PM +0200, George Russell wrote:
 According to the report
  Instances of Monad should satisfy the following laws:
 
 return a = k  = k
 m = return= m
 m = (\x - k x = h) = (m = k) = h
 so neither IO nor my events satisfy this.  Up to now I haven't had
 any problems with this.
 
 Does GHC or any other Haskell compiler actually rely on instances of
 Monad satisfying left identity?  If not, I would suggest dropping
 the requirement, if it can be done without upsetting category
 theorists.  (What the hell, they stole the term Monad from
 philosophy and changed its meaning, so why shouldn't we?)

I don't think this is necessarily wise to drop this from the report
altogether.  To me, it seems comparable to associativity of addition
for instances of Num; many instances don't satisfy it (e.g., Float),
but it's a useful guideline to keep in mind.

I've often been bothered by the inconsistent treatment of laws in the
report; why are there laws for functors, monads, and quot/rem and
div/mod, and not much else?  I'm pleased to see that the laws that are
given actually do have exceptions.

--Dylan




msg10876/pgp0.pgp
Description: PGP signature


Re: preprocessing printf/regex strings (like ocaml)

2002-05-14 Thread anatoli

Robert Ennals [EMAIL PROTECTED] wrote:
 I personally much prefer the syntax currently used in Haskell, which is also 
 essentially what is used in most other recent languages, including Java, C++, 
 and (god help me) Perl.
 
 In the example given, I could write:
 
 I have  ++ action ++   ++ number ++   ++ whatas
 where
 action = trained
 number = show 1
 whatas = Jedi

This is all fine and dandy, but how would you translate this to
42 different languages your customers want supported, with
different word order and all that?
-- 
anatoli t.

__
Do You Yahoo!?
LAUNCH - Your Yahoo! Music Experience
http://launch.yahoo.com
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: State monads don't respect the monad laws in Haskell

2002-05-14 Thread George Russell

Dylan Thurston wrote:
[snip]
 I've often been bothered by the inconsistent treatment of laws in the
 report; why are there laws for functors, monads, and quot/rem and
 div/mod, and not much else?  I'm pleased to see that the laws that are
 given actually do have exceptions.
[snip]
Even the quot/rem and div/mod laws are not always true, for example if you
divide by zero, or (for div/mod, where overflows cause an error) where
you get an overflow with (x `div` y) * y.  Perhaps we need something in the
report to state that these laws like these and the Monad laws are only intended
as aspirations rather than promises.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: preprocessing printf/regex strings (like ocaml)

2002-05-14 Thread Robert Ennals

 Robert Ennals [EMAIL PROTECTED] wrote:
  I personally much prefer the syntax currently used in Haskell, which is also 
  essentially what is used in most other recent languages, including Java, C++, 
  and (god help me) Perl.
  
  In the example given, I could write:
  
  I have  ++ action ++   ++ number ++   ++ whatas
  where
  action = trained
  number = show 1
  whatas = Jedi
 
 This is all fine and dandy, but how would you translate this to
 42 different languages your customers want supported, with
 different word order and all that?

Surely that problem only arises if one insists on encoding all the relevant 
information inside a string.

An alternative would be to encode all user-visible messages in an external 
module, with a Haskell function for each message.

The translator would then redefine this module for each language.

It doesn't involve any more complexity - it just shifts the complexity into a 
more expressive language.

For example:

module Messages

-- English language version 

where

stuffDone :: String - Int - String - String
stuffDone action number whatas 
= I have  ++ action ++   ++ (show number) ++   ++ whatas

jedi = Jedi
trained = Trained


Normal code then does the following:

import qualified Messages as M

putStrLn $ M.stuffDone M.trained 1 M.jedi



Much nicer IMHO.


-Rob 


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



Re: State monads don't respect the monad laws in Haskell

2002-05-14 Thread Jan-Willem Maessen

Dylan Thurston [EMAIL PROTECTED] writes:
 I don't think this is necessarily wise to drop this from the report
 altogether.  To me, it seems comparable to associativity of addition
 for instances of Num; many instances don't satisfy it (e.g., Float),
 but it's a useful guideline to keep in mind.

 I've often been bothered by the inconsistent treatment of laws in the
 report; why are there laws for functors, monads, and quot/rem and
 div/mod, and not much else?  I'm pleased to see that the laws that are
 given actually do have exceptions.

Chalk me up as someone in favor of laws without exceptions.

Allow me for a moment to make a reductio argument: We should just make
Haskell into a strict language.  Our equational laws still hold 95% of
the time---after all, we don't really write non-terminating
computations that often, and that's where the laws break down.  And
gosh darn, we sure get an efficient implementation.

Of course, this argument doesn't really work out for the Haskell
constructs we know and love (monadic computations spring to mind given
the present conversation, along with certain uses of parsing
combinators, but I bet you can think of your own examples).

Having spent several years working with versions of Haskell with
weakened equational semantics, I have become a bit of a reactionary on
this point.  Sort-of equational semantics just aren't powerful enough
for many applications---we spend our time mired in the corner cases
(such as non-termination), which is exactly what we were trying to
avoid by using Haskell in the first place.

I can't stress that enough.  Freedom from crazy corner cases is
Haskell's big selling point.  None of this except for infinite
computations stuff.  None of this as long as f has no side
effects.  If I have to worry about corner cases, I'm probably better
off adding type classes and beautiful syntax to OCaml.

That said, seq is a big wart on Haskell to begin with.  I might be
willing to allow nice rules like the monad laws to apply *as long as
the results are not passed (directly or indirectly) to seq*.  But I'm
not willing to go from the IO monad disobeys the laws in the presence
of seq, and that might be OK to my monad disobeys the laws in code
that never uses seq, and that's OK because even IO breaks the monad
laws.  And I'd really much rather we cleaned up the semantics of
seq---or better yet, fixed the problems with lazy evaluation which
make seq necessary in the first place.  [Let me be clear: I believe
hybrid eager/lazy evaluation, the subject of my dissertation, does
eliminate the need for seq in most cases---so I'm a bit biased here.]

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



Re: preprocessing printf/regex strings (like ocaml)

2002-05-14 Thread anatoli

Robert Ennals [EMAIL PROTECTED] wrote:
 Surely that problem only arises if one insists on encoding all the relevant 
 information inside a string.

This is pretty much the only option, because translators
and programmers are different people. Translators can deal with
simple text files with one message string per line and not
much else. You can't hire a translation firm and tell them
translate this Haskell module for me.

You can treat message strings as declarations in a specialised
language. This language can be typed, and you could theoretically
typecheck it against your Haskell program using specialised tools.
But translators need to see simple readable message strings.
-- 
anatoli t.

__
Do You Yahoo!?
LAUNCH - Your Yahoo! Music Experience
http://launch.yahoo.com
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: State monads don't respect the monad laws in Haskell

2002-05-14 Thread George Russell

S.M.Kahrs wrote:
[snip]
 I don't think this really solves the problem with the left unit
 (not in general, and not for IO either),
 it merely pushes it to a different place.
[snip]
Not being a category theorist I find this all a bit confusing.  Can you
give an example where with GHC and the fix I suggested you can show that
the associative law has been broken?
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: State monads don't respect the monad laws in Haskell

2002-05-14 Thread S.M.Kahrs

 S.M.Kahrs wrote:
 [snip]
  I don't think this really solves the problem with the left unit
  (not in general, and not for IO either),
  it merely pushes it to a different place.
 [snip]
 Not being a category theorist I find this all a bit confusing.

Nothing to do with category theory.
I took the law you cited and checked it out.

  Can you
 give an example where with GHC and the fix I suggested you can show that
 the associative law has been broken?

I didn't try to find a counter example.
I tried to prove the result and got stuck:

This is the law I was stuck with:
m = (\x - k x = h) === (m = k) = h  

There were two cases to consider, m=R a, and m=M a - the former works out nicely,
but with the latter you get:

m = (\x - k x = h)
=   M a = (\x - k x = h)
=   M (a = \a'-case (\x - k x = h) a' of
R b - return b
M c - c)
=   M (a = \a'-case (k a' = h) of
R b - return b
M c - c)

and on the other side:
(m = k) = h 
=   (M a = k) = h
=   M (a = \a'-case k a' of
R b - return b
M c - c) = h
=   M ((a = \a'-case k a' of
R b - return b
M c - c) = \a''-case h a'' of
R b - return b
M c - c)

Assuming that the associativity law holds for the original monad
(the one we try to fix for its dodgy left unit) then this can be changed to:

M (a = \a' - (\a'-case k a' of
R b - return b
M c - c) a' = \a''-case h a'' of
R b - return b
M c - c)
=   M ((a = \a' - case k a' of
R b - return b
M c - c) = \a''-case h a'' of
R b - return b
M c - c)

Using associativity again:
=   M (a = \x-(\a' - case k a' of
R b - return b
M c - c)x=(\a''-case h a'' of
R b - return b
M c - c))
=   M (a = \a' - (case k a' of
R b - return b
M c - c) = \a''-case h a'' of
R b - return b
M c - c)

Assuming further that = is left-strict we can change that to:
=   M (a = \a' - (case k a' of
R b - return b = \a''-...
M c - c = \a''-...))
where the ... is twice the old case h a'' expression.

Now, this is the expression why I claimed the left-unit property of
the underlying monad would still show: if (return b=f) is the same
as f b (in the monad we try to fix) then the first part of this case
expression simplifies to exactly the same thing as we had derived from the
other side of the equation.

But if it does not hold, we should be able to construct a counter example
using the left-unit counter example from the underlying monad together
with, say, k=R.  This all under the assumptions that the original monad m
satisfied the assoc law and that its = is left-strict.

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



Re: State monads don't respect the monad laws in Haskell

2002-05-14 Thread Ken Shan

On 2002-05-14T12:32:30-0400, Jan-Willem Maessen wrote:
 And I'd really much rather we cleaned up the semantics of
 seq---or better yet, fixed the problems with lazy evaluation which
 make seq necessary in the first place.

A general question: What is seq useful for, other than efficiency?

-- 
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
QUIET! Do you smell something?



msg10886/pgp0.pgp
Description: PGP signature


Re: State monads don't respect the monad laws in Haskell

2002-05-14 Thread Hal Daume III

It's useful for:

debug :: Show a = a - a
debug x = unsafePerformIO (hPutStrLn stderr (show x)) `seq` x

(Presumably trace is defined similarly)

One may ask the question: what is seq useful for not in conjunction with
unsafePerformIO, other than efficiency.  That, I don't know the answer to.

 - Hal

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Tue, 14 May 2002, Ken Shan wrote:

 On 2002-05-14T12:32:30-0400, Jan-Willem Maessen wrote:
  And I'd really much rather we cleaned up the semantics of
  seq---or better yet, fixed the problems with lazy evaluation which
  make seq necessary in the first place.
 
 A general question: What is seq useful for, other than efficiency?
 
 -- 
 Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
 QUIET! Do you smell something?
 


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



Re: State monads don't respect the monad laws in Haskell

2002-05-14 Thread Jorge Adriano


 One may ask the question: what is seq useful for not in conjunction with
 unsafePerformIO, other than efficiency.  That, I don't know the answer to.

Here is an example.

 main::IO()
 main=do
  time1 - getCPUTime
  w - return $! calcSomething
  time2 - getCPUTime
...

J.A.

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



How to get functional software engineering experience?

2002-05-14 Thread Jeffrey Palmer

Hello all,

I've got a not-quite-so-technically-detailed question for everyone.

For the past ten or so years, I've been building relatively large real-world 
software systems, and I've always been interested in finding new and 
innovative ways to reduce complexity and improve system maintainability. I 
was recently seduced by functional programming, and I'm now VERY interested 
in applying a functional software engineering approach to a real project.

However, it appears that the only place (short of Ericsson) I can actually 
work on a complex functional system is in academia. Unfortunately, this is 
not an option, as I have no Ph.D., and going back to school is probably not 
realistic.

Are there any options for people like me, or does my functional experience 
remain limited to the hobby* work I can squeeze in at night and on weekends?

Thoughts?

- j

* I'm building a realistic image synthesis package in Haskell, if anyone's 
interested.  ;)

-- 
The river is moving. 
The blackbird must be flying.


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



Re: State monads don't respect the monad laws in Haskell

2002-05-14 Thread Iavor S. Diatchki

hello,

this is misleading. seq only evaluates to whnf, i.e.
the outermost lazy constructor (or lambda) and that only if the
seq ... expression is actually evaluated, which is often tricky to 
ensure.  furthermore, for non-functions one can get the same behaviour,
by using a case with a pattern.

here is why i think the example does not illustrate what is seq good for:

 main::IO()
 main=do
  time1 - getCPUTime
  w - return $! map undefined [1..]
  time2 - getCPUTime
   

the above computation does not take very long.

bye
iavor


Jorge Adriano wrote:
One may ask the question: what is seq useful for not in conjunction with
unsafePerformIO, other than efficiency.  That, I don't know the answer to.
 
 
 Here is an example.
 
 
main::IO()
main=do
 time1 - getCPUTime
 w - return $! calcSomething
 time2 - getCPUTime
 
 ...
 
 J.A.
 
 ___
 Haskell mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell
 



-- 
==
| Iavor S. Diatchki, Ph.D. student   |
| Department of Computer Science and Engineering |
| School of OGI at OHSU  |
| http://www.cse.ogi.edu/~diatchki   |
==

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



Re: State monads don't respect the monad laws in Haskell

2002-05-14 Thread Hal Daume III

True, but using seq you can define deepSeq/rnf (depening on which camp
you're from), which isn't misleading in this way.

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Tue, 14 May 2002, Iavor S. Diatchki wrote:

 hello,
 
 this is misleading. seq only evaluates to whnf, i.e.
 the outermost lazy constructor (or lambda) and that only if the
 seq ... expression is actually evaluated, which is often tricky to 
 ensure.  furthermore, for non-functions one can get the same behaviour,
 by using a case with a pattern.
 
 here is why i think the example does not illustrate what is seq good for:
 
  main::IO()
  main=do
   time1 - getCPUTime
   w - return $! map undefined [1..]
   time2 - getCPUTime

 
 the above computation does not take very long.
 
 bye
 iavor
 
 
 Jorge Adriano wrote:
 One may ask the question: what is seq useful for not in conjunction with
 unsafePerformIO, other than efficiency.  That, I don't know the answer to.
  
  
  Here is an example.
  
  
 main::IO()
 main=do
  time1 - getCPUTime
  w - return $! calcSomething
  time2 - getCPUTime
  
  ...
  
  J.A.
  
  ___
  Haskell mailing list
  [EMAIL PROTECTED]
  http://www.haskell.org/mailman/listinfo/haskell
  
 
 
 
 -- 
 ==
 | Iavor S. Diatchki, Ph.D. student   |
 | Department of Computer Science and Engineering |
 | School of OGI at OHSU  |
 | http://www.cse.ogi.edu/~diatchki   |
 ==
 
 ___
 Haskell mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell
 

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



Re: State monads don't respect the monad laws in Haskell

2002-05-14 Thread Alastair Reid


Hal Daume [EMAIL PROTECTED] writes:
 [seq is] useful for:
 
 debug :: Show a = a - a
 debug x = unsafePerformIO (hPutStrLn stderr (show x)) `seq` x
 
 (Presumably trace is defined similarly)
 
 One may ask the question: what is seq useful for not in conjunction with
 unsafePerformIO, other than efficiency.  That, I don't know the answer to.


Of course, this can be defined without seq:

 debug :: Show a = a - a
 debug x = unsafePerformIO (hPutStrLn stderr (show x)  return x)

-- 
Alastair ReidReid Consulting (UK) Ltd
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: How to get functional software engineering experience?

2002-05-14 Thread Andrew J Bromage

G'day all.

On Tue, May 14, 2002 at 04:47:13PM -0500, Jeffrey Palmer wrote:

 Are there any options for people like me, or does my functional experience 
 remain limited to the hobby* work I can squeeze in at night and on weekends?
 
 Thoughts?

The first thing you have to understand is that there isn't a lot of
functional (or even declarative) software engineering experience out
there.

Going into academia wouldn't help even if you were qualified.  With all
due respect to the fine people who have produced some wonderful pieces
of software, they tend to concentrate on research rather than
engineering, as they should.

On the other hand, it's an exciting time to do engineering in
declarative languages, because we can invent the design patterns and
discover what the good habits are as we go along.

Yay for the bleeding edge.

Slight digression: Would it be good to have a forum to discuss the
specific issues which arise when doing software engineering in Haskell,
or declarative languages in general?  Just a thought...

All I can suggest that you do is if you have some leeway in how you
implement something, do it in Haskell.  Especially if it's a tool to
be used internally.

 * I'm building a realistic image synthesis package in Haskell, if anyone's 
 interested.  ;)

You've got me curious now.  I was using Haskell last year while
working in the visual effects industry.  We might discuss this
off-list...

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



(no subject)

2002-05-14 Thread LAURENT MPETI KABILA

REQUEST FOR URGENT BUSINESS ASSISTANCE
--
I stumbled into your contact by stroke of luck after a
long search for an honest and trust worthy person who
could handle issue with high confidentiality.
I was so dilghted when i got your contact and i decided
to contact you  and solicite for your kind assistance.
i hope you will let this issue to remain confidential even
if you are not interested because of my status.

I am Laurent Mpeti Kabila (Jnr) the second son of
Late President LAURENT DESIRE KABILA the immediate
Past president of the DEMOCRATIC REPUBLIC OF CONGO in
Africa who was murdered by his opposition through his personal
bodyguards in his bedroom on Tuesday 16th January, 2001.
I have the privilege of being mandated by my father,s
colleagues to seek your immediate and urgent co-operation
to receive into your bank account the sum of US $25m.
(twenty-five million Dollars) and some thousands carats
of Diamond. This money and treasures was lodged in a vault with a
security firm in Europe and South-Africa.

SOURCES OF DIAMONDS AND FUND
In August 2000, my father as a defence minister and
president has a meeting with his cabinet and armychief about the
defence budget for 2000 to 2001 which was US $700m.
so he directed one of his best friend. Frederic Kibasa Maliba
who was a minister of mines and a political party leader known
as the Union Sacree de,opposition radicale et ses allies (USORAL)
to buy arms with US $200m on 5th January 2001; for him to finalize
the arms deal,my father was murdered. f.K. Maliba (FKM) and I have
decided to keep the money with a foreigner after which he will use
it to contest for the political election. Inspite of all this we
have resolved to present you or your company for the firm to pay
it into your nominated account the above sum and diamonds.
This transaction should be finalized within seven (7) working
days and for your co-operation and partnership, we have unanimously
agreed that you will be entitled to 5.5% of the money when successfully
receive it in your account. The nature of your business is not relevant to
the successful execution of this transaction what we require is your
total co-operation and commitment to ensure 100%risk-free transaction at
both ends and to protect the persons involved in this transaction  strict
confidence and utmost secrecy is required even after the uccessful conclusion
of this transaction. If this proposal is acceptable to you, kindly provide me
with your personal telephone and fax through my E-mail box for immediate
commencement of the transaction. I count on your honour to keep my
secret, SECRET.

Looking forward for your urgent reply

Thanks.
Best Regards

MPETI L. KABILA (Jnr)






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



Re: How to get functional software engineering experience?

2002-05-14 Thread John Hughes


 However, it appears that the only place (short of Ericsson) I can actually
 work on a complex functional system is in academia. Unfortunately, this is
 not an option, as I have no Ph.D., and going back to school is probably not
 realistic.

There are other companies using Erlang, if not on as large a scale. The
Erlang User Conference (proceedings online at erlang.org) is a good
starting point to find out which. Some of the best stories, though, are
from very small Erlang groups in companies mainly using something else...

I would guess the biggest Haskell company is Galois Connections Inc
(galois.com), although I know there are others. Funny there's no Haskell
in Industry section on haskell.org -- it might be small, but it wouldn't
be empty, if people using Haskell were willing to stand up and be counted.

John Hughes

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



Re: State monads don't respect the monad laws in Haskell

2002-05-14 Thread Jay Cox


On Tue, 14 May 2002, Ken Shan wrote:

 On 2002-05-14T12:32:30-0400, Jan-Willem Maessen wrote:
  And I'd really much rather we cleaned up the semantics of
  seq---or better yet, fixed the problems with lazy evaluation which
  make seq necessary in the first place.

 A general question: What is seq useful for, other than efficiency?

seq can create a new, strict definition of a function from an existing
non-strict function.

const a = \_ - a

(const nonstrict in second arg)

strict_const a b = seq b (const a b)

strict_const now strict in second arg, even though it doesnt use arg.


I believe the strictness properties of functions in haskell and
program-execution-flow are very much intertwined, as in one defines the
other.  This seems like a simple concept, and I know of no real proof,
but I think the idea is worth considering.


I have found that functions can be classified three ways (for some given
argument to the function)  I will use the first argument for simplicity.


Strict:
1. For all values x for all of v_1 ... v_n ,

f _|_ v_1 ... v_n = _|_


Conditionally-Strict:
2. There exists a value x for v_i (1=i=n) such that when v_i =x

f _|_ v_1 ... v_i .. vn = _|_

but it is not the case that f is strict (in the argument in question).


Lazy:
3. There exists no value x for v_i (1=i=n) such that

f _|_ v1 .. vn = _|_




When there is only one argument, the cases are wittled down to case one
and case three, or strict versis nonstrict.

When f _|_ a = _|_ for some a, that means when f is reduced, f causes some
reduction in the first argument of f.  For the third case, f doesn't
cause any reduction in the first argument.

Most functions I believe are in case two, or conditionally strict in some
argument.  here's an example.





lets define a simplified take function

take 0 _ = []
take n (x:xs) = x :take (n-1) xs

Prelude take 0 undefined :: [Int]
[]
Prelude take 1 undefined :: [Int]
*** Exception: Prelude.undefined

It just so happens that take is not strict in the second argument
when the first argument happens to be zero.

we can fix this with seq (or perhaps by redefining take just a tad
so it pattern matches on the list or something)

take' 0 [] = []
take' 0 xs = []
take' n (x:xs) = x:take' (n-1) xs

take'' n l = seq l (take n l)

so now then
Main take' 0 undefined :: [Int]
*** Exception: Prelude.undefined
Main take'' 0 undefined :: [Int]
*** Exception: Prelude.undefined


/**Aside:
but did I really fix take''? that is, are take' and take'' the same?

Main take' 1 (9:undefined)
*** Exception: Prelude.undefined
Main take'' 1 (9:undefined)
[9]

No.  an almost equivalant definition to take could be.

take'' 0 [] = []
take'' 0 xs = []
take'' n (x:xs) = x:take (n-1) xs
  ^^notice the use of take instead of take'' !!

**/



So what have I done?  With strict_const, I took a lazy function and made
it strict. with take'', I took a conditionally strict function and made it
strict.  all with the simple application of seq.  I also changed the order
of evaluation for the application of both functions, obviously.

I hope I have shown some evidence of why I think my conjecture is correct.
Why does it matter if my conjecture is correct and what does it have to do
with this thread?  I'm sure it has something to do with it, but my head
hurts trying to think of it.  Seq has to do with changing the order of
operations, which I'm trying to say also changes strictness properties.
Ugh.  I swear they're all related somehow, I just can't grasp all of it at
the moment.

Appologies if my message seems rather incoherent.  I thought about not
sending it but I also thought there was enough useful info (for somebody)
that it might just be worth posting.  I am not a researcher, so take
this message with usual dosage of salt.

Cheers,

Jay Cox

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



Re: Replacing the Prelude

2002-05-14 Thread Dylan Thurston

On Sun, May 12, 2002 at 09:31:38PM -0700, Ashley Yakeley wrote:
 I have recently been experimenting writing code that replaces large 
 chunks of the Prelude, compiling with -fno-implicit-prelude. I notice 
 that I can happily redefine numeric literals simply by creating functions 
 called 'fromInteger' and 'fromRational': GHC will use whatever is in 
 scope for those names.
 
 I was hoping to do something similar for 'do' notation by redefining 
 (), (=) etc., but unfortunately GHC is quite insistent that 'do' 
 notation quite specifically refers to GHC.Base.Monad (i.e. Prelude.Monad, 
 as the Report seems to require). I don't suppose there's any way of 
 fooling it, is there? I was rather hoping 'do' notation would work like a 
 macro in rewriting its block, and not worry about types at all.
 
 I accept that this might be a slightly bizarre request. There are a 
 number of things I don't like about the way the Prelude.Monad class and 
 'do' notation are set up, and it would be nice to be able to experiment 
 with alternatives.

A while ago, there were extensive discussions about replacing the
Prelude on this list.  (Search for Prelude shenanigans.)  I started
to write up a design document for how to enable replacing the Prelude.
This boiled down to taking most of the syntactic sugar defined in
the report seriously, ignoring the types (as you say).

I'm surprised that ghc uses the fromInteger and fromRational that are
in scope; I thought there was general agreement that it should use the
Prelude.from{Integer,Rational} in scope.

As I recall, there were several relevant bits of syntactic sugar:

- Numeric types, including 'fromInteger', 'fromRational', and
  'negate'.  This all works fine, except that the defaulting mechanism
  is completely broken, causing a number of headaches.

- Monads.  The translation given in the report is clean, and it seems
  like it can be used without problems.

- Bools.  There was a slight problem here: the expansion of
  'if ... then ... else ...' uses a case construct referring to the
  constructors of the Bool type, which prevents any useful
  redefinition of Bool.  I would propose using a new function,
  'Prelude.ifThenElse', if there is one in scope.

- Enumerations.  Clean syntactic sugar.

- List comprehensions.  The report gives one translation, but I think
  I might prefer a translation into monads.

- Lists and tuples more generally.  At some point the translations
  start getting too hairy; I think I decided that lists and tuples
  were too deeply intertwined into the language to change cleanly.

I'll dig up my old notes and write more, and then maybe write a
complete design document and get someone to implement it.

--Dylan Thurston


msg01674/pgp0.pgp
Description: PGP signature


RE: Replacing the Prelude

2002-05-14 Thread Simon Peyton-Jones

Ashley writes

|  I was hoping to do something similar for 'do' notation by redefining
|  (), (=) etc., but unfortunately GHC is quite insistent 
| that 'do' notation quite specifically refers to GHC.Base.Monad 

Dylan replies

| I'm surprised that ghc uses the fromInteger and fromRational 
| that are in scope; I thought there was general agreement that 
| it should use the Prelude.from{Integer,Rational} in scope.

Ashley is referring to a GHC extension.  Normally, GHC uses
Prelude.fromInteger etc, regardless of what is in scope.  But if you
say -fno-implicit-prelude, GHC will instead use whatver fromInteger
is in scope.  (This is documented in the manual.)

Ashley's question, as I understand is whether something similar
could be done for monads. 

Answer: I think so, without much bother.   I'm beavering away on
a Haskell workshop paper at the moment, but ping me in a fortnight
to do it.

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