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

2013-09-24 Thread Sven Panne
2013/9/22 Mike Meyer m...@mired.org:
 On Sat, Sep 21, 2013 at 5:28 PM, Bardur Arantsson s...@scientician.net
 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 Nothings, i.e. the infinities and NaNs,
which all propagate in a well-defined way. Basically a monad built
into your CPU's FP unit. ;-)

 I just went back through the thread, and the only examples I could
 find where that happened (as opposed to where floating point
 calculations or literals resulted in unexpected values) was with
 NaNs. Just out of curiosity, do you know of any that don't involve
 NaNs?

Well, with IEEE arithmetic almost nothing you learned in school about
math holds anymore. Apart from rounding errors, NaNs and infinities,
-0 is another fun part:

   x * (-1)

is not the same as

   0 - x

(Hint: Try with x == 0 and use recip on the result.)

 Float violates the expected behavior of instances of - well, pretty
 much everything it's an instance of. Even if you restrict yourself to
 working with integer values that can be represented as floats.  If
 we're going to start removing it as an instance for violating instance
 expectations, we might as well take it out of the numeric stack (or
 the language) completely.

Exactly, and I am sure 99.999% of all people wouldn't like that
removal. Learn IEEE arithmetic, hate it, and deal with it. Or use
something different, which is probably several magnitudes slower. :-/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Hackathon der Frankfurt-Haskell-User-Group

2013-09-24 Thread Peter Althainz
the Frankfurt Haskell User Group announces its first Hackathon, if
interested, see here:
http://www.meetup.com/Frankfurt-Haskell-User-Group/events/138895112/

Peter Althainz
___
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 svenpa...@gmail.com wrote:

 2013/9/22 Mike Meyer m...@mired.org:
  On Sat, Sep 21, 2013 at 5:28 PM, Bardur Arantsson s...@scientician.net
  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 Nothings, 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


[Haskell-cafe] Why superclass' instances are bad idea?

2013-09-24 Thread Wvv
I suggest to add superclass' instances into  libraries.

http://ghc.haskell.org/trac/ghc/ticket/8348

In brief, we could write next:

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}

instance Monad m = Applicative m where
pure  = return
(*) = ap
   
instance Monad m = Functor m where
fmap = liftM

instance Monad m = Bind m where
(-) = flip (=)
B.join = M.join

this code is valid! 

I've already defined 3 superclassses for Monad: Functor, Applicative and
Bind!

Similar idea said Edward Kmett in 2010 (founded by monoidal) (
http://stackoverflow.com/questions/3213490/how-do-i-write-if-typeclass-a-then-a-is-also-an-instance-of-b-by-this-definit/3216937#3216937
)

And he said but effectively what this instance is saying is that every
Applicative should be derived by first finding an instance for Monad, and
then dispatching to it. So while it would have the intention of saying that
every Monad is Applicative (by the way the implication-like = reads) what
it actually says is that every Applicative is a Monad, because having an
instance head 't' matches any type. In many ways, the syntax for 'instance'
and 'class' definitions is backwards.

Why? I don't understand.
Not every Applicative is a Monad, but every Monad is Applicative



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/Why-superclass-instances-are-bad-idea-tp5737056.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
___
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 John Lato
On Tue, Sep 24, 2013 at 11:36 AM, Stijn van Drongelen rhym...@gmail.comwrote:

 On Tue, Sep 24, 2013 at 5:39 PM, Sven Panne svenpa...@gmail.com wrote:

 2013/9/22 Mike Meyer m...@mired.org:
  On Sat, Sep 21, 2013 at 5:28 PM, Bardur Arantsson s...@scientician.net
 
  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 Nothings, i.e. the infinities and NaNs,
 which all propagate in a well-defined way.


 So, `Either IeeeFault Float`? ;)


Sort of, but IeeeFault isn't really a zero.   Sometimes they can get back
to a normal Float value:

  Prelude let x = 1.0/0
  Prelude x
  Infinity
  Prelude 1/x
  0.0

Also, IEEE float support doesn't make sense as a library, it needs to be
built into the compiler (ignoring extensible compiler support via the
FFI).  The whole point of IEEE floats is that they're very fast, but in
order to take advantage of that the compiler needs to know about them in
order to use the proper CPU instructions.  Certainly you could emulate them
in software, but then they'd no longer be fast, so there'd be no point to
it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with HXT `when`

2013-09-24 Thread Albert Y. C. Lai

On 13-09-21 05:13 AM, Vlatko Basic wrote:

I'd like to extract A texts from row with header Caption, and have
come up with this

runX $ doc
  (deep (hasName tr)   --
filter only TRs
 withTraceLevel 5 traceTree   --
shows correct TR
`when`
  deep (
 hasName th 
-- filter THs with specified text
 getChildren  hasText (==Caption)
  ) -- inner deep
   getChildren  hasName td -- shouldn't here be only
one TR?
   getChildren
   )
   getName  (getChildren  getText)  -- list has TDs
from all three TRs


Operator precedences:
   infixr 1
  `when` infixl 9 (default)

Therefore, this expression redundantly parenthesized and systematically 
indented to ensure that you are on the same page with the computer is:


runX $
doc

( deep (hasName tr)
  
-- begin{conditionally prints but otherwise is arr id}
  ( withTraceLevel 5 traceTree
`when`
deep ( hasName th
   
   getChildren
   
   hasText (==Caption)
 ) -- inner deep
  )
-- end{conditionally prints but otherwise is arr id}
  
  getChildren
  
  hasName td
  
  getChildren
)

( getName  (getChildren  getText) )

The condition on thCaption/th ends up controlling trace messages 
only; it is not used to limit real processing.


when doesn't help even when used correctly: it doesn't ban data. 
guards and containing ban data, but you have to put them at the 
right place, i.e., parenthesize correctly.


runX $
doc

( deep ( hasName tr
 `containing`
 deep ( hasName th

getChildren

hasText (==Caption)
  )
   )
  
  getChildren
  
  hasName td
  
  getChildren
)

( getName
  
  (getChildren  getText)
)

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


[Haskell-cafe] Hackage 2 switchover imminent

2013-09-24 Thread Duncan Coutts
Hi everyone,

Having been running the Hackage 2 alpha  beta for several months we
intend to do the final switchover tomorrow (Wednesday 25th Sept).

This will involve disabling uploads to the old server for a few hours.
If all goes well we will switch the DNS over. If anything goes wrong
we will just re-enable the old server.

After the switch, everyone with a hackage account will need to do a
one-time self-service account upgrade. A small handful of hackage
early adopters will need assistance from an administrator to upgrade
their accounts. We will email these people individually with
instructions.

If you wish to help or keep an eye on the switchover process then you
are welcome to join us on the #hackage IRC channel on Freenode.

If you run into problems after the switch there are site
administrators you can contact and there is an issue tracker. Please
report bugs in the site issue tracker:

https://github.com/haskell/hackage-server/issues

For issues with accounts or permissions please contact the
administrators by email at adm...@hackage.haskell.org

-- 
Duncan Coutts, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why superclass' instances are bad idea?

2013-09-24 Thread John Lato
This line

instance Monad m = Applicative m where

tells the compiler Every type (of the appropriate kind) is an instance of
Applicative.  And it needs to have a Monad instance as well.

That's what Edward means when he said that it means every Applicative is a
Monad.  Theoretically the statement makes no sense, but that's what this
instance head means.  Everything is Applicative, and it also needs a Monad
instance to use that Applicative.

Consider what happens for something that isn't a Monad, e.g. ZipList.
Since it's not a Monad, it would need its own instance

instance Applicative ZipList where
...

But now you'd need to enable OverlappingInstances, because ZipList matches
both this instance and the general one you've defined above (GHC doesn't
consider constraints when matching instance heads).  OverlappingInstances
is much more problematic than the other extensions because it could (and
almost certainly would in this case) give rise to incoherence (see the
warning under
http://www.haskell.org/ghc/docs/latest/html/users_guide/type-class-extensions.html#instance-overlap
).

You might want to read the wiki page on default superclass instances (
http://ghc.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances) for
further discussion of this problem.

John L.

On Tue, Sep 24, 2013 at 12:17 PM, Wvv vite...@rambler.ru wrote:

 I suggest to add superclass' instances into  libraries.

 http://ghc.haskell.org/trac/ghc/ticket/8348

 In brief, we could write next:

 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE UndecidableInstances #-}
 
 instance Monad m = Applicative m where
 pure  = return
 (*) = ap
 
 instance Monad m = Functor m where
 fmap = liftM
 
 instance Monad m = Bind m where
 (-) = flip (=)
 B.join = M.join

 this code is valid!

 I've already defined 3 superclassses for Monad: Functor, Applicative and
 Bind!

 Similar idea said Edward Kmett in 2010 (founded by monoidal) (

 http://stackoverflow.com/questions/3213490/how-do-i-write-if-typeclass-a-then-a-is-also-an-instance-of-b-by-this-definit/3216937#3216937
 )

 And he said but effectively what this instance is saying is that every
 Applicative should be derived by first finding an instance for Monad, and
 then dispatching to it. So while it would have the intention of saying that
 every Monad is Applicative (by the way the implication-like = reads) what
 it actually says is that every Applicative is a Monad, because having an
 instance head 't' matches any type. In many ways, the syntax for 'instance'
 and 'class' definitions is backwards.

 Why? I don't understand.
 Not every Applicative is a Monad, but every Monad is Applicative



 --
 View this message in context:
 http://haskell.1045720.n5.nabble.com/Why-superclass-instances-are-bad-idea-tp5737056.html
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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