Re: [Haskell-cafe] Newclasses

2013-10-04 Thread Stijn van Drongelen
On Fri, Oct 4, 2013 at 10:31 PM, Wvv  wrote:

> Newclasses are something like instances, but out of scope. In a baggage.
>

So under the hood of GHC, newclasses would be partially filled in
dictionaries.

We already have too many classes: (...)
>
> We can't divide all classes to atimic ones.
>

As you have seen, we can. As you also see, it is a little impractical.

Main purpose of newclasses is to make instances as minimal as possible. In
> many cases empty.
>
> About newclass and compose data, we can do next:
>
>newclass Foo [a] => FooList a where {containerMainipulation=...}
>
>newclass Foo (Set a) => FooSet a where {containerMainipulation=...}
>
>newclass Foo (Sequence a) => FooSeq a where {containerMainipulation=...}
>
> so now I can switch any container of my data, changing only name of
> newclass:
>
>   instance FooList MyData where {dataMainipulation=...}
>

You can already solve that in Haskell 98:

class Foo2 f where { containerManipulation = ... }
instance Foo2 [] where { ... }
instance Foo2 Set where { ... }
instance Foo2 Sequence where { ... }

class (Foo2 f) => Foo1 f a where { dataManipulation = ... }

Or even:

class Foo' a where { dataManipulation' = ... }
dataManipulation = dataManipulation' yourDefaultContainerManipulation

Remember: the only special things about type classes is that they are types
that can/must be implicit. You can (almost?) always replace them by
explicit parameters.

Or let I have an MyArrow data. And I need some semigroupoid manipulations.
> I just write
>
>   instance ArrSemigroupoid MyArrow --empty
>
> that's all, I plug-in, let's just use semigroupoids functions!
>
> Or I have MyMonad and I want some Functor, so I just plug-in:
>
>   instance MFunctor MyMonad   --empty
>
> that's all.
> I also need some Applicative! Easy:
>
>   instance MApplicative MyMonad   --empty again
>
> done!
>

Let's see how many lines of code this costs in Haskell 98:

instance Monad MyMonad where { ... }
instance Functor MyMonad where
fmap = liftM
instance Applicative MyMonad where
pure = return
(<*>) = ap

Only three lines more, and they're readable.

I think newclasses are not solving the existing problems, as you're only
removing three well-understood lines of code in the above example, while
people have to look up what you mean by MFunctor and MApplicative.

I think default superclass instances are a much better idea, or
alternatively, the ConstraintSynonymInstances I previously mentioned (but
not both -- they'll probably bite each other).

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


Re: [Haskell-cafe] Newclasses

2013-10-03 Thread Stijn van Drongelen
On Thu, Oct 3, 2013 at 8:16 AM, Wvv  wrote:

> > Your first two cases will be fixed in 7.10, as Applicative finally
> becomes
> a superclass of Monad.
>
> Sure, newclassses not about Applicative and Monads only.
> This question is more wider.
>
> Must Apply be a superclass of Bind?
> Must Bind be a superclass of Monad?
> So, must Monad has 2 superclasses at once: Bind and Applicative?
>
> Must Semigroupoids be a superclass of Category?
> Must Category be a superclass of Arrow?


There is no theoretical problem here, just a practical one. It would be
resolved by solving your 4th problem, for which you don't need newclasses.
Consider:

{-# LANGUAGE ConstraintKinds #-}
class Functor f where { fmap :: (a -> b) -> f a -> f b }
class Functor f => Apply f where { (<*>) :: f (a -> b) -> f a -> f b }
class Apply f => Applicative f where { pure :: a -> f a }
class Apply f => Bind f where { (=<<) :: (a -> f b) -> f a -> f b }

type Monad f = (Applicative f, Bind f)
return :: Monad f => a -> f a
return = pure

I might have made some mistakes in the exact hierarchy, but something like
this should work. There are no problems with having hierarchies like this,
as far as I'm aware.

The current problem is that nobody wants to use this hierarchy: to get a
Monad instance, you have to write four separate instances for your type.
What would be nicer is a feature (ConstraintSynonymInstances?) where
something like this can be written:

instance (Functor Maybe, Apply Maybe, Monad Maybe) where
fmap _ Nothing = Nothing
fmap f (Just x) = Just (f x)

Just f <*> Just x = Just (f x)
_ <*> _ = Nothing

pure = Just

f =<< Just x = f x
_ =<< Nothing = Nothing

This would be sugar for

instance Functor Maybe where { fmap = ... }
instance Apply Maybe where { (<*>) = ... }
instance Monad Maybe where { pure = ... ; (=<<) = ... }

and the last would be sugar for

instance Applicative Maybe where { pure = ... }
instance Bind Maybe where { (=<<) = ... }

You don't need any new keywords for this, because the above does not
conflict with the existing rules for instance declarations.

 > Also, I don't see why it would be a misfeature to have Eq as a superclass
> > of Ord, or Functor as a superclass of Applicative.
> I see 2 reasons:
> 1) class functions in reality don't depend of superclass functions
> 2) Haskell can't check if superclass instance is correspond with class laws


Again, I don't see why that makes it a misfeature.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newclasses

2013-10-02 Thread Stijn van Drongelen
Hi!

Your first two cases will be fixed in 7.10, as Applicative finally becomes
a superclass of Monad. I haven't really looked at your third case, so I
can't comment on that. Your fourth case is something I'd really like to see
solved properly (*together* with a better record system), but as you say,
it could be solved separately.

Also, I don't see why it would be a misfeature to have Eq as a superclass
of Ord, or Functor as a superclass of Applicative.

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


Re: [Haskell-cafe] Any precedent or plan for guaranteed-safe Eq and Ord instances?

2013-10-02 Thread Stijn van Drongelen
On Wed, Oct 2, 2013 at 6:57 PM, Stijn van Drongelen wrote:

>
> On Wed, Oct 2, 2013 at 5:36 PM, Roman Cheplyaka  wrote:
>
>> * Stijn van Drongelen  [2013-10-02 15:46:42+0200]
>> > I do think something has to be done to have an Eq and Ord with more
>> strict
>> > laws.
>> >
>> > * Operators in Eq and Ord diverge iff any of their parameters are
>> bottom.
>>
>> This outlaws the Eq instances of lists, trees, and other (co)recursive
>> types.
>>
>> Furthermore, in this formulation, even Eq for tuples is illegal, because
>>
>>   (undefined, something) == somethingElse
>>
>> is going to diverge.
>>
>> Roman
>>
>
> I knew this was going to bite me in the ass. Let me try again:
>
> * Operators in Eq and Ord may only diverge when any of their parameters
> are bottom.
>

What am I thinking. Scratch that.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Any precedent or plan for guaranteed-safe Eq and Ord instances?

2013-10-02 Thread Stijn van Drongelen
On Wed, Oct 2, 2013 at 4:17 PM, Tom Ellis <
tom-lists-haskell-cafe-2...@jaguarpaw.co.uk> wrote:

> What's the benefit of this requirement, as opposed to, for example
>
>False <= _ = True
>

I was trying to cover for void types, where the only sensible definitions
are

instance Eq Void where
_ == _ = error "void (==)"

instance Ord Void where
_ <= _ = error "void (<=)"

This is because reflexivity must be guaranteed, so undefined == undefined
may not yield False, but I doubt error "foo" == (let x = x in x) should
yield True either. But perhaps this exception deserves its own rule.

On Wed, Oct 2, 2013 at 5:36 PM, Roman Cheplyaka  wrote:

> * Stijn van Drongelen  [2013-10-02 15:46:42+0200]
> > I do think something has to be done to have an Eq and Ord with more
> strict
> > laws.
> >
> > * Operators in Eq and Ord diverge iff any of their parameters are bottom.
>
> This outlaws the Eq instances of lists, trees, and other (co)recursive
> types.
>
> Furthermore, in this formulation, even Eq for tuples is illegal, because
>
>   (undefined, something) == somethingElse
>
> is going to diverge.
>
> Roman
>

I knew this was going to bite me in the ass. Let me try again:

* Operators in Eq and Ord may only diverge when any of their parameters are
bottom.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Any precedent or plan for guaranteed-safe Eq and Ord instances?

2013-10-02 Thread Stijn van Drongelen
On Wed, Oct 2, 2013 at 3:49 PM, Niklas Haas  wrote:

> On Wed, 2 Oct 2013 15:46:42 +0200, Stijn van Drongelen 
> wrote:
> > I do think something has to be done to have an Eq and Ord with more
> strict
> > laws.
> >
> > * Operators in Eq and Ord diverge iff any of their parameters are bottom.
> > * The default definitions of (/=), (<), (>) and `compare` are law.
> > * (==) is reflexive and transitive
> > * (<=) is antisymmetric ((x <= y && y <= x) `implies` (x == y))
> > * (<=) is 'total' (x <= y || y <= x)
> > * (<=) is transitive
> >
> > Currently, reflexivity of (==) is broken in the Prelude (let x = 0/0 in x
> > == x). I know this is for IEEE 754 compliance, but c'mon, this is
> Haskell,
> > we can have better ways of dealing with NaNs.
>
> Like making Double not be an instance of Eq?
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

Like making IEEE754 Doubles not an instance of Eq. Normal and denormal
Doubles should have Eq instances.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Any precedent or plan for guaranteed-safe Eq and Ord instances?

2013-10-02 Thread Stijn van Drongelen
I do think something has to be done to have an Eq and Ord with more strict
laws.

* Operators in Eq and Ord diverge iff any of their parameters are bottom.
* The default definitions of (/=), (<), (>) and `compare` are law.
* (==) is reflexive and transitive
* (<=) is antisymmetric ((x <= y && y <= x) `implies` (x == y))
* (<=) is 'total' (x <= y || y <= x)
* (<=) is transitive

Currently, reflexivity of (==) is broken in the Prelude (let x = 0/0 in x
== x). I know this is for IEEE 754 compliance, but c'mon, this is Haskell,
we can have better ways of dealing with NaNs.

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


Re: [Haskell-cafe] Mystery of an Eq instance

2013-09-24 Thread Stijn van Drongelen
On Tue, Sep 24, 2013 at 5:39 PM, Sven Panne  wrote:

> 2013/9/22 Mike Meyer :
> > On Sat, Sep 21, 2013 at 5:28 PM, Bardur Arantsson 
> > wrote:
> > Trying to make something whose name is "Not A Number" act like a
> > number sounds broken from the start.
>
> The point here is that IEEE floats are actually more something like a
> "Maybe Float", with various "Nothing"s, i.e. the infinities and NaNs,
> which all propagate in a well-defined way.


So, `Either IeeeFault Float`? ;)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Mystery of an Eq instance

2013-09-21 Thread Stijn van Drongelen
On Sep 21, 2013 4:17 PM, "Bob Hutchison"  wrote:
>
>
> On 2013-09-21, at 4:46 AM, Stijn van Drongelen  wrote:
>
>> I do have to agree with Damodar Kulkarni that different laws imply
different classes. However, this will break **a lot** of existing software.
>
>
> You could argue that the existing software is already broken.
>

I agree, but that might also be hardly relevant when fixing an existing
language.

>> If we would do this, only Eq and Ord need to be duplicated, as they
cause most of the problems. Qualified imports should suffice to
differentiate between the two.
>>
>> import qualified Data.Eq.Approximate as A
>> import qualified Data.Ord.Approximate as A
>>
>> main = print $ 3.16227766016837956 A.== 3.16227766016837955
>
>
> As soon as you start doing computations with fp numbers things get much
worse.

Only when you start reasoning about (in)equalities. Really, in (a + b) * c
= a * c + b * c, it isn't + or * that's causing problems, but =.

I'm going to look at Kmett's work and that ltu link when I'm home ;)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Mystery of an Eq instance

2013-09-21 Thread Stijn van Drongelen
On Sat, Sep 21, 2013 at 10:26 AM, Mike Meyer  wrote:

> On Sat, Sep 21, 2013 at 2:21 AM, Bardur Arantsson 
> wrote:
> > On 2013-09-21 06:16, Mike Meyer wrote:
> > >  The single biggest gotcha is that two calculations
> > > we expect to be equal often aren't. As a result of this, we warn
> > > people not to do equality comparison on floats.
> > The Eq instance for Float violates at least one expected law of Eq:
> >
> >   Prelude> let nan = 0/0
> >   Prelude> nan == nan
> >   False
>
>  Yeah, Nan's are a whole 'nother bucket of strange.
>
> But if violating an expected law of a class is a reason to drop it as
> an instance, consider:
>
> Prelude> e > 0
> True
> Prelude> 1 + e > 1
> False
>
> Of course, values "not equal when you expect them to be" breaking
> equality means that they also don't order the way you expect:
>
> Prelude> e + e + 1 > 1 + e + e
> True
>
> So, should Float's also not be an instance of Ord?
>
> I don't think you can turn IEEE 754 floats into a well-behaved numeric
> type. A wrapper around a hardware type for people who want that
> performance and can deal with its quirks should provide access to
> as much of the types behavior as possible, and equality comparison
> is part of IEEE 754 floats.
>
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
I do have to agree with Damodar Kulkarni that different laws imply
different classes. However, this will break **a lot** of existing software.

If we would do this, only Eq and Ord need to be duplicated, as they cause
most of the problems. Qualified imports should suffice to differentiate
between the two.

import qualified Data.Eq.Approximate as A
import qualified Data.Ord.Approximate as A

main = print $ 3.16227766016837956 A.== 3.16227766016837955
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Mystery of an Eq instance

2013-09-21 Thread Stijn van Drongelen
On Sep 21, 2013 9:38 AM, "Colin Adams"  wrote:
>
>
> On 21 September 2013 08:34, Stijn van Drongelen  wrote:
>>
>> * As mentioned, there is a total order (Ord) on floats (which is what
you should be using when checking whether two approximations are
approximately equal), which implies that there is also an equivalence
relation (Eq).
>
>
> how do you get a total order when nan compares false with everything
including itself?

Good point. It should be a partial order.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Mystery of an Eq instance

2013-09-21 Thread Stijn van Drongelen
I think you are trying to solve a problem that doesn't exist.

* Float and Double are imprecise types by their very nature. That's exactly
what people are forgetting, and exactly what's causing misunderstandings.
Perhaps(!) it would be better to remove the option to use rational literals
as floats, and require people to convert rationals using approx ::
(Approximates b a) => a -> b when they want to use FP math (instance
Approximates Float Rational, etc).

* Pure equality tests make perfect sense in a few situations, so Eq is
required. In fact, it's required to have an IEEE754-compliant
implementation.

* As mentioned, there is a total order (Ord) on floats (which is what you
should be using when checking whether two approximations are approximately
equal), which implies that there is also an equivalence relation (Eq).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Mystery of an Eq instance

2013-09-20 Thread Stijn van Drongelen
On Fri, Sep 20, 2013 at 6:17 PM, damodar kulkarni wrote:

> Ok, let's say it is the effect of truncation. But then how do you explain
> this?
>
> Prelude> sqrt 10.0 == 3.1622776601683795
> True
> Prelude> sqrt 10.0 == 3.1622776601683796
> True
>
>
Well, that's easy:

λ: decodeFloat 3.1622776601683795
(7120816245988179,-51)
λ: decodeFloat 3.1622776601683796
(7120816245988179,-51)

On my machine, they are equal. Note that ...4 and ...7 are also equal,
after they are truncated to fit in 53 (which is what `floatDigits 42.0`
tells me) bits (`floatRadix 42.0 == 2`).

Ok, again something like truncation or rounding seems at work but the
> precision rules the GHC is using seem to be elusive, to me.
>

It seems to me that you're not familiar with the intricacies of
floating-point arithmetic. You're not alone, it's one of the top questions
on StackOverflow.

Please find yourself a copy of "What Every Computer Scientist Should Know
About Floating-Point Arithmetic" by David Goldberg, and read it. It should
be very enlightening. It explains a bit about how IEEE754, pretty much the
golden standard for floating point math, defines these precision rules.

But more importantly, if one is advised NOT to test equality of two
> floating point values, what is the point in defining an Eq instance?
>

Although equality is defined in IEEE754, it's not extremely useful after
arithmetic (except perhaps for zero tests). Eq is a superclass of Ord,
however, which is vital to using floating point numbers.

Is the Eq instance there just to make __the floating point types__ members
> of the Num class?
>

That was also a reason before GHC 7.4 (Eq is no longer a superclass of Num).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe