A Pointless Library Proposal

Hi folks This seems like the ideal time to make a wannabe library proposal which is pointless, but pointless by design. The code's quite short: ----------
module Zero where
-- import GHC.Prim -- if you can
The Zero type has nothing in it. Well, nothing worth worrying about anyway.
data Zero
Elements of Zero are rather special, powerful things.
magic :: Zero -> a magic _ = error "There's magic, as no such thing!"
It's a little frustrating to have to define this function lazily. I prefer the strict definition with no lines, but it isn't valid Haskell! The main use of Zero is to give types |f Zero| to the closed ('elementless') values of some functorial structure f, especially closed /terms/. These closed values should be embedded (as cheaply as possible) into all the f-types which do permit elements.
fMagic :: Functor f => f Zero -> f a fMagic = fmap magic -- if you must -- fMagic = unsafeCoerce# -- if you can
----------- I'm not being facetious here. The reason it ought to be in a library rather than ad hoc is that it (ideally) packs up a perfectly safe use of unsafeCoerce#, which deserves some veneer of legitimacy. This is seriously useful stuff if you want better static checking for scope (and related notions), without taking a performace hit. For example, you should all know the classic de Bruijn representation...
data Tm x = V x | A (Tm x) (Tm x) | L (Tm (Maybe x)) deriving Show
...for which fmap does renaming...
instance Functor Tm where fmap rho (V x) = V (rho x) fmap rho (A f a) = A (fmap rho f) (fmap rho a) fmap rho (L b) = L (fmap (fmap rho) b)
...and (>>=) does capture-avoiding simultaneous substitution.
instance Monad Tm where return = V V x >>= sgm = sgm x A f a >>= sgm = A (f >>= sgm) (a >>= sgm) L b >>= sgm = L (b >>= shift sgm) where shift sgm Nothing = V Nothing shift sgm (Just x) = fmap Just (sgm x)
But operationally, you'd never do any such thing. See how capture is avoided? The shift operator (aka traverse, but that's another story), has to tweak all the free variables in the image of the substitution to avoid capturing the new bound variable, Nothing. Ouch! However, if you've ever fooled around with Int-based de Bruijn representations, you'll know that the really cool thing is to substitute /closed/ terms without any need for shifting. A term with no free variables can't capture anything! Hence
closedSubst :: (x -> Either (Tm Zero) y) -> Tm x -> Tm y closedSubst sgm (V x) = either fMagic V (sgm x) closedSubst sgm (A f a) = A (closedSubst sgm f) (closedSubst sgm a) closedSubst sgm (L b) = L (closedSubst (shift sgm) b) where shift sgm Nothing = Right Nothing shift sgm (Just x) = either Left (Right . Just) (sgm x)
Here, variables are either mapped to closed terms or renamed. We never need to traverse the closed terms to push them under a binder: the shift operator (aaka traverse, ahem) only shifts the renaming part (cheap!) and the closed terms stay closed. When we finally hit a variable, the closed images just get fMagic'd into the right scope! So there you have it, a bone fide useful use of the Zero type, given a module exporting a safe use of a usually dodgy operator. I don't think module Zero is as pointless as the the datatype it defines. My apologies for not providing any QuickCheck properties. All the best Conor This message has been checked for viruses but the contents of an attachment may still contain software viruses, which could damage your computer system: you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation.

On Mon, Oct 23, 2006 at 03:26:33PM +0100, Conor McBride wrote:
This seems like the ideal time to make a wannabe library proposal which is pointless, but pointless by design. The code's quite short:
so, just to clarify, is what you are proposing is a type whose only inhabitant is _|_, and since _|_ inhabits all types, we should be able to freely cast this bottom-only-containing type to any other? Sounds good to me. I can't think of a use off the top of my head, but I ended up using Identity all over the place... and this sounds like just the random sort of thing I will find odd uses for. :) but since 'Zero' is often used in type arithmetic implementations (even though those uses arn't entirely incompatable) I think we should name it something else. I think data Bottom is waht I would like. John -- John Meacham - ⑆repetae.net⑆john⑈

On Monday 23 October 2006 17:26, Jason Dagit wrote:
On 10/23/06, Samuel Bronson
wrote: On 10/23/06, John Meacham
wrote: On Mon, Oct 23, 2006 at 03:26:33PM +0100, Conor McBride wrote:
data Bottom
Why not "data Void"?
I'm partial to: data Intercalate
I'd have to vode for: data BikeShed Seriously, though. I prefer 'Void' to 'Bottom'.
Jason
-- Rob Dockins Talk softly and drive a Sherman tank. Laugh hard, it's a long way to the bank. -- TMBG

On Mon, Oct 23, 2006 at 05:17:49PM -0400, Samuel Bronson wrote:
On 10/23/06, John Meacham
wrote: On Mon, Oct 23, 2006 at 03:26:33PM +0100, Conor McBride wrote:
data Bottom Why not "data Void"?
also good. or data Absurd also works for me. John -- John Meacham - ⑆repetae.net⑆john⑈

On 10/23/06, John Meacham
On Mon, Oct 23, 2006 at 05:17:49PM -0400, Samuel Bronson wrote:
On 10/23/06, John Meacham
wrote: On Mon, Oct 23, 2006 at 03:26:33PM +0100, Conor McBride wrote:
data Bottom Why not "data Void"?
also good.
or
data Absurd
also works for me.
Hmm, I like Absurd too ;-).

Samuel Bronson
On 10/23/06, John Meacham
wrote: On Mon, Oct 23, 2006 at 03:26:33PM +0100, Conor McBride wrote:
data Bottom Why not "data Void"?
I'd say that ``Void'' is not a desirable candidate since too many people know C, and the C type ``void'' corresponds to ``()'' (or ``IO ()''...) (One name I have used before is ``Empty'', but I find ``Zero'' and ``Absurdity'' appropriate, too. ``Absurd'' perhaps sounds more like a value than like a type...) Wolfram

On Tue, 23 Oct 2006 kahl@cas.mcmaster.ca wrote:
Samuel Bronson
wrote: On 10/23/06, John Meacham
wrote: On Mon, Oct 23, 2006 at 03:26:33PM +0100, Conor McBride wrote:
data Bottom Why not "data Void"?
I'd say that ``Void'' is not a desirable candidate since too many people know C, and the C type ``void'' corresponds to ``()'' (or ``IO ()''...)
It doesn't, we just use () for similar things. You can't have a value of type void in C - don't confuse a denotational semantics of C with C itself. -- flippa@flippac.org 'In Ankh-Morpork even the shit have a street to itself... Truly this is a land of opportunity.' - Detritus, Men at Arms

kahl:
Samuel Bronson
wrote: On 10/23/06, John Meacham
wrote: On Mon, Oct 23, 2006 at 03:26:33PM +0100, Conor McBride wrote:
data Bottom Why not "data Void"?
I'd say that ``Void'' is not a desirable candidate since too many people know C, and the C type ``void'' corresponds to ``()'' (or ``IO ()''...)
(One name I have used before is ``Empty'', but I find ``Zero'' and ``Absurdity'' appropriate, too. ``Absurd'' perhaps sounds more like a value than like a type...)
A precedent for Void comes from Djinn, http://darcs.augustsson.net/Darcs/Djinn, well-known to #haskell irc people: Since Djinn handles propositional calculus it also knows about the absurd proposition, corresponding to the empty set. This set is called Void in Haskell, and Djinn assumes an elimination rule for the Void type: data Void type Not x = x -> Void void :: Void -> a Using Void is of little use for programming, but can be interesting for theorem proving. Example, the double negation of the law of excluded middle: Djinn> f ? Not (Not (Either x (Not x))) f :: Not (Not (Either x (Not x))) f x1 = void (x1 (Right (\ c23 -> void (x1 (Left c23))))) I'd go so far as to say its intuitive to use Void, after the last year spent playing with Djinn online. -- Don

On 23 Oct 2006 22:05:58 -0400, kahl@cas.mcmaster.ca
I'd say that ``Void'' is not a desirable candidate since too many people know C, and the C type ``void'' corresponds to ``()'' (or ``IO ()''...)
So how come whenever I say that, someone invariably corrects me that C's void type is uninhabited, whereas the () type is inhabited by ()? And that a real void-alike wouldn't have any constructors?

On Mon, 23 Oct 2006, Samuel Bronson wrote:
On 23 Oct 2006 22:05:58 -0400, kahl@cas.mcmaster.ca
wrote: I'd say that ``Void'' is not a desirable candidate since too many people know C, and the C type ``void'' corresponds to ``()'' (or ``IO ()''...)
So how come whenever I say that, someone invariably corrects me that C's void type is uninhabited, whereas the () type is inhabited by ()? And that a real void-alike wouldn't have any constructors?
Because C's an impure language - and thus it's possible to do something meaningful without returning a value. Oh, and because they're right. -- flippa@flippac.org The task of the academic is not to scale great intellectual mountains, but to flatten them.

Philippa Cowderoy wrote:
On Mon, 23 Oct 2006, Samuel Bronson wrote:
On 23 Oct 2006 22:05:58 -0400, kahl@cas.mcmaster.ca
wrote: I'd say that ``Void'' is not a desirable candidate since too many people know C, and the C type ``void'' corresponds to ``()'' (or ``IO ()''...) So how come whenever I say that, someone invariably corrects me that C's void type is uninhabited, whereas the () type is inhabited by ()? And that a real void-alike wouldn't have any constructors?
Because C's an impure language - and thus it's possible to do something meaningful without returning a value. Oh, and because they're right.
No, I think Wolfram's correct. In C, void represents a return structure of zero bytes. It therefore has 256^0 = 1 value, just like the "()" type (ignoring bottom). AFAIR C disallows declaring a variable void, though it would be theoretically possible to relax this, and have them allocated as zero bytes. Reading a variable of type "void" would return the "void value" without actually reading from memory (since zero of it is allocated to read from), and assigning to it would do nothing. -- Ashley Yakeley

Indeed, let's resurrect Void. Haskell 1.4 had Void. I never understood why it was removed. -- Lennart On Oct 23, 2006, at 17:17 , Samuel Bronson wrote:
On 10/23/06, John Meacham
wrote: On Mon, Oct 23, 2006 at 03:26:33PM +0100, Conor McBride wrote:
data Bottom Why not "data Void"?
Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Hi John Meacham wrote:
On Mon, Oct 23, 2006 at 03:26:33PM +0100, Conor McBride wrote:
This seems like the ideal time to make a wannabe library proposal which is pointless, but pointless by design. The code's quite short:
so, just to clarify, is what you are proposing is a type whose only inhabitant is _|_, and since _|_ inhabits all types, we should be able to freely cast this bottom-only-containing type to any other?
Exactly, although I prefer to avoid talking about _|_ unless I absolutely have to. The fact that there are no values worth speaking of in |Zero| is a good way of pinning down the /absence/ of things, hence the use of |Tm Zero| to represent terms with no free variables. Moreover, general tree-like structures given by fixpoints of functors
data Fix f = In (f (Fix f))
have a general notion of |leaf|
leaf :: Functor f => f Zero -> Fix f leaf = In . fMagic
If you're interested in calculating types of one-hole contexts, then |Zero| is very handy
class (Functor f, Functor g) => Diff f g | f -> g where ...
instance Diff (Const c) (Const Zero) where ... instance Diff Id (Const ()) where ... instance (Diff f f', Diff g g') => Diff (Sum f g) (Sum f' g') where ... instance (Diff f f', Diff g g') => Diff (Prod f g) (Sum (Prod f' g) (Prod f g')) where ...
where Sum and Prod are Either and (,) lifted pointwise to kind * -> *
Sounds good to me. I can't think of a use off the top of my head, but I ended up using Identity all over the place... and this sounds like just the random sort of thing I will find odd uses for. :)
so plenty of odd uses!
but since 'Zero' is often used in type arithmetic implementations (even though those uses arn't entirely incompatable) I think we should name it something else.
I think the two go very well together. If you define
data Suc n = New | Old n
then the type-level unary numbers double as types with that many values worth speaking of. I'm rather fond of the idea that |Tm (Suc (Suc Zero))| is the type of terms in two free variables, and so on. You also get that addition, multiplication, etc, for type-level numbers correspond to, er, sum, product, etc for the types. I know this kind of breaks the singleton hack to give run-time proxies for static types, but there are other ways to make proxies.
I think
data Bottom
is waht I would like.
This is one thing we've got that we shouldn't flaunt. If I can't have Zero, please may I have
data Naught
naughty :: Naught -> y
innocent :: Functor f => f Naught -> f x
or some such? Cheers Conor This message has been checked for viruses but the contents of an attachment may still contain software viruses, which could damage your computer system: you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation.

On Mon, Oct 23, 2006 at 10:43:36PM +0100, Conor McBride wrote:
This is one thing we've got that we shouldn't flaunt. If I can't have Zero, please may I have
data Naught
naughty :: Naught -> y
innocent :: Functor f => f Naught -> f x
or some such?
I am liking the 'Void' idea proposed earlier, so we have
module Data.Void where
data Void deriving(Typeable,Data,Eq,Ord,...) -- ^ a lot of valid classes -- are defined for _|_
fromVoid :: forall a . Void -> a fromVoid = unsafeCoerce#
as a bonus, with void, we get to be reminded of b-movie titles like this friday, at your local theater: "BEWARE! the catamorph from the VOID!" I am not sure what a catamorph would be, depending on whether it is preceded by cuddly or deadly I'd say a sidekick on thundercats or a metamorphic feline killing machine. speaking of which, there should be a contest among category theorists to come up with the best definition for a 'Xenomorphism'. I am not sure what it would be, but I doubt it would be structure preserving.. John -- John Meacham - ⑆repetae.net⑆john⑈

G'day all.
Quoting John Meacham
but since 'Zero' is often used in type arithmetic implementations (even though those uses arn't entirely incompatable) I think we should name it something else.
Actually, this works fine. data Zero data Succ a class Add a b c | a b -> c instance Add Zero b b instance (Add a b c) => Add (Succ a) b (Succ c) It does smell like semantic overloading, though. Cheers, Andrew Bromage

Conor McBride wrote:
magic :: Zero -> a magic _ = error "There's magic, as no such thing!"
It's a little frustrating to have to define this function lazily. I prefer the strict definition with no lines, but it isn't valid Haskell!
This issue comes up a lot with GADTs. For instance: data MyGADT a where MyInt :: MyGADT Int MyChar :: MyGADT Char never :: MyGADT Bool -> a Annoyingly, this doesn't compile without adding a definition line mentioning a bottom value. -- Ashley Yakeley

Hi Ashley Yakeley wrote:
I wrote:
magic :: Zero -> a magic _ = error "There's magic, as no such thing!"
It's a little frustrating to have to define this function lazily. I prefer the strict definition with no lines, but it isn't valid Haskell!
This issue comes up a lot with GADTs.
It's quite familiar with dependent types too, so that shouldn't come as a surprise. Some of us have spent quite a while figuring out how to suck a complete absence of eggs.
For instance:
data MyGADT a where MyInt :: MyGADT Int MyChar :: MyGADT Char
or even data Eq a b where Refl :: Eq a a never :: Eq Int Bool -> a In 'Eliminating Dependent Pattern Matching', Healf Goguen, James McKinna and I suggest a notation which supplements the usual 'return an output' notation with a 'refute an input' notation. Something like never x _|_ x -- 'never x refutes x' which requires x to be checkably in a type with no constructors (under any hypotheses). This notation enables a machine to check whether the programmer has explained how to cover all cases by an explanation either of what to return or why there's no need. I wouldn't presume to propose this notation for Haskell, but equally, it's dangerous to presume that as more and more of these phenomena show up in Haskell, the old language choices will remain sufficient or suitable. We live in interesting times. All the best Conor This message has been checked for viruses but the contents of an attachment may still contain software viruses, which could damage your computer system: you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation.

Ashley Yakeley wrote:
data MyGADT a where MyInt :: MyGADT Int MyChar :: MyGADT Char
never :: MyGADT Bool -> a
Annoyingly, this doesn't compile without adding a definition line mentioning a bottom value.
This can't be fixed because the desugaring is ambiguous. never might be _|_ or \x. _|_ or \x y. _|_ or ... How about never :: MyGADT Bool -> a never x = case x of {} which is just the desugared form of your intended empty definition? GHC doesn't allow it, but it would be a simple extension. -- Ben

On 10/24/06, Russell O'Connor
Conor McBride
writes: Elements of Zero are rather special, powerful things.
magic :: Zero -> a magic _ = error "There's magic, as no such thing!"
Why have a function body at all? Shouldn't the type signature be sufficent?
Remember that type signatures need not be adjacent to function definitions. Now ponder what would happen if you forgot to define a function. Have a clue why it isn't sufficient now?

Samuel Bronson
On 10/24/06, Russell O'Connor
wrote: Why have a function body at all? Shouldn't the type signature be sufficent?
Remember that type signatures need not be adjacent to function definitions. Now ponder what would happen if you forgot to define a function. Have a clue why it isn't sufficient now?
If you turn on -Wall in GHC, you would get a warning that your pattern coverage is incomplete. We should make it so that if the pattern coverage is incomplete and there is no function body, then that is an error.

Russell O'Connor schrieb:
Samuel Bronson
writes: On 10/24/06, Russell O'Connor
wrote: Why have a function body at all? Shouldn't the type signature be sufficent? Remember that type signatures need not be adjacent to function definitions. Now ponder what would happen if you forgot to define a function. Have a clue why it isn't sufficient now?
If you turn on -Wall in GHC, you would get a warning that your pattern coverage is incomplete. We should make it so that if the pattern coverage is incomplete and there is no function body, then that is an error.
You mean a warning for a completely missing body, don't you? I'ld find type signatures of functions only perfect for specification purposes. Some time ago I even submitted a feature request. http://hackage.haskell.org/trac/ghc/ticket/393 Christian

Hi Russell O'Connor wrote:
Samuel Bronson
writes: On 10/24/06, Russell O'Connor
wrote: Why have a function body at all? Shouldn't the type signature be sufficent?
Hmmm
Remember that type signatures need not be adjacent to function definitions. Now ponder what would happen if you forgot to define a function. Have a clue why it isn't sufficient now?
If you turn on -Wall in GHC, you would get a warning that your pattern coverage is incomplete. We should make it so that if the pattern coverage is incomplete and there is no function body, then that is an error.
So, taking Void to be the colour of the empty bikeshed and avoid :: Void -> x suppose I define data WrapVoid = Wrap Void may I now write boo :: WrapVoid -> x with no equations? Does this cover? Or does it neglect the crucial boo (Wrap _|_) case? What about hoo :: Void -> Bool -> x ? Does this cover, or did I forget hoo v True and hoo v False? Funny business, coverage checking. With GADTs, things become even more entertaining... All the best Conor

Conor McBride
So, taking Void to be the colour of the empty bikeshed and
avoid :: Void -> x
suppose I define
data WrapVoid = Wrap Void
may I now write
boo :: WrapVoid -> x
with no equations? Does this cover? Or does it neglect the crucial boo (Wrap _|_) case?
It would be considered ``covered''; however you may, at your option, wish to add function body to handle (Wrap x).
What about
hoo :: Void -> Bool -> x
? Does this cover, or did I forget hoo v True and hoo v False?
This is considered covered, but again you may, at your option, wish to add a function body to handle the hoo v True and hoo v False cases. Basically we considered all the cases covered if they are covered for all non-bottom values. This is (I understand) what the warning in GHC does. I would also be willing to consider Christian Maeder's proposal where a missing function body is never an error.

Hi again [editing slightly] Russell O'Connor wrote:
Conor McBride
writes: may I now write
boo :: WrapVoid -> x hoo :: Void -> Bool -> x
with no equations? It would be considered ``covered''; however you may, at your option, wish to add function body to handle (Wrap x).
This is considered covered, but again you may, at your option, wish to add a function body to handle the hoo v True and hoo v False cases.
Hmmm. For GADTs, I fear that this coverage checking problem may be undecidable. To see why, check page 179 of my PhD thesis, although the result (due to Gerard Huet, I believe) was certainly known to Thierry Coquand in 1992. But...
Basically we considered all the cases covered if they are covered for all non-bottom values. This is (I understand) what the warning in GHC does.
...isn't (Wrap _|_) a non-bottom value? Doesn't moo (Wrap v) = True distinguish (Wrap _|_) from _|_ ? If you're willing to tolerate the need to cover these cases, coverage checking becomes decidable! Of course, it leaves you wondering what to write on the right-hand side...
I would also be willing to consider Christian Maeder's proposal where a missing function body is never an error.
I'd be more comfortable with a more explicit way to leave a stub, but I agree that there should be a way to indicate 'unfinished' which is distinct from 'defined to be _|_'. Moreover, I should very much like to have a token I can write in the place of an expression, such that on compilation, I receive a diagnostic giving me as much type information as possible about what must replace the token. When you try the old trick of making a deliberate type error to achive this effect, you often get less back than you might hope. Fine for genuine errors, but not enough to satisfy the ulterior motive. Cheers Conor

On 10/25/06, Conor McBride
Moreover, I should very much like to have a token I can write in the place of an expression, such that on compilation, I receive a diagnostic giving me as much type information as possible about what must replace the token. When you try the old trick of making a deliberate type error to achive this effect, you often get less back than you might hope. Fine for genuine errors, but not enough to satisfy the ulterior motive.
I often want something similar but just a hair different. Sometimes I going along writing some code and I need a function or some monadic action but maybe I don't want to think yet how to define it. So I'll stick in the name of the function as a place holder, then quickly define the function to be undefined. This way I can try to compile my program to make sure all the defined code has the right types. This trick becomes even handier with Visual Haskell since it only displays type information if the whole module type checks. The obvious problem is that I may go off and forget to finish defining that undefined function. It would be nice if the compiler could say, "Oh, don't forget to finish writing that function stub!". In fact, maybe the special token in this case could be stub :: a, that is just designed to pass type checking and give an error as late in the compilation as possible. Hmm...maybe stub could be defined using some TH...Although, the error may still happen too soon. Ideally it would happen after all the relevant modules have been type checked. Jason

On Oct 25, 2006, at 5:24 AM, Conor McBride wrote:
Hi again
[editing slightly]
Russell O'Connor wrote:
Conor McBride
writes: may I now write
boo :: WrapVoid -> x hoo :: Void -> Bool -> x
with no equations? It would be considered ``covered''; however you may, at your option, wish to add function body to handle (Wrap x). This is considered covered, but again you may, at your option, wish to add a function body to handle the hoo v True and hoo v False cases.
Hmmm. For GADTs, I fear that this coverage checking problem may be undecidable. To see why, check page 179 of my PhD thesis, although the result (due to Gerard Huet, I believe) was certainly known to Thierry Coquand in 1992. But...
Basically we considered all the cases covered if they are covered for all non-bottom values. This is (I understand) what the warning in GHC does.
...isn't (Wrap _|_) a non-bottom value? Doesn't
moo (Wrap v) = True
distinguish (Wrap _|_) from _|_ ?
If you're willing to tolerate the need to cover these cases, coverage checking becomes decidable! Of course, it leaves you wondering what to write on the right-hand side...
I would also be willing to consider Christian Maeder's proposal where a missing function body is never an error.
I'd be more comfortable with a more explicit way to leave a stub, but I agree that there should be a way to indicate 'unfinished' which is distinct from 'defined to be _|_'.
I'd have to say that all we really need for the original problem is a case statement with no arms. eg, data Void void :: Void -> a void x = case x of {} However, I feel this whole conversation is pretty academic because void x = undefined has exactly the same semantics, and void x = x `seq` undefined will even have pretty much the same operational behavior. I agree that being able to directly implement the Void catamorphism is appealing, I just don't think it makes a big practical difference. I would not at all like to see the ability to define functions by just writing type signatures.
Moreover, I should very much like to have a token I can write in the place of an expression, such that on compilation, I receive a diagnostic giving me as much type information as possible about what must replace the token. When you try the old trick of making a deliberate type error to achive this effect, you often get less back than you might hope. Fine for genuine errors, but not enough to satisfy the ulterior motive.
Cheers
Conor
Rob Dockins Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG

Conor McBride writes:
magic :: Zero -> a magic _ = error "There's magic, as no such thing!"
It's a little frustrating to have to define this function lazily. I prefer the strict definition with no lines, but it isn't valid Haskell!
I think you could avoid that frustration by defining Zero/Void/Bikeshed
liko so:
newtype Void = Void { avoid :: forall a. a }
That gets you a strictly defined avoid and emphasizes that Void is
isomorphic to (forall a. a).
On a semi-related note, how about instances for the Prelude classes?
For example,
instance Show Void where
show = avoid
instance Read Void where
readsPrec _ _ = []
instance Eq Void where
a == b = avoid a
instance Ord Void where
compare a b = avoid a
Enum and Bounded are out, because they have methods which produce
values, but Data and Typeable instances might be reasonable.
--
David Menendez

Hi David Menendez wrote:
Conor McBride writes:
magic :: Zero -> a magic _ = error "There's magic, as no such thing!"
It's a little frustrating to have to define this function lazily. I prefer the strict definition with no lines, but it isn't valid Haskell!
I think you could avoid that frustration by defining Zero/Void/Bikeshed liko so:
newtype Void = Void { avoid :: forall a. a }
That gets you a strictly defined avoid and emphasizes that Void is isomorphic to (forall a. a).
Aha, the Church Void! That's a neat way of doing it under the circumstances. The datatype with no constructors issue will show up again with GADTs, but this is a sensible way to postpone it. I guess (to answer Rob Dockins) that it's not the number of lines I'm bothered by, but rather the invocation of 'undefined', 'error' or some other signal of /underdefinition/ to present a function which is entirely well-defined, indeed trivially so. This may seem academic, but with types being used increasingly in their role as evidence, we'll eventually need to be comfortable with negative information as well as positive.
On a semi-related note, how about instances for the Prelude classes?
For example,
instance Show Void where show = avoid
instance Read Void where readsPrec _ _ = []
instance Eq Void where a == b = avoid a
instance Ord Void where compare a b = avoid a
Absolutely! It's not a joke. Some notion of Zero (and here's really why I like Zero) is very useful if you're doing algebra, let alone calculus with data structures. Given how many of our favourite datatypes are fixpoints of polynomial functors, with Show, Eq, etc, it's important that each of the building blocks of polynomials is closed under these things. You might not often need to use a Zero in the polynomial datatypes you define, but it's useful to have Zero if you're calculating one polynomial from another. I want to get for free that if my datatype has polynomial nodes, its type of one-hole contexts is showable. All the best Conor

On Thu, Oct 26, 2006 at 02:11:18AM -0400, David Menendez wrote:
Enum and Bounded are out, because they have methods which produce values, but Data and Typeable instances might be reasonable.
definitely! Most of the uses percolating through my brain involve Data and Typeable instances. of coures, I am of the opinion that _every_ type should automatically get a Typeable instance. (but not Data obviously) John -- John Meacham - ⑆repetae.net⑆john⑈

| > magic :: Zero -> a | > magic _ = error "There's magic, as no such thing!" | | It's a little frustrating to have to define this function lazily. I | prefer the strict definition with no lines, but it isn't valid | Haskell! I've occasionally wondered about emitting a warning, but not an error, when there's a type signature for a function but no definition. The compiler could automatically generate an error message stub implementation, much as it does for an incomplete pattern match, of which this is an extreme example. If anyone is keen on this, pls create a Trac feature request, and fill out the details (e.g. what flags, what should the warning look like..). Better still do that, and submit a patch! Simon

Simon Peyton-Jones wrote:
I've occasionally wondered about emitting a warning, but not an error, when there's a type signature for a function but no definition. The compiler could automatically generate an error message stub implementation, much as it does for an incomplete pattern match, of which this is an extreme example.
I don't like this idea because the necessary stub is different for different numbers of arguments, and there's no way to tell how many arguments the programmer intended. I do like the idea of allowing empty case expressions, though, and I don't think that even a warning would be necessary. -- Ben

| I don't like this idea because the necessary stub is different for different | numbers of arguments, and there's no way to tell how many arguments the | programmer intended. Why? What's wrong with expanding foo :: Int -> Int -> Int into foo :: Int -> Int -> Int foo = error "foo is not yet implemented" which is what I usually write by hand. |I do like the idea of allowing empty case expressions, | though, and I don't think that even a warning would be necessary. So how would you define foo? How would it be better than the above (even if written by hand)? Simon

I like to use undefined is the stub for unimplemented functions since it's nice and terse. Unfortunately, ghc doesn't give much information about where the undefined was called. It would be great if the message for undefined could include file name and line number (like hbc did :). -- Lennart On Oct 30, 2006, at 09:54 , Simon Peyton-Jones wrote:
| I don't like this idea because the necessary stub is different for different | numbers of arguments, and there's no way to tell how many arguments the | programmer intended.
Why? What's wrong with expanding foo :: Int -> Int -> Int into foo :: Int -> Int -> Int foo = error "foo is not yet implemented"
which is what I usually write by hand.
|I do like the idea of allowing empty case expressions, | though, and I don't think that even a warning would be necessary.
So how would you define foo? How would it be better than the above (even if written by hand)?
Simon _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Mon, Oct 30, 2006 at 10:16:46AM -0500, Lennart Augustsson wrote:
I like to use undefined is the stub for unimplemented functions since it's nice and terse. Unfortunately, ghc doesn't give much information about where the undefined was called. It would be great if the message for undefined could include file name and line number (like hbc did :).
jhc has the SRCLOC_ANNOTATE pragma, which lets you attach file and line number information to arbitrary functions. sort of a generalization of the 'assert' feature of ghc. One day I will get around to implementing it in ghc. perhaps the next time a program I write mysteriously dies with "Prelude.undefined" being the only thing printed. John -- John Meacham - ⑆repetae.net⑆john⑈

john:
On Mon, Oct 30, 2006 at 10:16:46AM -0500, Lennart Augustsson wrote:
I like to use undefined is the stub for unimplemented functions since it's nice and terse. Unfortunately, ghc doesn't give much information about where the undefined was called. It would be great if the message for undefined could include file name and line number (like hbc did :).
jhc has the SRCLOC_ANNOTATE pragma, which lets you attach file and line number information to arbitrary functions. sort of a generalization of the 'assert' feature of ghc. One day I will get around to implementing it in ghc. perhaps the next time a program I write mysteriously dies with "Prelude.undefined" being the only thing printed.
I've previously used assert for this, For locating errors with line numbers: http://www.cse.unsw.edu.au/~dons/tmp/Exception.hs and adding line numbers to 'trace' http://www.cse.unsw.edu.au/~dons/tmp/Location.hs But seems like we need a 'proper' solution. undefineds with lines numbers, and errors with line numbers, would be a good start. -- Don

On 31/10/06, Donald Bruce Stewart
But seems like we need a 'proper' solution. undefineds with lines numbers, and errors with line numbers, would be a good start.
I think it'd be nice to keep undefined around as a 'pure' bottom, and introduce a new value, say 'stub :: forall a. a' which is magic and sends the file and line location of its mention to stderr when executed. -- -David House, dmhouse@gmail.com

David House wrote:
On 31/10/06, Donald Bruce Stewart
wrote: But seems like we need a 'proper' solution. undefineds with lines numbers, and errors with line numbers, would be a good start.
I think it'd be nice to keep undefined around as a 'pure' bottom, and introduce a new value, say 'stub :: forall a. a' which is magic and sends the file and line location of its mention to stderr when executed.
As Haskell insists that bottom is a value, it's conceptually important to separate 'defined to be bottom' from 'not finished yet'. Never mind the run-time stub reports, we should have compile-time stub warnings which are as informative as possible about the task of instantiating the stub. Cheers Conor

Hello David, Tuesday, October 31, 2006, 1:20:42 PM, you wrote:
But seems like we need a 'proper' solution. undefineds with lines numbers, and errors with line numbers, would be a good start.
I think it'd be nice to keep undefined around as a 'pure' bottom, and introduce a new value, say 'stub :: forall a. a' which is magic and sends the file and line location of its mention to stderr when executed.
and then you will introduce exception handling? :) i think that 'undefined' should be not function but preprocessor symbol that's translated into "file:line" notation, and we need the same symbol for monads while error/fail should be used for custom error messages (as they currently used) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Mon, 30 Oct 2006 16:58:40 -0800
John Meacham
On Mon, Oct 30, 2006 at 10:16:46AM -0500, Lennart Augustsson wrote:
I like to use undefined is the stub for unimplemented functions since it's nice and terse. Unfortunately, ghc doesn't give much information about where the undefined was called. It would be great if the message for undefined could include file name and line number (like hbc did :).
jhc has the SRCLOC_ANNOTATE pragma, which lets you attach file and line number information to arbitrary functions. sort of a generalization of the 'assert' feature of ghc. One day I will get around to implementing it in ghc. perhaps the next time a program I write mysteriously dies with "Prelude.undefined" being the only thing printed.
There are many other situations where this would be _extremely_ useful. In my commercially deployed Haskell system, I received repeated requests for filename/line number information to be added to trace logs. I had to resort to using a preprocessor. This is for obvious reasons not an attractive solution. Seth
John
-- John Meacham - ⑆repetae.net⑆john⑈ _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Oct 30, 2006, at 9:38 AM, Ben Rudiak-Gould wrote:
Simon Peyton-Jones wrote:
I've occasionally wondered about emitting a warning, but not an error, when there's a type signature for a function but no definition. The compiler could automatically generate an error message stub implementation, much as it does for an incomplete pattern match, of which this is an extreme example.
I don't like this idea because the necessary stub is different for different numbers of arguments, and there's no way to tell how many arguments the programmer intended. I do like the idea of allowing empty case expressions, though, and I don't think that even a warning would be necessary.
This opinion++
-- Ben
Rob Dockins Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG

Robert Dockins wrote:
On Oct 30, 2006, at 9:38 AM, Ben Rudiak-Gould wrote:
Simon Peyton-Jones wrote:
I've occasionally wondered about emitting a warning, but not an error, when there's a type signature for a function but no definition. The compiler could automatically generate an error message stub implementation, much as it does for an incomplete pattern match, of which this is an extreme example.
I don't like this idea because the necessary stub is different for different numbers of arguments, and there's no way to tell how many arguments the programmer intended. I do like the idea of allowing empty case expressions, though, and I don't think that even a warning would be necessary.
This opinion++
Yes, when I'm not being facetious, I'm inclined to think that some syntax which represents the explicit dismissal of impossible input is preferable to the mere absence of anything to deliver an output. Empty case expressions are one possibility, but I'd also be pleased to see a 'definition form', ie some sort of pattern rejection, in the same way that pattern equations give a neat definition form for nonempty case analysis. Moreover, in the case of GADTs, if you want coverage checking, you need something of the sort. The key question, unless this is just a storm in a teacup in a bikeshed, is how to distinguish underdefined programs from well-defined but vacuous ones. To do the job properly, whatever syntax is used to reject some element of an uninhabited datatype should be considered erroneous if there is a constructor-pattern of that type in some context. That is (if it's empty case) voo :: Void -> x voo v = case v of {} should be fine, but boo :: Bool -> x boo b = case b of {} should be rejected because True (and False) provide a case to answer. Moreover, if we have data Overjoid = Joy Void woo :: Overjoid -> a woo x = case x of {} noo :: Overjoid -> a noo (Joy x) = case x of {} then woo should be rejected but noo accepted. I'd also like to see more support for stubs in code, by way of being able to ask a compiler 'what more must I do here?', but I should also prefer this to be more actively indicated than just by an empty space. Artful silence may be alright for Samuel Beckett, but it strikes me a dangerous way to be straightforward about what sort of nothing you mean. All the best Conor
participants (21)
-
ajb@spamcop.net
-
Ashley Yakeley
-
Ben Rudiak-Gould
-
Bulat Ziganshin
-
Christian Maeder
-
Conor McBride
-
Conor McBride
-
David House
-
David Menendez
-
dons@cse.unsw.edu.au
-
Jason Dagit
-
John Meacham
-
kahl@cas.mcmaster.ca
-
Lennart Augustsson
-
Philippa Cowderoy
-
Robert Dockins
-
Russell O'Connor
-
Russell O\'Connor
-
Samuel Bronson
-
Seth Kurtzberg
-
Simon Peyton-Jones