Re: Debugging partial functions by the rules

Donald Bruce Stewart wrote:
So all this talk of locating head [] and fromJust failures got me thinking:
Couldn't we just use rewrite rules to rewrite *transparently* all uses of fromJust to safeFromJust, tagging the call site with a location?
I'm sorry for shifting the topic: I'm wondering if, rather than trying to make an error message more informative, we ought to make sure that no error will ever arise? The fromJust and `head of empty list' errors are totally equivalent to the dereferencing of zero pointer in C++ or NullPointerException in Java. It pains me to see that exactly the same problem arises in Haskell -- keeping in mind that already in C++ and Java one may exterminate these errors given right encapsulations. Languages like Cyclone or Cw use the type system to eliminate such errors. Surely Haskell can do something about this? This topic has been discussed at length on this list. It seems that the discussion came to the conclusion that eliminating head of the empty list error is possible and quite easy in Haskell. http://www.haskell.org/pipermail/haskell-cafe/2006-September/017915.html http://www.haskell.org/pipermail/haskell-cafe/2006-September/017937.html As to fromJust: would the world come to an end if this function is just not available? Oftentimes when we get the value of the type |Maybe a|, the algorithm prescribes the actions for the case if this value is Nothing. Thus the function `maybe', the deconstructor, seems to be called for. And if we are dead sure that the |Maybe a| value is definitely |Just smth| and we need to extract this |smth|, we can always write maybe (assert False undefined) id value I like how this phrase stands out in the code, to remind me to double-check my certainty about the value (and perhaps, to re-factor the code). Similarly for empty lists: it is often algorithmically significant as it is the base case for our recursion/induction. Thus, we have to make the null check according to the algorithm anyway. The type system can carry the result of such a test, so we don't have to repeat it. The functions head and tail should operate on the newtype NonemptyList -- in which case they are total. Other list functions may remain as they are, because we can always `forget' the NonemptyList tag. The run-time overhead is zero, the notational overhead is not much: writing a few extra `fromNonemptyList'. Compare with writing `fromIntegral', especially in the FFI-related code. The Haskell type system can do far more complex things, for example, solve the pervasive SQL injections and cross-site scripting problems: http://blog.moertel.com/articles/2006/10/18/a-type-based-solution-to-the-str... (This URL appeared on one of the recent Haskell Weekly News, btw). Surely we can do something about a far simpler problem of head [] and fromJust? We may have to adjust our coding styles a little. The adjustment doesn't appear extensive; besides, isn't the whole point of programming in Haskell is to think differently?

oleg:
Donald Bruce Stewart wrote:
So all this talk of locating head [] and fromJust failures got me thinking:
Couldn't we just use rewrite rules to rewrite *transparently* all uses of fromJust to safeFromJust, tagging the call site with a location?
I'm sorry for shifting the topic: I'm wondering if, rather than trying to make an error message more informative, we ought to make sure that no error will ever arise?
The fromJust and `head of empty list' errors are totally equivalent to the dereferencing of zero pointer in C++ or NullPointerException in Java. It pains me to see that exactly the same problem arises in Haskell -- keeping in mind that already in C++ and Java one may exterminate these errors given right encapsulations. Languages like Cyclone or Cw use the type system to eliminate such errors. Surely Haskell can do something about this?
Yes, these techniques are fairly well known now, and hopefully some of the more experienced Haskellers are using them (I certainly use the non-empty list tricks). Any anyone with more than 6 months Haskell knows to avoid fromJust. The problem I see is that head/fromJust errors are usually caused by *beginner* Haskellers, who don't know the techniques for statically avoiding them. One solution would be to deprecate fromJust (we recently decided not to add fromLeft/Right for the same reasons). Having a compiler warning is a good way to encourage good behaviour :) But it seems hardly likely that head will be deprecated any time soon, and we have no support for checked non-empty lists in the base libraries. So how do we help out the beginners, other than warning about fromJust, and providing a useful error message as we can, for when they just go ahead and use head anyway? -- Don

| > The fromJust and `head of empty list' errors are totally equivalent to | > the dereferencing of zero pointer in C++ or NullPointerException in | > Java. It pains me to see that exactly the same problem arises in | > Haskell -- keeping in mind that already in C++ and Java one may | > exterminate these errors given right encapsulations. Languages like | > Cyclone or Cw use the type system to eliminate such errors. Surely | > Haskell can do something about this? | | Yes, these techniques are fairly well known now, and hopefully some of | the more experienced Haskellers are using them (I certainly use the | non-empty list tricks). Any anyone with more than 6 months Haskell knows | to avoid fromJust. | | The problem I see is that head/fromJust errors are usually caused by | *beginner* Haskellers, who don't know the techniques for statically | avoiding them. I don't agree. My programs have invariants that I can't always express in a way that the type system can understand. E.g. I know that a variable is in scope, so searching for it in an environment can't fail: head [ v | (n,v) <- env, n==target ] (Maybe if I had an Oleg implant I could express all this in the type system -- but I don't.) But yes, we should have more sophisticated techniques to express and check these invariants. With Dana Xu I'm working on this very thing (see her Haskell Workshop paper http://www.cl.cam.ac.uk/~nx200/research/escH-hw.ps); and Neil Mitchell is doing complementary work at York. So I think there is reason to be hopeful. Simon

On Wed, Nov 15, 2006 at 09:04:01AM +0000, Simon Peyton-Jones wrote:
I don't agree. My programs have invariants that I can't always express in a way that the type system can understand. E.g. I know that a variable is in scope, so searching for it in an environment can't fail: head [ v | (n,v) <- env, n==target ] (Maybe if I had an Oleg implant I could express all this in the type system -- but I don't.)
Yes, that is sometimes true (though many of the uses of fromJust I see could be easily avoided). The problem is an imbalance of costs. It's so easy to write these things, to the point of discouraging alternatives, but the costs come in debugging and reading. Every time I read code containing these functions, I have to perform a non-local analysis to verify the invariant, or even to determine the invariant. I don't think it's unreasonable to ask the programmer to give some justification, in something like (using Neil's library): headNote "The variable is in scope" [...] That would be extra tagging for the static analysis techniques too. Of course there'd be nothing to stop someone defining head = headNote "I'm all right, Jack"

Simon Peyton-Jones
| The problem I see is that head/fromJust errors are usually |caused by *beginner* Haskellers, who don't know the |techniques for statically avoiding them.
I don't agree. My programs have invariants that I can't always express in a way that the type system can understand. E.g. I know that a variable is in scope, so searching for it in an environment can't fail: head [ v | (n,v) <- env, n==target ] (Maybe if I had an Oleg implant I could express all this in the type system -- but I don't.)
But instead of “blah (head [ v | (n,v) <- env, n==target ]) blah”, you could write blah the_v_in_scope blah where (the_v_in_scope:_) = [ v | (n,v) <- env, n==target ] and get a source-code located error message, couldn't you? It's not very high tech, but it's what you would write if head didn't exist, and it doesn't seem /that/ great an imposition. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

Hi Haskell is great for equational reasoning.
blah the_v_in_scope blah where (the_v_in_scope:_) = [ v | (n,v) <- env, n==target ]
This piece of code isn't. If you used head then you could trivially inline the_v_in_scope, this way is a lot harder. You might spot a pointfree pattern and lift it up. You might move code around more freely. Lots of patterns like this breaks the equational reasoning in the style that most people are used to.
and it doesn't seem /that/ great an imposition.
I disagree, this is a massive imposition, and requires lots of refactoring, and is just a little bit ugly. What to go in a where should be the programmers decision, not the decision based on which hoops one has to hop through to write a debuggable Haskell program. Thanks Neil

"Neil Mitchell"
Hi
Haskell is great for equational reasoning.
blah the_v_in_scope blah where (the_v_in_scope:_) = [ v | (n,v) <- env, n==target ]
This piece of code isn't.
Strange. It's semantically the same, isn't it? Indeed, the definition of head gets you to it.
If you used head then you could trivially inline the_v_in_scope, this way is a lot harder.
I don't follow that at all. I don't do inlining, the compiler does. Or are you talking about the inlining that was originally there and my version explicitly removed?
You might spot a pointfree pattern and lift it up. You might move code around more freely. Lots of patterns like this breaks the equational reasoning in the style that most people are used to.
To convince me of that, you'd have to convince me that (head []) doesn't break the equational reasoning.
and it doesn't seem /that/ great an imposition.
I disagree, this is a massive imposition, and requires lots of refactoring,
"lots" is in the eye of the beholder. You only have to do this where you would have used head -- and if you can already /prove/ that head won't fail, there's no reason to replace it. So it's only necessary in cases where the proof is absent.
and is just a little bit ugly.
Sure, I don't dispute that. I was merely suggesting that one can already do this for the uncertain cases, rather than have to invoke a whole other set of new machinery just to get a line number in the error message. Your headNote is a good approach, but it strikes me that it's a bit redundant. Instead of “headNote "foo"” just use “headDef (error "foo")”. It's a wee bit longer, but having the “error” out there in the open seems more honest somehow, and there would be fewer function names to remember. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

On Nov 15, 2006, at 9:48 AM, Jón Fairbairn wrote:
Simon Peyton-Jones
writes: | The problem I see is that head/fromJust errors are usually |caused by *beginner* Haskellers, who don't know the |techniques for statically avoiding them.
I don't agree. My programs have invariants that I can't always express in a way that the type system can understand. E.g. I know that a variable is in scope, so searching for it in an environment can't fail: head [ v | (n,v) <- env, n==target ] (Maybe if I had an Oleg implant I could express all this in the type system -- but I don't.)
But instead of “blah (head [ v | (n,v) <- env, n==target ]) blah”, you could write
blah the_v_in_scope blah where (the_v_in_scope:_) = [ v | (n,v) <- env, n==target ]
and get a source-code located error message, couldn't you? It's not very high tech, but it's what you would write if head didn't exist, and it doesn't seem /that/ great an imposition.
Or how about.... ?? lookupVarible target env = case [ v | (n,v) <- env, n==target ] of (x:_) -> x _ -> assert False $ "BUG: Unexpected variable out of scope "++ (show target)++" in environment "++(show env) ... lookupVariable target env .... It seems to me that every possible use of a partial function has some (possibly imagined) program invariant that prevents it from failing. Otherwise it is downright wrong. 'head', 'fromJust' and friends don't do anything to put that invariant in the program text. Custom functions like the above 1) give you a great opportunity to add a meaningful assertion AND document the program invariant 2) attach some semantic meaning to the operation by naming it 3) make you think about what you're doing and help you avoid writing bugs in the first place 4) give you nice hooks for replacing your data- structure with a better one later, should it be necessary 5) encourage you to break down larger functions into smaller ones. Big win if you ask me. The frequent use of partial functions from the Prelude counters all of these advantages, and I avoid them as much as possible.
-- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk
Rob Dockins Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG

Robert Dockins
On Nov 15, 2006, at 9:48 AM, Jón Fairbairn wrote:
But instead of “blah (head [ v | (n,v) <- env, n==target ]) blah”, you could write
blah the_v_in_scope blah where (the_v_in_scope:_) = [ v | (n,v) <- env, n==target ]
Or how about.... ??
lookupVarible target env = case [ v | (n,v) <- env, n==target ] of (x:_) -> x _ -> assert False $ "BUG: Unexpected variable out of scope "++ (show target)++" in environment "++(show env)
... lookupVariable target env ....
It seems to me that every possible use of a partial function has some (possibly imagined) program invariant that prevents it from failing. Otherwise it is downright wrong. 'head', 'fromJust' and friends don't do anything to put that invariant in the program text.
Hear hear. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

Robert Dockins wrote:
Or how about.... ??
lookupVarible target env = case [ v | (n,v) <- env, n==target ] of (x:_) -> x _ -> assert False $ "BUG: Unexpected variable out of scope "++(show target)++" in environment "++(show env)
Other have pointed out that, in the CURRENT Haskell semantics, the above is quite difficult to reason about. Note that the whole point of Wolfram Kahl's Pattern Matching Calculus is to restore equational reasoning to pattern-matches. http://www.cas.mcmaster.ca/~kahl/PMC/ Jacques

Hi
Yes, these techniques are fairly well known now, and hopefully some of the more experienced Haskellers are using them (I certainly use the non-empty list tricks). Any anyone with more than 6 months Haskell knows to avoid fromJust.
I'm not, I use fromJust all the time. Ditto for head, init, maximum, foldr1...
One solution would be to deprecate fromJust (we recently decided not to add fromLeft/Right for the same reasons). Having a compiler warning is a good way to encourage good behaviour :)
We didn't decide not to add fromLeft/fromRight, Russell decided to defer it to a later patch. I am still very interested in them being put in! There seem to be two sides forming to this issue - use partial functions or don't. I don't see why we should restrict the functions available to the partial people, when the unpartial people can choose not to use them. Thanks Neil

Should Haskell also provide unrestricted side effects, setjmp/ longjmp, missile launching functions, etc? After all, people who don't want to use them can just avoid them. :) On Nov 15, 2006, at 05:07 , Neil Mitchell wrote:
Hi
Yes, these techniques are fairly well known now, and hopefully some of the more experienced Haskellers are using them (I certainly use the non-empty list tricks). Any anyone with more than 6 months Haskell knows to avoid fromJust.
I'm not, I use fromJust all the time. Ditto for head, init, maximum, foldr1...
One solution would be to deprecate fromJust (we recently decided not to add fromLeft/Right for the same reasons). Having a compiler warning is a good way to encourage good behaviour :)
We didn't decide not to add fromLeft/fromRight, Russell decided to defer it to a later patch. I am still very interested in them being put in!
There seem to be two sides forming to this issue - use partial functions or don't. I don't see why we should restrict the functions available to the partial people, when the unpartial people can choose not to use them.
Thanks
Neil _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi
Should Haskell also provide unrestricted side effects, setjmp/ longjmp, missile launching functions, etc? After all, people who don't want to use them can just avoid them. :)
Fair point. But if you eliminate incomplete cases, and the error function, you'd probably need to increase the power of the type checker by introducing dependant types. It's a good research avenue, and an interesting approach, but its not what Haskell is to me (but it might be to others).
Every time I read code containing these functions, I have to perform a non-local analysis to verify the invariant, or even to determine the invariant.
If you use the Programmatica annotations, the ESC/Haskell annotations or Catch then you can have these assertions checked for you, and in the case of Catch even infered for you. Admitedly ESC/Haskell and Catch aren't ready for use yet, but they will be soon! Thanks Neil

Hello Lennart, Wednesday, November 15, 2006, 3:37:34 PM, you wrote:
Should Haskell also provide unrestricted side effects, setjmp/ longjmp, missile launching functions, etc? After all, people who don't want to use them can just avoid them. :)
these are documented in "tackling the awkward squad, or that remains from our beauty Haskell after uncheckedMissileLauch" :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Lennart Augustsson
Should Haskell also provide unrestricted side effects, setjmp/ longjmp, missile launching functions, etc? After all, people who don't want to use them can just avoid them. :)
Yes. It is indeed a common problem that programs have unintended behavior, and partial functions are only the tip of the iceberg. We can keep patching things up. For instance, 'head' can be made to never fail simply by requiring all lists to be infinite. Similarly, fromJust can be fixed by having 'data Maybe a = Just a', and doing away with 'Nothing', which is hardly useful for anything anyway. But this is only superficial patchwork that glosses over the deeper problem. I therefore propose that all functions should either be of type '() -> ()', or non-terminating. That should avoid most error messages, I think, and make it very easy to avoid any unintended consequences - and the programmer is relieved of the burden of actively avoiding dangerous stuff. Is it possible to implement this for Haskell'? -k -- If I haven't seen further, it is by standing in the footprints of giants

Donald Bruce Stewart wrote:
So how do we help out the beginners, other than warning about fromJust, and providing a useful error message as we can, for when they just go ahead and use head anyway?
Kill head and tail right now and provide a safe equivalent? Either uncons :: [a] -> Maybe (a,[a]) which is to be used in conjunction with 'maybe' (or with fmap/first/second/unfoldr) or list :: r -> (a -> [a] -> r) -> [a] -> r in analogy with 'maybe' and 'either'. Or combine it with 'foldr' to form the paramorphism (if I got the terminology right). Or even better, don't mention the existence of uncons and encourage people to write list consumers in terms of 'destroy'. -Udo -- Sturgeon's Law: Ninety percent of everything is crud. (Sturgeon was an optimist.)

It must be stressed that the advocated technique for avoiding partial function errors requires *NO* research advances, *NO* dependent types, *NO* annotations, and *NO* tools. Everything is possible in Haskell as it is -- actually, even in Haskell98. As a matter of fact, exactly the same approach applies to OCaml (and even to any language with a half-decent type system, including Java and C++). The only required advancement is in our thinking and programming style. First, regarding fromJust: to quote Nancy Reagan, let's `Just say NO'. Let us assume that `fromJust' just does not exist. That does not reduce any expressiveness, as `maybe' always suffices. The latter function causes us to think of the boundary case, when the value is Nothing. And if we are absolutely positive that the value is (Just x), we can always write maybe (assert False undefined) id v This is *exactly* equivalent to `fromJust v', only with a better error message. So, no `safeFromJust' is ever necessary! The expression above takes longer to type than `fromJust v' -- and I consider that a feature. Whenever I am telling the compiler that I know better, I'd rather had to type it in more words -- so I could think meanwhile if I indeed know better. Also, such phrases should stand out in the code. I'd be quite happy seeing fromJust removed from the standard libraries, or at least tagged `deprecated' or with the stigma attached that is rightfully accorded to unsafePerformIO. Regarding head and tail. Here's the 0th approximation of the advocated approach:
{-# Haskell98! #-} -- Safe list functions
module NList (FullList, fromFL, indeedFL, decon, head, tail, Listable (..) ) where
import Prelude hiding (head, tail)
newtype FullList a = FullList [a] -- data constructor is not exported!
fromFL (FullList x) = x -- Injection into general lists
-- The following is an analogue of `maybe' indeedFL :: [a] -> w -> (FullList a -> w) -> w indeedFL x on_empty on_full | null x = on_empty | otherwise = on_full $ FullList x
-- A possible alternative, with an extra Maybe tagging -- indeedFL :: [a] -> Maybe (FullList a)
-- A more direct analogue of `maybe', for lists decon :: [a] -> w -> (a -> [a] -> w) -> w decon [] on_empty on_full = on_empty decon (h:t) on_empty on_full = on_full h t
-- The following are _total_ functions -- They are guaranteed to be safe, and so we could have used -- unsafeHead# and unsafeTail# if GHC provides though...
head :: FullList a -> a head (FullList (x:_)) = x
tail :: FullList a -> [a] tail (FullList (_:x)) = x
-- Mapping over a non-empty list gives a non-empty list instance Functor FullList where fmap f (FullList x) = FullList $ map f x
-- Adding something to a general list surely gives a non-empty list infixr 5 !:
class Listable l where (!:) :: a -> l a -> FullList a
instance Listable [] where (!:) h t = FullList (h:t)
instance Listable FullList where (!:) h (FullList t) = FullList (h:t)
Now we can write
import NList import Prelude hiding (head, tail) safe_reverse l = loop l [] where loop l accum = indeedFL l accum $ (\l -> loop (tail l) (head l : accum))
test1 = safe_reverse [1,2,3]
As we can see, the null test is algorithmic. After we've done it, head and tail no longer need to check for null list. Those head and tail functions are total. Thus we achieve both safety and performance. We can also write
-- Again, we are statically assured of no head [] error! test2 = head $ 1 !: 2 !: 3 !: []
This would look better had `[1,2,3]' been a rebindable syntax similar to `do'. I should point to http://pobox.com/~oleg/ftp/Computation/lightweight-dependent-typing.html for further, more complex examples. We can also use the approach to ensure various control properties, e.g., the yield property: a thread may not invoke `yield' while holding a lock. We can assure this property both for recursive and non-recursive locks. If there is a surprise in this, it is in the triviality of approach. One can't help but wonder why don't we program in this style. Simon Peyton-Jones wrote:
My programs have invariants that I can't always express in a way that the type system can understand. E.g. I know that a variable is in scope, so searching for it in an environment can't fail: head [ v | (n,v) <- env, n==target ]
In the 0th approximation, the above line will read as indeedFL [ v | (n,v) <- env, n==target ] (assert False undefined) head Alternatively, one may write case [ v | (n,v) <- env, n==target ] of (h:_) -> h with the compiler issuing a warning over the incomplete match and prompting us to consider the empty list case (writing assert False undefined if we are sure it can't happen). I have a hunch we can do better and really express our knowledge that [ v | (n,v) <- env, n==target ] can't be empty. We don't ask the type system to decide this for us; we only ask the type system to carry along our decisions (and complain if we seem to be contradicting ourselves). To test if we indeed can do better, I'd like to see the above line in a larger context (with more code). Incidentally, this is an open invitation. If someone has a (complex) example with head/tail/readArray etc. partial functions and is interested in possibly improving static assurances of that code, Chung-chieh Shan and I would be quite interested in looking into it. The code can be either posted here or mailed to us privately.

On Wed, 15 Nov 2006 oleg@pobox.com wrote:
... I'd be quite happy seeing fromJust removed from the standard libraries, or at least tagged `deprecated' or with the stigma attached that is rightfully accorded to unsafePerformIO.
However, unsafe* functions are still recommended by Haskell users to newbies, as if these functions belong to the normal usage. Maybe one should add a string parameter to these functions, which must be bound to "I confirm that I know that this function should be used only if really necessary and that I checked properly that safe alternatives do not exist.". The unsafe* function must be undefined, if the confirmation argument does not match. :-)

On 16/11/06, oleg@pobox.com
And if we are absolutely positive that the value is (Just x), we can always write maybe (assert False undefined) id v
It should be pointed out that Data.Maybe does export a less well-known function, fromMaybe: fromMaybe z = maybe z id This can be used to make the 'maybe X id' case a bit tidier (although technically it's not a save on characters). -- -David House, dmhouse@gmail.com

dmhouse:
On 16/11/06, oleg@pobox.com
wrote: And if we are absolutely positive that the value is (Just x), we can always write maybe (assert False undefined) id v
It should be pointed out that Data.Maybe does export a less well-known function, fromMaybe:
fromMaybe z = maybe z id
This can be used to make the 'maybe X id' case a bit tidier (although technically it's not a save on characters).
How controversial would a proposal to {-# DEPRECATE fromJust #-} be, in favour of: Just _ = x -- which will give you the precise line number maybe (assert False) maybe id fromMaybe It seems to me this is one cause of mysterious newbie errors we could easily discourage, with little harm. -- Don

dons:
dmhouse:
On 16/11/06, oleg@pobox.com
wrote: And if we are absolutely positive that the value is (Just x), we can always write maybe (assert False undefined) id v
It should be pointed out that Data.Maybe does export a less well-known function, fromMaybe:
fromMaybe z = maybe z id
This can be used to make the 'maybe X id' case a bit tidier (although technically it's not a save on characters).
How controversial would a proposal to {-# DEPRECATE fromJust #-} be, in favour of:
Just _ = x -- which will give you the precise line number
maybe (assert False)
maybe id
fromMaybe
It seems to me this is one cause of mysterious newbie errors we could easily discourage, with little harm.
Btw, I'm not seriously suggesting removing it ;) It could be discouraged ever so slightly in the haddocks though. I'd encourage those worried about fromJust not to use it though, and perhaps try: import Debug.Trace.Location fromMaybe (failure assert "my just was nothing") (Nothing :: Maybe ()) $ ./a.out *** Exception: A.hs:5:34-39: my just was nothing instead of: fromJust (Nothing :: Maybe ()) $ ./a.out *** Exception: Maybe.fromJust: Nothing While Dana and Neil work on more tools for spotting these for us. -- Don

As long as we are doing this, perhaps we should also discourage the use of (head list)? -Alex- ______________________________________________________________ S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com On Fri, 17 Nov 2006, Donald Bruce Stewart wrote:
dons:
dmhouse:
On 16/11/06, oleg@pobox.com
wrote: And if we are absolutely positive that the value is (Just x), we can always write maybe (assert False undefined) id v
It should be pointed out that Data.Maybe does export a less well-known function, fromMaybe:
fromMaybe z = maybe z id
This can be used to make the 'maybe X id' case a bit tidier (although technically it's not a save on characters).
How controversial would a proposal to {-# DEPRECATE fromJust #-} be, in favour of:
Just _ = x -- which will give you the precise line number
maybe (assert False)
maybe id
fromMaybe
It seems to me this is one cause of mysterious newbie errors we could easily discourage, with little harm.
Btw, I'm not seriously suggesting removing it ;) It could be discouraged ever so slightly in the haddocks though.
I'd encourage those worried about fromJust not to use it though, and perhaps try:
import Debug.Trace.Location fromMaybe (failure assert "my just was nothing") (Nothing :: Maybe ())
$ ./a.out *** Exception: A.hs:5:34-39: my just was nothing
instead of:
fromJust (Nothing :: Maybe ())
$ ./a.out *** Exception: Maybe.fromJust: Nothing
While Dana and Neil work on more tools for spotting these for us.
-- Don _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi
How controversial would a proposal to {-# DEPRECATE fromJust #-} be, in favour of:
Just _ = x -- which will give you the precise line number
It seems to me this is one cause of mysterious newbie errors we could easily discourage, with little harm.
Btw, I'm not seriously suggesting removing it ;) It could be discouraged ever so slightly in the haddocks though.
I strongly disagree. If we are removing things that confuse newbies why not start with higher rank types, MPTC's and GADT's ;) fromJust is simple, useful and clear. What you mean is that implementations aren't very good at debugging this. It seems unfair to blame partial functions for the lack of a debugger. If a call stack was automatically output every time a fromJust failed would this even be something people complained about? Thanks Neil

On Fri, 17 Nov 2006, Neil Mitchell wrote:
Hi
How controversial would a proposal to {-# DEPRECATE fromJust #-} be, in favour of:
Just _ = x -- which will give you the precise line number
It seems to me this is one cause of mysterious newbie errors we could easily discourage, with little harm.
Btw, I'm not seriously suggesting removing it ;) It could be discouraged ever so slightly in the haddocks though.
I strongly disagree. If we are removing things that confuse newbies why not start with higher rank types, MPTC's and GADT's ;)
fromJust is simple, useful and clear. What you mean is that implementations aren't very good at debugging this. It seems unfair to blame partial functions for the lack of a debugger. If a call stack was automatically output every time a fromJust failed would this even be something people complained about?
It seems to me like the discussion about static typesafety vs. no or weak typesafety. (Which still exists with respect to several Haskell libraries.) Of course, all type errors can be catched also by a debugger. So was the decision of making Haskell statically type-safe only made in order to be freed of writing a debugger? Certainly not, because type checks can catch errors early and precisely, that is, better than any debugger. That's also true for DEPRECATE fromJust. Give the user a hint early, that his decision of using fromJust is shortsighted and is possibly due to unfortunate program design.

Exactly! On Nov 17, 2006, at 07:30 , Henning Thielemann wrote:
It seems to me like the discussion about static typesafety vs. no or weak typesafety. (Which still exists with respect to several Haskell libraries.) Of course, all type errors can be catched also by a debugger. So was the decision of making Haskell statically type-safe only made in order to be freed of writing a debugger? Certainly not, because type checks can catch errors early and precisely, that is, better than any debugger. That's also true for DEPRECATE fromJust. Give the user a hint early, that his decision of using fromJust is shortsighted and is possibly due to unfortunate program design. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Fri, Nov 17, 2006 at 11:37:12AM +0000, Neil Mitchell wrote:
fromJust is simple, useful and clear. What you mean is that implementations aren't very good at debugging this. It seems unfair to blame partial functions for the lack of a debugger. If a call stack was automatically output every time a fromJust failed would this even be something people complained about?
indeed. jhc debugs this quite fine. when you use it the wrong way you get Main.hs:23:33:fromJust Nothing as your error message. or you should at least. likewise for head, tail, undefined, etc.. actually any function including ones you write yourself for which you give the SRCLOC_ANNOTATE pragma. boy I want to have the time to port that to ghc... a six pack of beer for whoever does :) John -- John Meacham - ⑆repetae.net⑆john⑈

On Saturday 18 November 2006 00:37, Neil Mitchell wrote:
Hi
How controversial would a proposal to {-# DEPRECATE fromJust #-} be, in favour of:
Just _ = x -- which will give you the precise line number
It seems to me this is one cause of mysterious newbie errors we could easily discourage, with little harm.
Btw, I'm not seriously suggesting removing it ;) It could be discouraged ever so slightly in the haddocks though.
I strongly disagree. If we are removing things that confuse newbies why not start with higher rank types, MPTC's and GADT's ;)
fromJust is simple, useful and clear. What you mean is that implementations aren't very good at debugging this. It seems unfair to blame partial functions for the lack of a debugger. If a call stack was automatically output every time a fromJust failed would this even be something people complained about?
Well, I strongly disagree. :) I suspect I would be classified as a newbie relative to most posters on this list but here's my thoughts anyway... I chose to learn haskell largely because I thought the static type safety would help eliminate bugs, I've never once been happy when I've needed to fire up a debugger or add trace statements and I hoped they would become things of the past. One of my initial responses to haskell was disappointment upon seeing head, fromJust and the like. 'Those look nasty', I sez to meself. From day one I've tried to avoid using them. Very occasionally I do use them in the heat of the moment, but it makes me feel unclean and I end up having to take my keyboard into the bathroom for a good scrubbing with the sandsoap. The disappointment has pretty much changed to frustration since reading Oleg, and others, type-hackery work. I realise the problems are just poor/limited usage of haskell, not inherent in the language. Unfortunately I can understand the 'right' solutions but still have trouble formulating them myself. I'm hoping that if I hang out in the type-hackery 'hot zone' long enough I'll start emitting enough picoOlegs myself to solve simple problems. ;) My view is that if I can reason about my program and know a static property I want to be able to stamp this into the types and have my reasoning validated during compilation. But existing library code with weak typesafety is a large inertial mass, when trying to do something 'right' the interfacing is a daunting prospect. In general I'd rather have effort go into promoting 'right' solutions, and making those solutions easier to express, than going into debuggers for 'wrong' solutions. Daniel

Daniel, you wrote:
I suspect I would be classified as a newbie relative to most posters on this list but here's my thoughts anyway... [...] One of my initial responses to haskell was disappointment upon seeing head, fromJust and the like. 'Those look nasty', I sez to meself. From day one I've tried to avoid using them. Very occasionally I do use them in the heat of the moment, but it makes me feel unclean and I end up having to take my keyboard into the bathroom for a good scrubbing with the sandsoap.
I completely agree and couldn't have said it in any better way (including the relative newbie part). Ben

On 11/15/06, Donald Bruce Stewart
Yes, these techniques are fairly well known now, and hopefully some of the more experienced Haskellers are using them (I certainly use the non-empty list tricks). Any anyone with more than 6 months Haskell knows to avoid fromJust.
The problem I see is that head/fromJust errors are usually caused by *beginner* Haskellers, who don't know the techniques for statically avoiding them.
I'm one of those "beginning" Haskellers (about one month in) and I'd like to know these techniques. Are they written up anywhere? Justin p.s. apologies for the double-email Donald - forget to CC the list on the first one.

On Nov 15, 2006, at 3:21 AM, oleg@pobox.com wrote:
Donald Bruce Stewart wrote:
So all this talk of locating head [] and fromJust failures got me thinking:
Couldn't we just use rewrite rules to rewrite *transparently* all uses of fromJust to safeFromJust, tagging the call site with a location?
I'm sorry for shifting the topic: I'm wondering if, rather than trying to make an error message more informative, we ought to make sure that no error will ever arise? ... This topic has been discussed at length on this list. It seems that the discussion came to the conclusion that eliminating head of the empty list error is possible and quite easy in Haskell.
http://www.haskell.org/pipermail/haskell-cafe/2006-September/ 017915.html
But this code contains a function with_non_empty_list (or perhaps with_nonempty_list or withNonemptyList or...) which has the same confusing failure mode as the examples under discussion. Fundamentally, if we try to package up "check for failure" in a function, whether the function does something useful as well (head, tail, fromJust) or not (withNonemptyList), we miss out on useful contextual information when our program fails. In addition, we have this rather nice assembly of functions which work on ordinary lists. Sadly, rewriting them all to also work on NonEmptyList or MySpecialInvariantList is a nontrivial task. Which isn't to say that I disapprove of this style: check your invariants early, maintain them as you go. I'm quite enjoying the escH paper, but I get through about a column per day between compiles. :-) -Jan-Willem Maessen

Jan-Willem Maessen wrote:
In addition, we have this rather nice assembly of functions which work on ordinary lists. Sadly, rewriting them all to also work on NonEmptyList or MySpecialInvariantList is a nontrivial task.
That's an excellent question. Indeed, let us assume we have a function foo:: [a] -> [a] (whose code, if available, we'd rather not change) and we want to write something like \l -> [head l, head (foo l)] To use the safe `head' from NList.hs , we should write \l -> indeedFL l onempty (\l -> [head l, head (foo l)]) But that doesn't type: first of all, foo applies to [a] rather than FullList a, and second, the result of foo is not FullList a, required by our |head|. The first problem is easy to solve: we can always inject FullList a into the general list: fromFL. We insist on writing the latter function explicitly, which keeps the typesystem simple, free of subtyping and implicit coercions. One may regard fromFL as an analogue of fromIntegral -- which, too, we have to write explicitly, in any code with more than one sort of integral numbers (e.g., Int and Integer, or Int and CInt). If we are not sure if our function foo maps non-empty lists to non-empty lists, we really should handle the empty list case: \l -> indeedFL l onempty $ \l -> [head l, indeedFL (foo $ fromFL l) onempty' head] If we have a hunch that foo maps non-empty lists to non-empty lists, but we are too busy to verify it, we can write \l -> indeedFL l onempty $ \l -> [head l, indeedFL (foo $ fromFL l) (assert (const False msg) undefined) head] where msg = "I'm quite sure foo maps non-empty lists to " ++ "non-empty lists. I'll be darned if it doesn't." That would get the code running. Possibly at some future date (during the code review?) I'll be called to justify my hunch, to whatever degree of formality (informal argument, formal proof) required by the policies in effect. If I fail at this justification, I'd better think what to do if the result of foo is really the empty list. If I succeed, I'd be given permission to update the module NList with the following definition nfoo (FullList x) = FullList $ foo x after which I could write \l -> indeedFL l onempty (\l -> [head l, head (nfoo l)]) with no extra empty list checks. It goes without saying that it would save a lot of typing if List were a typeclass (like Num) rather than a datatype...
participants (20)
-
Benjamin Franksen
-
Bulat Ziganshin
-
Daniel McAllansmith
-
David House
-
dons@cse.unsw.edu.au
-
Henning Thielemann
-
Jacques Carette
-
Jan-Willem Maessen
-
John Meacham
-
Justin Bailey
-
Jón Fairbairn
-
Ketil Malde
-
Lennart Augustsson
-
Neil Mitchell
-
oleg@pobox.com
-
Robert Dockins
-
Ross Paterson
-
S. Alexander Jacobson
-
Simon Peyton-Jones
-
Udo Stenzel