[Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-03 Thread Bulat Ziganshin
Hello Wolfgang,

Friday, February 03, 2006, 1:46:56 AM, you wrote:
 i had one idea, what is somewhat corresponding to this discussion:

 make a strict Haskell dialect. implement it by translating all
 expressions of form f x into f $! x and then going to the standard
 (lazy) haskell translator. the same for data fields - add to all field
 definitions ! in translation process. then add to this strict
 Haskell language ability to _explicitly_ specify lazy fields and lazy
 evaluation, for example using this ~ sign

 what it will give? ability to use Haskell as powerful strict language,
 what is especially interesting for real-world programmers. i have
 found myself permanently fighting against the lazyness once i starting to
 optimize my programs. for the newcomers, it just will reduce learning
 path - they don't need to know anything about lazyness

WJ Since laziness often allows you to solve problems so elegantly, I'm really 
WJ scared of the idea of a Strict Haskell! :-(  Is laziness really so 
unreal 
WJ that real-world programmers have to see it as an enemy which they have to 
WJ fight against?

WJ In fact, I was kind of shocked as I read in Simon Peyton Jones' 
presentation 
WJ Wearing the hair shirt [1] that in his opinion Lazyness doesn't really 
WJ matter.

i suggest you to write some large program like darcs and try to make
it as efficient as C++ ones. i'm doing sort of it, and i selected
Haskell primarily because it gives unprecedented combination of power
and safety due to its strong but expressive type system, higher-order
functions and so on. i also use benefits of lazyness from time to
time, and may be even don't recognize each occasion of using lazyness.
but when i'm going to optimize my program, when i'm asking myself why
it is slower than C counterparts?, the answer is almost exclusively
because of lazyness. for example, i now wrote I/O library. are you
think that i much need lazyness here? no, but that i really need is
the highest possible speed, so now i'm fighting against lazyness even
more than usual :)

well, 80% of any program don't need optimization at all. but when i
write remaining 20% or even 5%, i don't want to fight against
something that can be easily fixed in systematic way. all other
widespread languages have _optional_, explicitly stated lazyness in
form of callable blocks, even the Omega goes in this way. and i'm
interested in playing with such Haskell dialect in order to see how my
programming will change if i need to explicitly specify lazyness when
i need it, but have strictness implicitly. i think that newcomers from
other languages who wants to implement real projects instead of
experimenting will also prefer strict Haskell

you may hear that last days Haskell become one of fastest language in
the Shootout. why? only because all those programs was rewritten to be
strict. it was slow and hard process. and adding preprocessor that
makes all code strict automagically will allow to write efficient
Haskell programs without reading fat manuals

each laguage feature has its time. 15 years ago i could substantially
speed up C program by rewriting it in asm. Now the C compilers in most
cases generate better code than i can. moreover, strict FP languages
now are ready to compete with gcc. But lazy languages are still not
compiled so efficient that they can be used for time-critical code.
so, if we don't want to wait another 10 years, we should implement
easier ways to create strict programs. if you think that lazy
programming is great, you can show this in shootout or by showing me
the way to optimize code of my real programs. i'm open to new
knowledge :)

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


[Haskell-cafe] Re: HUnit

2006-02-03 Thread Shae Matijs Erisson
Matt Roberts [EMAIL PROTECTED] writes:

 I am in love with HUnit and QuickCheck.  However, I am missing one
 important functionality

I'm rather fond of them also.
Check my prototype of test-driven-development for QuickCheck:
http://www.scannedinavian.com/~shae/qc-tdd.tgz

 I want to call a command line program that will search all the .hs
 files I have in a particular directory, pull out all HUnit test
 (based on what they are called, or perhaps their type signature) and
 run them all.

Look at the quickcheck script by John Hughes, it searches for 'prop_' tests and
executes them. You can likely add 'unit_' to that without much trouble.
-- 
I've tried to teach people autodidactism,| ScannedInAvian.com
but it seems they always have to learn it for themselves.| Shae Matijs Erisson

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


[Haskell-cafe] Re: Haskell code for this example of flow control

2006-02-03 Thread Maurício

Kurt Hutchinson wrote:

On 2/2/06, Maurício [EMAIL PROTECTED] wrote:


  I understand those examples, but I really would like to know how to
do that with monads. I would like to ask the same question, but now with
this code:

double a = 1000;
double b = 0;
while (a != b) {
a /= 2;
cout  a; // Prints a
cin  b; // User gives a number, stored in b
};



