Re: [Haskell-cafe] exceptions vs. Either

2004-08-04 Thread Ketil Malde
MR K P SCHUPKE [EMAIL PROTECTED] writes:

 As for head, I think it's fine that it throws an error because it is
 specified to be defined for only non-empty lists.

 But surely it is better to encode this fact in the type system by
 useing a separate type for non-empty lists.

Yes, in principle.  But that means you still need to write more and
tedious code to deal with it.  

And there's a question how far you can practically get with this
approach.  Are you going to discard lists in favor of tuples, just
because the type systems can't verify that the index passed to (!!) is
witin range?

 A mechanism for a function to report the caller site would obliviate
 the need for all this ugliness

 Unfortunately the cost of this is prohabative as the call stack
 would have to contain backtrace information. Also due to lazy
 evaluation the 'call site' may not be what you expect.

AFAICS, this disadvantage is shared by all other schemes of labeling
call sites.  The only difference is that I want to do it automatically
(perhaps when a debug option is passed to the compiler)

I don't want it for all functions or anything, just the annoying,
small, and commonly used leaf functions.

 Here's what John Meacham had to say:

 ---
 Note that pattern matching rather than deconstruction functions have a
 number of benefits, not just relating to error messages, consider two
 functions which use the head of their argument.

 f xs = ... head xs ...=20
 g (x:_) = ... x ...

 now, g is superior to f in several ways,=20

I agree with this.  How about constructs like

  mins = map (head.sort)

Is 

   mins = map ((\(x:_)-x).sort)

still so superior?  Is it really necessary to sacrifice code clarity
just to get decent error messages?

And how do you extend this approach to 'read' and (!!)?

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] exceptions vs. Either

2004-08-04 Thread MR K P SCHUPKE
Yes, in principle.  But that means you still need to write more and
tedious code to deal with it.

Just because code is tedious does not mean it is not necessary to
handle all corner cases. A robust application does not fail when
given unexpected input.

Are you going to discard lists in favor of tuples,

Of course not... You can actually define constrained datatypes where
the maximum length is a parameter of the type. Unfortunately in haskell
because these values have to be at the type level we end up encoding
them as Peano numbers... See Conor McBrides Faking It paper for
some examples of how to do this. Also see Oleg, Ralf and My paper
Stronly Typed Heterogeneous Lists to se how far you can get with
these techniques (we define a heterogeneous list that can be constrained
in many ways, including by length, or content type).

I guess in a way you are nearly right as these techniques fundamentaly
us binary products like (,) - but thats also exactly what any binary
constructor including ':' is anyway...

The only difference is that I want to do it automatically

My point was that you can manually label some functions, but to automatically
do it for all functions is going to cause big stack space problems - think
about recursive functions... or mutually recursive functions... 

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


Re: [Haskell-cafe] exceptions vs. Either

2004-08-04 Thread MR K P SCHUPKE

mins = map ((\(x:_)-x).sort)

maybe what you meant was:

case sort x of
   (x:_) - ... do whatever with x ...
   _ - ... do failure conition ...

As I said, if you can _guarantee_ non failure I guess head is okay, but the
fact that this thread started with the observation that the error produced
by head is difficault to track dow
n we must conclude that programmers make mistakes and cannot be trusted to
make such guarantees  Hence my suggestion to use the type system.

Effectively the 'case' forms a guarantee of non-emtyness for the stuff in 
the case... but you cannot pass this guarantee into functions like 'head'

Using the type system to encode such things allows this 'guarantee' to
be passed into functions... 

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


Re: [Haskell-cafe] exceptions vs. Either

2004-08-04 Thread David Roundy
On Tue, Aug 03, 2004 at 12:51:50PM +0200, Ketil Malde wrote:
 Is there any easy way (TH?) to amend these to output the line number
 of the offending caller?  It would be a great improvement to see
 something like
 
 Prelude.head : empty list in Foo.hs, line 4711
 
 since programs generally contain many, many calls to functions like
 these.  

I include the following file in most files (and always use the C
preprocessor):

import DarcsUtils ( bug )
#define impossible (bug $ Impossible case at ++__FILE__++:++show (__LINE__ :: 
Int)++ compiled ++__TIME__++ ++__DATE__)

#define fromJust (\m - case m of {Nothing - bug (fromJust error at 
++__FILE__++:++show (__LINE__ :: Int)++ compiled ++__TIME__++ ++__DATE__); Just 
x - x})

Here bug is a function that just calls error with a little prefix
explaining that there is a bug in darcs, and would the user please report
it.  Obviously, defining a head here would be just as easy, but I usually
have more trouble with fromJust, which in a few places gets called in
internal routines where I *should* know that the data structure has no
Nothings, but have been known to make mistakes.

I also catch all error exceptions and print a nicer error message, so I
use fail and error raw to indicate actual user errors.
-- 
David Roundy
http://www.abridgegame.org
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] exceptions vs. Either

2004-08-04 Thread Malcolm Wallace
Ketil Malde [EMAIL PROTECTED] writes:

 Hmm...if I run it through CPP and 
   #define HEAD (\x - if null x then error (__FILE__:__LINE__) else head x)
 is the __LINE__ resolved at the place of declaration or at the place of usage?

According to the C standard, at the position of /usage/ of the macro `HEAD'.

Incidentally, cpphs does not yet implement __FILE__ or __LINE__
replacements.  Is their usage widespread amongst Haskell users?

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


Re: [Haskell-cafe] exceptions vs. Either

2004-08-04 Thread Ketil Malde
MR K P SCHUPKE [EMAIL PROTECTED] writes:

 mins = map ((\(x:_)-x).sort)

 maybe what you meant was:

   case sort x of
  (x:_) - ... do whatever with x ...
  _ - ... do failure conition ...

No, I don't think so.  I only want the bug to be reported, and the
umatched pattern will do it nicely.

 Yes, in principle.  But that means you still need to write more and
 tedious code to deal with it.

 Just because code is tedious does not mean it is not necessary to
 handle all corner cases. A robust application does not fail when
 given unexpected input.

But if I use head, I should *know* that I never pass it an
empty list.  Whether head returns a Nothing or just crashes doesn't
matter, I have to go and fix my *design*, because it has a bug,
and not a corner case that should be handled.

 Are you going to discard lists in favor of tuples,

 Of course not... You can actually define constrained datatypes where
 the maximum length is a parameter of the type. 

The only difference is that I want to do it automatically

 My point was that you can manually label some functions, but to automatically
 do it for all functions is going to cause big stack space problems - think
 about recursive functions... or mutually recursive functions... 

Yes, of course.  So *my* point is that it would be really nice to
write small leaf functions like these with an implicit file/line
parameter that identified the caller site, in order to avoid
cluttering the code with them.

Okay, perhaps I'm not using the type system to its full extent, but I
think this is fairly common practice.  

An easy solution seems to be to use -cpp and add

   #define head (\(x:_)-x)

at the top of the relevant source files.  However, I'm not sure how to
make this work with the other difficult functions.  Another
alternative (basically emulating the GHC's behavior in the above case)
is

   #define head (\x - case x of {(x:_) - x; _ - error (head failed at 
++__FILE__++:++ show __LINE__)})

It seems difficult to generalize this, though.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] exceptions vs. Either

2004-08-04 Thread MR K P SCHUPKE
No, I don't think so.  I only want the bug to be reported   

I think preventing the bug using the type system if possible is a good
idea... something that should be encouraged!

and not a corner case that should be handled.

So if the list depends on user input is not the empty list a corner
case of the function on user input?

write small leaf functions like these with an implicit file/line

This is a good idea - If I have given the impression I am opposed to it 
then I have not expressed myself very well. I just think where this can
be avoided using the type system in the first place is an even better
idea. Design by contract is the way forward for large complex systems, 
and where that contract can be expressed using the type system is
a selling point for Haskell in such applications.

It seems difficult to generalize this, though.

Again for read you can use reads...

Sven Panne said:

reads is probably what you are looking for:

Prelude (reads :: ReadS Integer) 
[]
Prelude (reads :: ReadS Integer) a
[]
Prelude (reads :: ReadS Integer) 2
[(2,)]
Prelude (reads :: ReadS Integer) 123blah
[(123,blah)]


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


Re: [Haskell-cafe] exceptions vs. Either

2004-08-04 Thread Ketil Malde
David Roundy [EMAIL PROTECTED] writes:

 Here bug is a function that just calls error with a little prefix
 explaining that there is a bug in darcs, and would the user please report
 it.  Obviously, defining a head here would be just as easy,

Cool!  The basic trick is just to inline the actual function
defintions using CPP macros.  I've made macros for most of the
troublesome functions, but I can't get it to work for operators
(something like `(!!)` doesn't parse, it seems)  Any tricks?

Unless I'm overlooking something, I could have a file prelude.h
containing something like:

8--
import Prelude hiding (head,(!!),read)

#define head (\xs - case xs of { (x:_) - x ; _ - bug head __FILE__ __LINE__})
#define at (let {at (y:_) 0  = y; at (y:ys) n = at ys (n-1); at _ _ = bug at 
__FILE__ __LINE__} in \a x - at a x)
#define read (\s - case [ x | (x,t) - reads s, (,) - lex t] of { [x] - x ; _ 
- bug read __FILE__ __LINE__})
#define fromJust (\x - case x of Just a - a; Nothing - bug fromJust __FILE__ 
__LINE__)

bug c f l = error (Program error - illegal parameters to '++c++', file '++f++', 
line ++show l)
8--

and just #include prelude.h if/when I want better debugging.  No
expensive stack frames, no unwanted strictness, and no clutter.

Any comments?

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] exceptions vs. Either

2004-08-04 Thread Ketil Malde
Ketil Malde [EMAIL PROTECTED] writes:

 Unless I'm overlooking something

Which I of course did.

 #define at (let {at (y:_) 0  = y; at (y:ys) n = at ys (n-1); at _ _ = bug at 
 __FILE__ __LINE__} in \a x - at a x)

No prize for spotting the bug here.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] exceptions vs. Either

2004-08-04 Thread Ketil Malde
Ketil Malde [EMAIL PROTECTED] writes:

 import Prelude hiding (head,(!!),read)

 Any comments?

Here's one: I thought this would make it difficult to have other
imports of Prelude, hiding other pieces of it (e.g. catch, to avoid
ambiguities with Control.Exception.catch)

(Also, the definition of 'bug' hinders forces the #include to be after
any imports, not sure it's better to have a separate module for it,
which would then need to be on the module search path)

(I seem to be mainly following up to my own posts, so if somebody
asks, I'll take this to a quiet corner at the -cafe :-) 

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] exceptions vs. Either

2004-08-03 Thread Graham Klyne
Two observations:
1. When I recently modified the HaXml XML parser, this is one of the 
significant changes I made:  providing (alterantive) return values based on 
Either, so that input errors could be handled by the invoking function, 
without forcing it into the IO monad.  I guess that's a vote of agreement.

2. I like to distinguish between expected errors and unexpected 
errors.  Having been burned in the past by using exceptions (not FP), I 
try to use them only for conditions that are truly unexpected; i.e. 
_exceptional_.  Bad input, IMO, is something that is not unexpected, so I 
don't really like to handle that via exceptions.

#g
--
At 13:09 02/08/04 -0700, Evan LaForge wrote:
Exceptions are convenient in that you can rely on libraries throwing them
instead of prechecking for valid values yourself (for instance, why check
that the argument to Char.digitToInt is valid if digitToInt does so already),
and you don't have to modify a lot of function signatures.  Unfortunately, in
the face of lazy evaluation, they can get thrown in unexpected places.  Even
with Exception.evaluate, or code which is already explicitly sequenced in the
IO monad, like t - Exception.evaluate (map Char.digitToInt ['a'..'g']) an
exception will only be thrown when you inspect the last element of 't'.
(digitToInt confusingly accepts hex digits---shouldn't it be higitToInt
then?).
So it seems to me that if you are, say, checking input, the options are
to handle exceptions from the checking code but expect them to come from the
processing code, or decorate all checking code with Rights and Lefts.
Problems with the first option are that checking code could also trigger some
exceptions, and Prelude functions throw undescriptive errors like user
error or low level ones like refuted pattern match and catching them over
the entire program means you could stifle a lot of real errors. This implies
that you have to make specific exceptions and convert Prelude and library
exceptions into yours as low down as possible, which is cluttering but maybe
not as cluttering as Either.  Problems with the second option are many of the
problems that lead to us wanting exceptions in the first place.
Using Either seems much simpler and functional-friendly.  So then, in what
contexts are exceptions appropriate in haskell?
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] exceptions vs. Either

2004-08-03 Thread Ketil Malde
Graham Klyne [EMAIL PROTECTED] writes:

 2. I like to distinguish between expected errors and unexpected
 errors.  Having been burned in the past by using exceptions (not FP),
 I try to use them only for conditions that are truly unexpected;
 i.e. _exceptional_.  Bad input, IMO, is something that is not
 unexpected, so I don't really like to handle that via exceptions.

I agree, trying to handle exceptions caused by incorrect input is just
needless complication, the program should crash, and the calling
function should be fixed instead. 

Common errors that happen to me are:

   Prelude.head : empty list
   Prelude.read : no parse
andPrelude.(!!) : index too large
and so on.
   
Is there any easy way (TH?) to amend these to output the line number
of the offending caller?  It would be a great improvement to see
something like

Prelude.head : empty list in Foo.hs, line 4711

since programs generally contain many, many calls to functions like
these.  

-kzm 
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] exceptions vs. Either

2004-08-03 Thread Bjoern Knafla
Hi - I am just learning Haskell and am far away from exception handling 
intricacies. However I just recently read an article of Herb Sutter 
about exception handling in C++ with some rules when to use exception 
handling - and perhaps these rules might be applicable to Haskell too 
(article: When and How to Use Exceptions, Herb Sutter, C/C++ Users 
Journal August 2004, pp. 47 -- 51)?

Herb Sutter gave these rules :
An error is any failure that prevents a function from succeeding. Three 
main kind of errors:
- a condition that prevents the function from meeting a precondition of 
another function that must be called (so to say: the caller has to 
check for preconditions while the function called my use C/C++ asserts 
to assert the correctness of its preconditions)

- a condition that prevents a function from establishing one of its own 
postconditions (e.g. producing a (valid) return value)

- a condition that prevents the function from reestablishing an 
invariant that it is responsible to maintain (special kind of 
postcondition mainly found in object oriented code).


Any other condition is not an error and shouldn't be reported as one.
The code that could cause an error is responsible for detecting and 
reporting the error otherwise this is a programming mistake.


I am not sure if these rules apply to real functional programming but 
at least they seem to be useable. The point that the caller is 
responsible for checking the preconditions of functions it is calling 
is something I also found as a suggestion in using the object oriented 
language Eiffel.

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


Re: [Haskell-cafe] exceptions vs. Either

2004-08-03 Thread Marcin 'Qrczak' Kowalczyk
W licie z wto, 03-08-2004, godz. 13:05 +0200, Bjoern Knafla napisa:

 Herb Sutter gave these rules :
 
 An error is any failure that prevents a function from succeeding. Three 
 main kind of errors:
[...]

These kinds don't explain much. They don't give a clue which errors
to report by exceptions and which by return values, because they don't
distinguish the reasons for which a (pre|post)condition can't be
fulfilled. And I see no point in distinguishing potential errors on
this axis.

I divide exceptional situations into 4 groups:

1. Expected error: The result can't be computed from this data; the
   caller was not supposed to check this beforehand because it would
   duplicate work of the function, or there would be a race condition,
   or the design is simpler that way.

2. Program error: The given function was not supposed to be invoked
   in this way by other parts of the program (with these arguments,
   or with this external state, in this order wrt. other functions
   etc.).

3. Out of resource: The function is sorry that it was not able to
   produce the result due to limited memory or arithmetic precision
   or similar resources. Not yet supported is also in this group.

4. Impossible error: The function thought this couldn't happen, it must
   have a bug. This is like 2 in that there is a bug somewhere, but like
   1 in that the calling code is probably fine.

I/O errors can be expected errors or out of resource conditions,
depending on whether they were caused by bad input or by external
failure.

Group 1 should be reported in Haskell by a distinguished result (Maybe,
Either, custom type) or by an exception passed in a suitable monad
(well, Maybe is a monad; this could be even the IO monad).

Other groups are handled in a similar way. In Haskell they can be
reported by a bottom, e.g. 'error' function. It makes sense to catch
them on a toplevel of the program or a large unit, and it's good that
GHC provides a way to catch them. There may be other actions possible
than just aborting the program: report the problem to the user, abort
just the given operation, but try to continue other work; save user data
before aborting; log the error or report it in an appropriate channel,
e.g. output a HTML page in case of a CGI program.

Sometimes the same function makes sense in two variants: one which
reports an expected error, and another which treats it as a program
error. Example: lookup in a dictionary.

Sometimes the qualification of an error changes while it is propagated.
I haven't thought about all cases, but for example program errors become
impossible errors if the caller thought that the arguments it passed
were good, and expected errors become program errors if the caller's
caller was not supposed to give arguments which cause such problems.

The most important distinction is between expected errors, whose way of
reporting should be visible in the interface and which should be checked
for in the calling code, and program errors, which should be
automatically propagated and reported near the toplevel.

-- 
   __( Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/

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


Re: [Haskell-cafe] exceptions vs. Either

2004-08-03 Thread Keith Wansbrough
 Exceptions should only really be used for unpredictcable events, I find
 that the defintion of functions like head is lacking rigor... I would 
 prefer to see:
 
 head :: [a] - Maybe a
 head (a0:_) = Just a0
 head _ = Nothing

In principle, yes, but in practice, that would be silly.  You use
head just when you know for sure that the list is non-empty; if it
is not, it's a program error for head, and an impossible error for
the caller.  Consider:

f (head xs)  -- old style

vs

f (case head xs of Some x - x; None - error whoops)  -- Schupke style

It should be clear that this function would never be used - if head
had this signature, programmers would just write

f (case xs of (x:_) - x; [] - error whoops)  -- direct style

--KW 8-)

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


Re: [Haskell-cafe] exceptions vs. Either

2004-08-03 Thread MR K P SCHUPKE
f (case xs of (x:_) - x; [] - error whoops)  -- direct style

Yup, this is how I do it... I never use head!

I like to pass failures back up to the level where some kind of sensible 
error message can be generated. In your example the error is no
better than with 'head' - the point is a Nothing can be 'caught' 
outside of an IO monad. 

I would suggest using the type system as I said earlier so:

toNonEmptyList :: [a] - Maybe (NonEmpty a)
toNonEmptyList (a0:_) = Just (NonEmpty a)
toNonEmptyList _ = Nothing

Then redefine head:

head :: NonEmpty a - a
head (NonEmpty (a0:_)) = a0


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


Re: [Haskell-cafe] exceptions vs. Either

2004-08-03 Thread Alastair Reid

Prelude.head : empty list
Prelude.read : no parse
 andPrelude.(!!) : index too large
 and so on.

 Is there any easy way (TH?) to amend these to output the line number
 of the offending caller?

In a program of any size, I usually avoid using these functions and instead 
define functions like:

  --| 1st arg is error message for empty lists 
  head' :: Doc - [a] - a

  --| 1st arg is description of kind of thing in list
  --  Reports error if length of list /= 1
  unique :: Doc - [a] - a

etc.

Another approach is to use a function:

  inContext :: String - a - a

(implemented using mapException) like this:

  inContext evaluating expression (eval env e)

to transform an exception of the form:

   error Division by zero

into

   error Division by zero while evaluating expression

Since the inContext function is rather like ghc's profiling function 'scc', it 
would be nice if ghc had a command-line flag to insert a call to inContext 
everywhere that it inserts a call to scc when you use -prof-all.  (Of course, 
you'd probably take a big stack-space hit from doing so since the chain of 
calls to inContext is equivalent to the stack you would expect if using call 
by value without tail call optimization.

--
Alastair Reid

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


Re: [Haskell-cafe] exceptions vs. Either

2004-08-03 Thread Evan LaForge

 A lot of programming errors come from failure to correctly validate.

This was actually nicely illustrated in my program: I assumed that digitToInt
accepted '0'..'9' and wanted to rely on it throwing.  After puzzling over
out of range errors (other functions expected digitToInt to be in the 0..9
range) I figured it out and inserted an explicit check.  Unfortunately there
is no static check for pre and post conditions, unless you manually add them
to the type system, as you suggest.  But that's work ;)

Wrting a monad bind for Either that returns Left immediately and binds Right
would make Either style error propagation easier.  But it seems like it would
over sequence:

do a' - checka a
   b' - checkb b
   return $ process a' b'

is rather messier looking than 'process (checka a) (checkb b)'.  It doesn't
really matter what order 'a' and 'b' are checked, what I really want is the
monad-style magic plumbing.  I suppose I should just wrap 'process' in a
liftM2 and stop worrying about it.

 Of course you must make sure you don't write more than
 one constructor function for ValidInt. This suggests a

Can't you do this at the module level by exporting the ValidInt type, but not
the constructor?  Of course, then you have to stick it in its own module, and
simple range validation is getting even more heavyweight...



In response to the mysterious head exceptions thread, isn't there a way to
compile with profiling and then get the rts to give a traceback on exception?
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] exceptions vs. Either

2004-08-03 Thread Graham Klyne
At 15:28 03/08/04 +0100, MR K P SCHUPKE wrote:
f (case xs of (x:_) - x; [] - error whoops)  -- direct style
Yup, this is how I do it... I never use head!
As a general principle, this bothers me.
In the longer term (i.e. if and when large-scale production Haskell systems 
become common), and as a matter of principle, I think it's better to use a 
prelude (or standard) function when one will do the job, because a 
widely-used industrial strength compiler might well have special 
knowledge of these and be able to apply special optimizations (as, e.g., 
some C/C++ compilers do for standard library functions like memcpy).

As for head, I think it's fine that it throws an error because it is 
specified to be defined for only non-empty lists.  (I remain silent on 
whether the prelude should contain a head-like function that returns a 
value for empty lists.)

#g

Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] exceptions vs. Either

2004-08-03 Thread Ketil Malde
MR K P SCHUPKE [EMAIL PROTECTED] writes:

 head :: [a] - Maybe a
 head (a0:_) = Just a0
 head _ = Nothing

Argh, no!  Violating the precondition of head is a bug in the caller,
I want it to crash, but I also want to know where.  Wrapping it up in
Maybe (or any other error propagation) is not a solution. 

I don't want to write a lot of unwrapping code in all the callers,
just to get a trackable error message in the (few) cases where I'm
using the function incorrectly.

Neither do I want to write

(\x - if null x then error (__FILE__:__LINE__) else head x)

everywhere instead of head, nor pollute my code with error tracking, but
otherwise meaningless strings. (Which is what I generally do when I
get this kind of anonymous error.  if null x then error foo else
head x.

A mechanism for a function to report the caller site would obliviate
the need for all this ugliness.

-kzm

Hmm...if I run it through CPP and 
  #define HEAD (\x - if null x then error (__FILE__:__LINE__) else head x)
is the __LINE__ resolved at the place of declaration or at the place of usage?
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] exceptions vs. Either

2004-08-03 Thread Fergus Henderson
On 03-Aug-2004, Evan LaForge [EMAIL PROTECTED] wrote:
 
 In response to the mysterious head exceptions thread, isn't there a way to
 compile with profiling and then get the rts to give a traceback on exception?

There is, but it doesn't really work properly, due to
- lazy evaluation
- tail call optimization
- lack of line numbers in the traceback

-- 
Fergus J. Henderson |  I have always known that the pursuit
Galois Connections, Inc.|  of excellence is a lethal habit
Phone: +1 503 626 6616  | -- the last words of T. S. Garp.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] exceptions vs. Either

2004-08-03 Thread David Menendez
David Menendez writes:

 MR K P SCHUPKE writes:
 
  I would suggest using the type system as I said earlier so:
  
  toNonEmptyList :: [a] - Maybe (NonEmpty a)
  toNonEmptyList (a0:_) = Just (NonEmpty a)
  toNonEmptyList _ = Nothing
  
  Then redefine head:
  
  head :: NonEmpty a - a
  head (NonEmpty (a0:_)) = a0
 
 Oleg described a similar technique a few months ago.
 
 From http://haskell.org/pipermail/haskell/2004-June/014271.html:
 
 | newtype NonEmpty a = NonEmpty [a] -- the NonEmpty constructor
should
 | -- be hidden (not exported from its module)
 |
 | head' (NonEmpty a) = head a -- no error can occur! Can use unsafe
 version
 | tail' (NonEmpty a) = tail a -- no error can occur! Can use unsafe
 version
 |
 | -- trusted function: the only one that can use NonEmpty
constructor.
 | fork_list_len f g x = if null x then f else g (NonEmpty x)
 |
 | revers x  = revers' x []
 |  where
 |revers' x accum = fork_list_len accum (g accum) x
 |g accum x = revers' (tail' x) ((head' x):accum)
 
 We have these equivalences:
 
 toNonEmptyList== fork_list_len Nothing Just
 fork_list_len d f == maybe d f . toNonEmptyList
 
 I think defining 'toNonEmptyList' in terms of 'fork_list_len' is
 cleaner, but that's just my personal taste. (As it happens, I ended up
 defining a very similar function 'cons' in my recursion module[1]).
 
 [1]
 http://www.eyrie.org/~zednenem/2004/hsce/Control.Recursion.html#v%
 3Acons
-- 
David Menendez [EMAIL PROTECTED] http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe