Re: [Haskell-cafe] ghc -O2 and HUnit weirdness

2011-01-06 Thread Jürgen Doser
El jue, 06-01-2011 a las 16:41 -0400, Joey Hess escribió:
 So, the problem seems to be that ghc -O2 somehow optimises the static
 assertBool _ True away, in what seems to be a bad way. Remove the -O2 and
 the test fails as expected. Presumably, although I have not verified,
 less static boolean values would not trigger the optimisation.
 Is this a ghc or HUnit bug? 
 
 (Versions: 6.12.1, 1.2.2.1)

Looks like a GHC bug. The following code mimics what HUnit does:

--
import Control.Exception as E
import Data.Typeable

data Fail = Fail deriving (Show)
instance Typeable Fail where typeOf _ = mkTyConApp (mkTyCon Fail) []
instance Exception Fail

t = (E.throw Fail  return Nothing) `E.catch` (\Fail - return $ Just Fail)

main = do a - t
  print a
--

it runs fine with -O0, but produces an internal error when compiled with -O1 or 
-O2:

$ ghc --make  -O2 t.hs
[1 of 1] Compiling Main ( t.hs, t.o )
Linking t ...
$ ./t
t: internal error: PAP object entered!
(GHC version 6.12.1 for i386_unknown_linux)
Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

It looks like the following bug:
http://hackage.haskell.org/trac/ghc/ticket/3959

I don't have a newer GHC version installed, though, so I can't test if it works 
in a newer GHC. 

Jürgen



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


Re: [Haskell-cafe] example in All about Monads

2010-09-17 Thread Jürgen Doser
El sáb, 18-09-2010 a las 00:48 +0800, ender escribió:
 
 my question is, why not define the function father and mother as type
 of father::Maybe Sheep - Maybe Sheep? this can also
 clean the code and it avoid the additional function comb
 
The composition of these functions would then be nice, yes. However, you
would have to duplicate the ugly handling of Nothings in each of the
functions father, mother, sister, brother, etc.:

father Nothing = Nothing
father (Just x) = ...

And you would still need a function of type Sheep - Maybe Sheep, to
fill in the dots.

 
 further more, why we need a function = with type of = m a - ( a -
 m b ) - mb? define some function with type m a - m b can solve these
 problems too.

Look at the the type m a - (a - m b) - m b in a slightly different
way, namely by flipping its arguments. You get:

(a - m b) - (m a - m b)

i.e., it transforms a function of type a - m b into one of type m a -
m b, which can then be composed by (.). Given that we want to be able to
deal with function of type a - m b, This is exactly what we want.
The usually given type m a - (a - m b) - m b is just a convention
because of the closer correspondence to the do-notation.

Jürgen

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


Re: [Haskell-cafe] Weird behavior with arrow commands

2010-07-24 Thread Jürgen Doser
El vie, 23-07-2010 a las 23:27 -0400, Ronald Guida escribió:
 I am trying to figure out how to use GHC's arrow commands, and I found
 some extremely weird behavior.

CC'ed to ghc-users, because this may be a ghc bug.

 In GHC's manual, there is a description of arrow commands, which I
 don't really understand.
 http://www.haskell.org/ghc/docs/latest/html/users_guide/arrow-notation.html#id667303
 (Primitive Constructs)
 
 I have two questions:
 1. What are arrow commands supposed to do?
 2. What is this code supposed to do?
 
 -- start of code --
 
 {-# LANGUAGE Arrows #-}
 module Main where
 
 import Control.Arrow
 
 foo :: (b - String) - b, Int), Float), Double) - String) - (b - 
 String)
 foo f g b = f b ++   ++ g (((b, 8), 1.0), 6.0)
 
 bar :: (t - String) - ((Double, Int) - String) - t - String
 bar f g  = proc x - do
   (f - x) `foo` \n m - g - (n)
 
 main = do
   putStrLn $ foo show show 17
   putStrLn $ bar show show 17
   putStrLn $ foo show show 42
   putStrLn $ bar show show 42
 
 -- end of code --
 
 Output from GHCi:
 
 17 (((17,8),1.0),6.0)
 17 (6.730326920298707e-306,0)
 42 (((42,8),1.0),6.0)
 42 (6.730326920298707e-306,0)
 
 Output after compiling with GHC:
 
 17 (((17,8),1.0),6.0)
 17 (5.858736684536801e-270,0)
 42 (((42,8),1.0),6.0)
 42 (5.858736684536801e-270,0)
 
 GHC Version:
 The Glorious Glasgow Haskell Compilation System, version 6.12.3


This seems to be a bug in ghc. First, let's fix bar to give the full
three arguments (Int, Float, Double)  to g:

bar f g  = proc x - do
  (f - x) `foo` (\n m k - g - (n,m,k))

ghc infers the type:

bar :: (t - String) - ((Double, Float, Int) - String) - t - String

and we see that the argument order in the second argument to bar is
reversed. But the arguments are still given to bar in the order (Int,
Float, Double). For example, the 6.0 in foo is interpreted as an Int and
outputs a 0 (the first 32 bits in such a small double are zeros).
When one varies the numbers in foo, one can see the effects in bar. Can
someone from GHC HQ confirm my understanding, or is this just not
supposed to work with multiple arguments?