An idiomatic approach:
example :: Double - Double - IO ()
example a b
| a == b= return ()
| otherwise = do
let a' = a / 2
print a'
b' - readLn
example a' b'

main = example 1000 0


  Thanks! Robert's, Chris' and yours examples solved many of my 
questions. I understand I can insert modifications in IORefs (as used by 
Robert and Chris) inside the loop above:


| otherwise = do
 let a' = a / 2
 ...
 modifyIORef some_ioref some_function
 ...
 example a' b'

  I wonder if I could write a generic while based on your example:

while :: (a - IO a) - (a - Bool) - IO ()

  I'll probably learn something trying that.

  Best,
  Maurício

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


Re: [Haskell-cafe] Re: Haskell code for this example of flow control

2006-02-03 Thread Robert Dockins


On Feb 3, 2006, at 11:28 AM, Maurício wrote:

Kurt Hutchinson wrote:

On 2/2/06, Maurício [EMAIL PROTECTED] wrote:
  I understand those examples, but I really would like to know  
how to
do that with monads. I would like to ask the same question, but  
now with

this code:

double a = 1000;
double b = 0;
while (a != b) {
a /= 2;
cout  a; // Prints a
cin  b; // User gives a number, stored in b
};

An idiomatic approach:
example :: Double - Double - IO ()
example a b
| a == b= return ()
| otherwise = do
let a' = a / 2
print a'
b' - readLn
example a' b'
main = example 1000 0


  Thanks! Robert's, Chris' and yours examples solved many of my  
questions. I understand I can insert modifications in IORefs (as  
used by Robert and Chris) inside the loop above:


| otherwise = do
 let a' = a / 2
 ...
 modifyIORef some_ioref some_function
 ...
 example a' b'

  I wonder if I could write a generic while based on your example:

while :: (a - IO a) - (a - Bool) - IO ()

  I'll probably learn something trying that.


FYI, here's a thread from a few months back about monad control  
structures; it may also provide some enlightenment.



http://www.haskell.org/pipermail/haskell-cafe/2005-October/011890.html



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


[Haskell-cafe] Pythonic monads

2006-02-03 Thread Graham Klyne
Constructing some code today in Python, using some functional-style coding
idioms, I found myself wondering if there would be any real benefit to using a
monad-based implementation (i.e. other than to demonstrate that it can be done).

The application that sparked this line of thought was a simple filter to trim
comments and whitespace out of an XML document.  I ended up with a simple
state-machine driven filter, thus:

[[
# Strip comments from XML strings
def stripXmlComments(x):
# State table for stripping XML comments
stStripXmlComments = \
{ 0: match1('',(1,stateFilterHold),(0,stateFilterPass))
, 1: match1('!',(2,stateFilterHold),(0,stateFilterPass))
, 2: match1('-',(3,stateFilterHold),(0,stateFilterPass))
, 3: match1('-',(4,stateFilterDrop),(0,stateFilterPass))
, 4: match1('-',(5,stateFilterDrop),(4,stateFilterDrop))
, 5: match1('-',(6,stateFilterDrop),(4,stateFilterDrop))
, 6: match1('',(0,stateFilterDrop),(4,stateFilterDrop))
}
return stateFilter(stStripXmlComments,x)

# Simple state machine driven filter
#
# The state table is a dictionary indexed by state values, where the
# initial state is 0, and each entry is a function that accepts a next
# symbol and returns a pair of (next state, action), where action is
# one of 'stateFilterPass', 'stateFilterDrop', 'stateFilterHold'.
# stateFilterHold means that the disposition will be determined later.
#
# The result is an iterator that returns elements from the filtered
# subsequence of the supplied sequence.
#
def stateFilter(stable,seq):
queue = []
state = 0
for symbol in seq:
(state,action) = stable[state](symbol)
(queue,emit) = action(queue,symbol)
for e in emit: yield e
return
def stateFilterPass(q,n):
return ([],q+[n])
def stateFilterDrop(q,n):
return ([],[])
def stateFilterHold(q,n):
return (q+[n],[])

# State transition function to match the specified symbol and return
# 'eqval' if matched, otherwise 'neval'
def match1(sym,eqval,neval):
def m(sym,eqval,neval,next):
if next==sym:  return eqval
return neval
return curry(m,sym,eqval,neval)

def curry(func, *args):

Curry multiple arguments:
See: http://aspn.activestate.com/ASPN/Cookbook/Python/Recipe/229472

def curried(*args2):
args2 = args + args2
return func(*args2)
return curried
]]

and a test case:
[[
def testFilter02(self):
fullstr = !-abc- !--def-- !- -ghi--
trimstr = list(stripXmlComments(fullstr))
expstr  = list(!-abc-  !- -ghi--)
assert trimstr==expstr, \
   stripSpaces, expected:\n+expstr+\nFound:\n+trimstr
]]

In thinking about this implementation, it seemed to me that this employed
patterns characteristic of a monadic type:  each entry in the state table (in
this case, an instance of match1, a curried function) is like a step in a
monadic computation, updating the monadic value and also returning some value.

What I can't quite visualize is if the code in Python would actually look any
better if it were implemented with a monadic type, as one might readily choose
for a Haskell implementation.  Or would there be no real benefit?

I have noticed that, while I like to use functional idioms in some of my Python
code, and the Python language is easily able to support these (even some lazy
evaluation, courtesy of generators), that the code doesn't always look as clean
as its Haskell equivalent.  In Haskell, composition and currying are fundamental
patterns and are directly supported by the syntax.  In Python, one has to work
harder to achieve these (e.g. the curry function above seems rather convoluted
to me, for such a fundamental notion).

Thoughts? Comments?

#g

-- 
Graham Klyne
For email:
http://www.ninebynine.org/#Contact

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


Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-03 Thread Brian Hulley

Bulat Ziganshin wrote:

Hello Wolfgang,

Friday, February 03, 2006, 1:46:56 AM, you wrote:

i had one idea, what is somewhat corresponding to this discussion:

make a strict Haskell dialect. implement it by translating all
expressions of form f x into f $! x and then going to the
standard (lazy) haskell translator. the same for data fields - add
to all field definitions ! in translation process. then add to
this strict
Haskell language ability to _explicitly_ specify lazy fields and
lazy evaluation, for example using this ~ sign


[Apologies for replying to a reply of a reply but I don't seem to have 
received the original post]


I've been thinking along these lines too, because it has always seemed to me 
that laziness is just a real nuisance because it hides a lot of inefficiency 
under the carpet as well as making the time/space behaviour of programs 
difficult to understand...


One question is how to get some kind of do notation that would work well 
in a strict setting.
The existing do notation makes use of lazyness in so far as the second arg 
of   is only evaluated when needed. Perhaps a new keyword such as go 
could be used to use = instead ie:


go {e1;e2;e3}   ===   e1 = (\_- (e2 = (\_-e3)))

Of course this doesn't solve the problem of how to translate programs that 
make heavy use of mapM etc.


I wonder: is monadic programming really dependent on lazyness or is there a 
realistic (ie not impossibly complicated) way to use monads in a strict 
setting?


A related question is: could monadic programming ever be as efficient as 
side-effect programming?


Regards, Brian. 


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


Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-03 Thread Jan-Willem Maessen


On Feb 3, 2006, at 2:33 PM, Brian Hulley wrote:


Bulat Ziganshin wrote:

Hello Wolfgang,

Friday, February 03, 2006, 1:46:56 AM, you wrote:

i had one idea, what is somewhat corresponding to this discussion:

make a strict Haskell dialect. implement it by translating all
expressions of form f x into f $! x and then going to the
standard (lazy) haskell translator. the same for data fields - add
to all field definitions ! in translation process. then add to
this strict
Haskell language ability to _explicitly_ specify lazy fields and
lazy evaluation, for example using this ~ sign


[Apologies for replying to a reply of a reply but I don't seem to  
have received the original post]


I've been thinking along these lines too, because it has always  
seemed to me that laziness is just a real nuisance because it hides  
a lot of inefficiency under the carpet as well as making the time/ 
space behaviour of programs difficult to understand...


I pointed out some problems with strict Haskell in a recent talk, but  
I think it'd be worth underscoring them here in this forum.


First off, I should mention that I was one of the main implementors  
of pH, which had Haskell's syntax, but used eager evaluation.  So  
what I'm about to say is based on my experience with Haskell code  
which was being eagerly evaluated.


There is one very difficult piece of syntax in a strict setting: The  
*where* clause.  The problem is that it's natural to write a bunch of  
bindings in a where clause which only scope over a few conditional  
clauses.  I'm talking about stuff like this:


f x
  | p x   = . a ...a . a  a ...
  | complex_condition = . b .. b ... b ..
  | otherwise = . a ... b .
  where a = horrible expression in x which is bottom when  
complex_condition is true.
b = nasty expression in x which doesn't terminate when p x  
is true.

complex_condition = big expression which
 goes on for lines and lines
 and would drive the reader
 insane if it occurred in line.

Looks pretty reasonable, right?  Not when you are using eager or  
strict evaluation.  I think a strict variant of Haskell would either  
end up virtually where-free (with tons of lets instead---a pity as I  
often find where clauses more readable) or the semantics of where  
would need to change.


This came up surprisingly more often than I expected, though it was  
hardly a universal problem.  The more interesting the code, the  
more likely there would be trouble in my experience.


A bunch of other stuff would have to be added, removed, or modified.   
The use of lists as generators would need to be re-thought (and  
probably discarded), idioms involving infinite lists would have to  
go, etc., etc.  But this is a simple matter of libraries (well, and  
which type(s) get(s) to use square brackets as special builtin  
notation).


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


Re: [Haskell-cafe] Pythonic monads

2006-02-03 Thread Collin Winter
On 2/3/06, Graham Klyne [EMAIL PROTECTED] wrote:
 I have noticed that, while I like to use functional idioms in some of my 
 Python
 code, and the Python language is easily able to support these (even some lazy
 evaluation, courtesy of generators), that the code doesn't always look as 
 clean
 as its Haskell equivalent.  In Haskell, composition and currying are 
 fundamental
 patterns and are directly supported by the syntax.  In Python, one has to work
 harder to achieve these (e.g. the curry function above seems rather 
 convoluted
 to me, for such a fundamental notion).

 Thoughts? Comments?

Hi Graham,

You might be interested in my `functional` package. It includes tools
for composition, partial application, flip, foldl, foldr, scanl and
scanr, all coded as C extensions for speed. I initially wrote the code
to scratch my own more-functional-programming-in-Python itch; maybe it
can help you out in that department as well : )

http://oakwinter.com/code/functional/

Feedback always appreciated.

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


Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-03 Thread Chris Kuklewicz
Brian Hulley wrote:
  ...

 [Apologies for replying to a reply of a reply but I don't seem to have
 received the original post]
 
 I've been thinking along these lines too, because it has always seemed
 to me that laziness is just a real nuisance because it hides a lot of
 inefficiency under the carpet as well as making the time/space behaviour
 of programs difficult to understand...
 
 One question is how to get some kind of do notation that would work
 well in a strict setting.
 The existing do notation makes use of lazyness in so far as the second
 arg of   is only evaluated when needed. Perhaps a new keyword such as
 go could be used to use = instead ie:
 
 go {e1;e2;e3}   ===   e1 = (\_- (e2 = (\_-e3)))
 
 Of course this doesn't solve the problem of how to translate programs
 that make heavy use of mapM etc.
 
 I wonder: is monadic programming really dependent on lazyness or is
 there a realistic (ie not impossibly complicated) way to use monads in a
 strict setting?
 
 A related question is: could monadic programming ever be as efficient as
 side-effect programming?
 
 Regards, Brian.

What about writing functions in a modified form of Control.Monad.Identity that
ensures the return value that forces the return values:

 module Control.Monad.Strict (Weak,mkWeak,unsafeMkWeak,runWeak,
  Deep,mkDeep,unsafeMkDeep,runDeep) where

Weak uses seq to achieve WHNF for it's argument

 newtype Weak a = WeakCon {runWeak :: a}
 mkWeak x = seq x (WeakCon x)
 unsafeMkWeak x = WeakCon x

 instance Functor Weak where
 fmap f w = mkWeak (f (runWeak w))

 instance Monad Weak where
 return x = mkWeak x
 w = f = f (runWeak w)


I can't make the deepSeq version typecheck:

Deep uses deepSeq to evaluate it's argument

 newtype Deep a = DeepCon {runDeep :: a}
 mkDeep x = deepSeq x (DeepCon a)
 unsafeDeep x = DeepCon x

 instance Functor Deep where
 fmap f d = mkDeep (f (runDeep d))

 instance Monad Deep where
 return d = mkDeep d
 d = f = f (runDeep d)

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


Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-03 Thread Chris Kuklewicz
Brian Hulley wrote:
 Bulat Ziganshin wrote:

 [Apologies for replying to a reply of a reply but I don't seem to have
 received the original post]
 
 I've been thinking along these lines too, because it has always seemed
 to me that laziness is just a real nuisance because it hides a lot of
 inefficiency under the carpet as well as making the time/space behaviour
 of programs difficult to understand...
 
 One question is how to get some kind of do notation that would work
 well in a strict setting.
 The existing do notation makes use of lazyness in so far as the second
 arg of   is only evaluated when needed. Perhaps a new keyword such as
 go could be used to use = instead ie:
 
 go {e1;e2;e3}   ===   e1 = (\_- (e2 = (\_-e3)))
 
 Of course this doesn't solve the problem of how to translate programs
 that make heavy use of mapM etc.
 
 I wonder: is monadic programming really dependent on lazyness or is
 there a realistic (ie not impossibly complicated) way to use monads in a
 strict setting?
 
 A related question is: could monadic programming ever be as efficient as
 side-effect programming?
 
 Regards, Brian.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 


What about writing functions in a modified form of Control.Monad.Identity that
ensures the return value that forces the return values:

 module Control.Monad.Strict (Weak,mkWeak,unsafeMkWeak,runWeak,
  Deep,mkDeep,unsafeMkDeep,runDeep) where

Weak uses seq to achieve WHNF for it's argument

 newtype Weak a = WeakCon {runWeak :: a}
 mkWeak x = seq x (WeakCon x)
 unsafeMkWeak x = WeakCon x

 instance Functor Weak where
 fmap f w = mkWeak (f (runWeak w))

 instance Monad Weak where
 return x = mkWeak x
 w = f = f (runWeak w)


I can't make the deepSeq version typecheck:

Deep uses deepSeq to evaluate it's argument

 newtype Deep a = DeepCon {runDeep :: a}
 mkDeep x = deepSeq x (DeepCon a)
 unsafeDeep x = DeepCon x

 instance Functor Deep where
 fmap f d = mkDeep (f (runDeep d))

 instance Monad Deep where
 return d = mkDeep d
 d = f = f (runDeep d)

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


Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-03 Thread Robin Green
On Fri, 3 Feb 2006 19:33:12 -
Brian Hulley [EMAIL PROTECTED] wrote:
 I've been thinking along these lines too, because it has always
 seemed to me that laziness is just a real nuisance because it hides a
 lot of inefficiency under the carpet as well as making the time/space
 behaviour of programs difficult to understand...
 
 One question is how to get some kind of do notation that would work
 well in a strict setting.
 The existing do notation makes use of lazyness in so far as the
 second arg of   is only evaluated when needed. Perhaps a new
 keyword such as go could be used to use = instead ie:
 
 go {e1;e2;e3}   ===   e1 = (\_- (e2 = (\_-e3)))

That's not necessary.  has something in common with if', where

if' True x _ = x
if' False _ y = y

- in both cases, it makes sense to evaluate the arguments lazily.

So simply make strictness the default and have laziness annotations
(for arguments), instead of making laziness the default and having
strictness annotations.

 A related question is: could monadic programming ever be as efficient
 as side-effect programming?

Monads can be viewed as code generators. So, with partial
evaluation, my guess is yes, at least in many important cases.
-- 
Robin
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-03 Thread John Meacham
On Fri, Feb 03, 2006 at 07:33:12PM -, Brian Hulley wrote:
 One question is how to get some kind of do notation that would work well 
 in a strict setting.
 The existing do notation makes use of lazyness in so far as the second 
 arg of   is only evaluated when needed. Perhaps a new keyword such as 
 go could be used to use = instead ie:

you can override () in your monad

instance Monad ... where
a  b = a `seq` b `seq` (a = \_ - b)


unless I am misunderstanding what you want.

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] Re[2]: strict Haskell dialect

2006-02-03 Thread Brian Hulley

Jan-Willem Maessen wrote:


I pointed out some problems with strict Haskell in a recent talk, but
I think it'd be worth underscoring them here in this forum.


Is the text of this talk or points raised in it available online anywhere?

snip There is one very difficult piece of syntax in a strict setting: 
The

*where* clause.  The problem is that it's natural to write a bunch of
bindings in a where clause which only scope over a few conditional
clauses.  I'm talking about stuff like this:

f x
  | p x   = . a ...a . a  a ...
  | complex_condition = . b .. b ... b ..
  | otherwise = . a ... b .
  where a = horrible expression in x which is bottom when
complex_condition is true.
b = nasty expression in x which doesn't terminate when p x
is true.
complex_condition = big expression which
 goes on for lines and lines
 and would drive the reader
 insane if it occurred in line.


Surely it would not be too difficult for the compiler to only evaluate the 
where bindings that are relevant depending on which guard evaluates to True 
ie in your example, the binding for a would be evaluated if p x is True, 
otherwise the complex_condition would be evaluated, and if True, b would be 
evaluated, otherwise a and b would be evaluated:


f x
| p x = let a = . in a a ...
| otherwise = let
complex_condition = ...
b = ...
 in
   if complex_condition then
   b  b
  else let
a = . a
 in
    a.b

where all the messy (possibly duplicated) let's are generated by the 
compiler so the user can still use the nice where syntax.


Regards, Brian. 


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


Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-03 Thread Brian Hulley

Robin Green wrote:

On Fri, 3 Feb 2006 19:33:12 -
Brian Hulley [EMAIL PROTECTED] wrote:

I've been thinking along these lines too, because it has always
seemed to me that laziness is just a real nuisance because it hides a
lot of inefficiency under the carpet as well as making the time/space
behaviour of programs difficult to understand...

One question is how to get some kind of do notation that would work
well in a strict setting.
The existing do notation makes use of lazyness in so far as the
second arg of   is only evaluated when needed. Perhaps a new
keyword such as go could be used to use = instead ie:

go {e1;e2;e3}   ===   e1 = (\_- (e2 = (\_-e3)))


That's not necessary.  has something in common with if', where

if' True x _ = x
if' False _ y = y

- in both cases, it makes sense to evaluate the arguments lazily.

So simply make strictness the default and have laziness annotations
(for arguments), instead of making laziness the default and having
strictness annotations.


Where would you put these laziness annotations?
If you put them in the function declaration eg as in:

if' :: ~a - ~b - Bool

presumably you'd want the compiler to pass the args as thunks instead of 
evaluated values. However this means that all args to every function would 
have to be passed as thunks, even though for strict functions these thunks 
would immediately be evaluated. The problem is that there is no way for the 
compiler to optimize out the thunk creation / evaluation step because it 
occurs across the black box of a function call, thus we wouldn't get the 
same efficiency as in a language such as ML where no thunks are created in 
the first place.


Ie there is a fundamental asymmetry between lazy annotations and strict 
annotations - it is trivial to go from lazy to strict before the function 
body is evaluated but impossible to unevaluate from strict back to lazy...


Regards, Brian. 


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


Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-03 Thread Brian Hulley

John Meacham wrote:

On Fri, Feb 03, 2006 at 07:33:12PM -, Brian Hulley wrote:

One question is how to get some kind of do notation that would
work well in a strict setting.
The existing do notation makes use of lazyness in so far as the
second arg of   is only evaluated when needed. Perhaps a new
keyword such as go could be used to use = instead ie:


you can override () in your monad

instance Monad ... where
a  b = a `seq` b `seq` (a = \_ - b)


unless I am misunderstanding what you want.

John


If strictness was the default (eg if the language were ML not Haskell), then 
in


putStr hello  putStr (show 1)

both args to  would be evaluated before  was called. Thus putStr (show 
1) would be evaluated before the combined monad is actually run, which would 
be wasteful if we were using a monad with a  function that only runs the 
rhs conditionally on the result of the lhs.
If Haskell were a strict language I think an equivalent for the do notation 
would have to lift everything (except the first expression) and use = 
instead of  .


Regards, Brian. 


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


Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-03 Thread Brian Hulley

Brian Hulley wrote:

if' :: ~a - ~b - Bool

Oooops :-)

 if' :: Bool - ~a - ~a - a

Regards, Brian.

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


Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-03 Thread Brian Hulley

Brian Hulley wrote:

Robin Green wrote:

snip
So simply make strictness the default and have laziness annotations
(for arguments), instead of making laziness the default and having
strictness annotations.


Where would you put these laziness annotations?
If you put them in the function declaration eg as in:

if' :: Bool - ~a - ~a - a   [corrected]

presumably you'd want the compiler to pass the args as thunks instead
of evaluated values. However this means that all args to every
function would have to be passed as thunks, even though for strict
functions these thunks would immediately be evaluated. The problem is
that there is no way for the compiler to optimize out the thunk
creation / evaluation step because it occurs across the black box
of a function call, thus we wouldn't get the same efficiency as in a
language such as ML where no thunks are created in the first place.


I'm just s slow!!! ;-) Of course the laziness info would now be part of 
the function's type so the compiler would be able to generate the correct 
code to prepare thunks or evaluated values before calling the function. So 
your idea of laziness annotations for args would give the best of both 
worlds :-)


Regards, Brian. 


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