Jürgen


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


Re: [Haskell-cafe] HaTeX build failure

2010-07-23 Thread Jürgen Doser
El vie, 23-07-2010 a las 16:53 +0400, Alexey Khudyakov escribió:
 On Fri, Jul 23, 2010 at 4:04 PM, Daniel Díaz lazy.dd...@gmail.com wrote:
  Hi,
 
  I uploaded a package, named HaTeX, to Hackage, but it gets a build failure:
 
  Any idea?
 
 Cabal file has BOM in the beginning. Maybe it make parser choke...

http://hackage.haskell.org/trac/hackage/ticket/533 claims that this bug
is fixed, however, removing the BOM does indeed help here.

Someone will have to fix this on the hackage server, I guess.

Jürgen

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


Re: [Haskell-cafe] Heavy lift-ing

2010-07-23 Thread Jürgen Doser
El vie, 23-07-2010 a las 15:05 -0400, Nick Bowler escribió:
 On 11:43 Fri 23 Jul , michael rice wrote:
 [...]
  But how does one add [0,1] and [0,2] to get [0,2,1,3]?
 
 liftM2 (+) [0,1] [0,2] gives the list
 
   [0+0, 0+2, 1+0, 1+2]

which one could have found out by asking ghci:

Prelude Control.Monad let f a b = show a ++  +  ++ show b
Prelude Control.Monad liftM2 f [0,1] [0,2]
[0 + 0,0 + 2,1 + 0,1 + 2]

or simpler:

Prelude Control.Monad liftM2 (,) [0,1] [2,3]
[(0,2),(0,3),(1,2),(1,3)]

i.e., the in the list monad, you pair each element of one list with each
element of the other(s).

 (recall that (=) in the list monad is concatMap).

(=) = flip concatMap, to be precise. Or, concatMap = (=)

Now let's have some fun with equational reasoning to see what liftM2
does exactly: (Only read this if you really want to!)

liftM2 f a b 

= { definition of liftM2 }

do {x - a; y - b; return (f x y)}

= { simplified translation of do-notation }

a = \x - (b = \y - return (f x y))

= { change (=) to (=) and flip arguments }

(\x - ((\y - return (f x y)) = b)) = a 

= { specialized to the list monad }

(\x - ((\y - [f x y])) `concatMap` b)) `concatMap` a 

= { change concatMap to prefix application }

concatMap (\x - concatMap (\y - [x+y]) b) a

and indeed:

Prelude concatMap (\x - concatMap (\y - [x+y]) [0,2]) [0,1]
[0,2,1,3]

with some effort, I think one can understand what happens here. It
should also be clear how this is generalized to liftM3, liftM4, etc. 

Oh, btw, what about liftM1? Obviously, this should be the following:

liftM1 f a

= { definition }

do { x - a ; return f a }
  
= { same changes as above }

concatMap (\x - [f x]) a

= { definition of concatMap }

concat (map (\x - [f x]) a

= { concating singletons can be simplified } 

map (\x - f x) a

= { eta-reduction }

map f a

i.e., liftM1 = map, which is indeed just fmap for lists, as already
pointed out.

You can use this to simplify the last line of the concatMap derivation
above:

concatMap (\x - concatMap (\y - [x+y]) b) a

= { see above }

concatMap (\x - map (\y - x+y) b) a

= { use operator section }

concatMap (\x - map (x+) b) a

which is about as clear as possible a definition for liftM2 (+)


Jürgen



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


Re: [Haskell-cafe] Heavy lift-ing

2010-07-23 Thread Jürgen Doser
El vie, 23-07-2010 a las 16:35 -0700, michael rice escribió:
 Thanks all,
 
 Wild, at least up to the optional part, which I haven't dug into
 yet.
 
 So the (+) for the Maybe monad and the (+) for the List monad are one
 in the same, the magic springs from the monads.
 
 Why is it called lift-ing?


g :: m a - m b - m c
   /\
  /||\
   ||
   ||
f ::   a -   b -   c


liftM2 lifts the function f and transforms it into the function g =
liftM2 f. 

Does that picture help?

Jürgen

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


Re: [Haskell-cafe] Function to find a substring

2010-06-08 Thread Jürgen Doser
El dom, 06-06-2010 a las 15:51 +, R J escribió:
 What's an elegant definition of a Haskell function that takes two
 strings and returns Nothing in case the first string isn't a
 substring of the first, or Just i, where i is the index number of
 the position within the first string where the second string begins?
 
import Data.List

f a b = findIndex (a `isPrefixOf`) (tails b)


Jürgen

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


Re: [Haskell-cafe] Removing alternate items from a list

2010-06-08 Thread Jürgen Doser
El dom, 06-06-2010 a las 14:46 +, R J escribió:
 What's the cleanest definition for a function f :: [a] - [a] that
 takes a list and returns the same list, with alternate items removed?
  e.g., f [0, 1, 2, 3, 4, 5] = [1,3,5]?

adding another suggestion:

import Data.Either(rights)

f = rights . zipWith ($) (cycle [Left,Right])

Jürgen



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