Re: [Haskell-cafe] a code that cannot compile with or without NoMonomorphismRestriction

2012-03-30 Thread Denis Moskvin
f :: (Show a, Ord b) = (a - String, b - b - Bool)
f = let commond_definitions = undefined in
let f1 = id.show
f2 x = ( x)
in
  (f1, f2)

 From: Ting Lei tin...@hotmail.com
 To: haskell-cafe@haskell.org
 Cc:
 Date: Wed, 28 Mar 2012 23:42:30 -0700
 Subject: [Haskell-cafe] a code that cannot compile with or without
 NoMonomorphismRestriction
 Hi

 I have met a piece of code that cannot be compiled whether I add or remove
 the NoMonomorphismRestriction flag (as of GHC 7.0.4, Haskell platform
 2011.4.0.0).
 I have extracted a minimal example below:



 {-# LANGUAGE NoMonomorphismRestriction #-}
 (f1, f2) =
     let commond_definitions = undefined in
     let f1 = id.show
     f2 x = ( x)
     in
   (f1, f2)

 I needed this format because there are many shared definitions in
 common_definitions for f1 and f2, and I want to keep them local.

 If I compile them with NoMonomorphismRestriction, I get:

 D:\work\test.hs:7:8:
     Ambiguous type variable `a0' in the constraint:
   (Show a0) arising from a use of `f1'
     Possible cause: the monomorphism restriction applied to the following:
   f1 :: a0 - String (bound at D:\work\hsOcaml\test.hs:2:2)
     Probable fix: give these definition(s) an explicit type signature
     In the expression: f1
     In the expression: (f1, f2)
     In the expression:
   let
     f1 = id . show
     f2 x = ( x)
   in (f1, f2)
 D:\work\test.hs:7:12:
     Ambiguous type variable `a1' in the constraint:
   (Ord a1) arising from a use of `f2'
     Possible cause: the monomorphism restriction applied to the following:
   f2 :: a1 - a1 - Bool (bound at D:\work\hsOcaml\test.hs:2:6)
     Probable fix: give these definition(s) an explicit type signature
     In the expression: f2
     In the expression: (f1, f2)
     In the expression:
   let
     f1 = id . show
     f2 x = ( x)
   in (f1, f2)
 Failed, modules loaded: none.

 If I comment out
 -- {-# LANGUAGE NoMonomorphismRestriction #-}
 I get:

 D:\work\hsOcaml\test.hs:4:17:
     Ambiguous type variable `a0' in the constraint:
   (Show a0) arising from a use of `show'
     Possible cause: the monomorphism restriction applied to the following:
   f1 :: a0 - String (bound at D:\work\hsOcaml\test.hs:2:2)
     Probable fix: give these definition(s) an explicit type signature
   or use -XNoMonomorphismRestriction
     In the second argument of `(.)', namely `show'
     In the expression: id . show
     In an equation for `f1': f1 = id . show
 D:\work\hsOcaml\test.hs:7:12:
     Ambiguous type variable `a1' in the constraint:
   (Ord a1) arising from a use of `f2'
     Possible cause: the monomorphism restriction applied to the following:
   f2 :: a1 - a1 - Bool (bound at D:\work\hsOcaml\test.hs:2:6)
     Probable fix: give these definition(s) an explicit type signature
   or use -XNoMonomorphismRestriction
     In the expression: f2
     In the expression: (f1, f2)
     In the expression:
   let
     f1 = id . show
     f2 x = ( x)
   in (f1, f2)
 Failed, modules loaded: none.

 Can anyone show me why this does not work and how to fix it (e.g. by
 adding type signature as the error message suggested)?
 I tried to add type signature by couldn't figure out the right way of
 doing it.

 Thanks in advance!

 Ting

Denis Moskvin

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


[Haskell-cafe] a code that cannot compile with or without NoMonomorphismRestriction

2012-03-29 Thread Ting Lei




Hi I have met a piece of code that cannot be compiled whether I add or remove 
the NoMonomorphismRestriction flag (as of GHC 7.0.4, Haskell platform 
2011.4.0.0).I have extracted a minimal example below:   {-# LANGUAGE 
NoMonomorphismRestriction #-}
(f1, f2) =
let commond_definitions = undefined in
let f1 = id.show 
f2 x = ( x) 
in
  (f1, f2) I needed this format because there are many shared definitions 
in common_definitions for f1 and f2, and I want to keep them local. If I 
compile them with NoMonomorphismRestriction, I get:
D:\work\test.hs:7:8:
Ambiguous type variable `a0' in the constraint:
  (Show a0) arising from a use of `f1'
Possible cause: the monomorphism restriction applied to the following:
  f1 :: a0 - String (bound at D:\work\hsOcaml\test.hs:2:2)
Probable fix: give these definition(s) an explicit type signature
In the expression: f1
In the expression: (f1, f2)
In the expression:
  let
f1 = id . show
f2 x = ( x)
  in (f1, f2)D:\work\test.hs:7:12:
Ambiguous type variable `a1' in the constraint:
  (Ord a1) arising from a use of `f2'
Possible cause: the monomorphism restriction applied to the following:
  f2 :: a1 - a1 - Bool (bound at D:\work\hsOcaml\test.hs:2:6)
Probable fix: give these definition(s) an explicit type signature
In the expression: f2
In the expression: (f1, f2)
In the expression:
  let
f1 = id . show
f2 x = ( x)
  in (f1, f2)
Failed, modules loaded: none. If I comment out  -- {-# LANGUAGE 
NoMonomorphismRestriction #-}
I get:
D:\work\hsOcaml\test.hs:4:17:
Ambiguous type variable `a0' in the constraint:
  (Show a0) arising from a use of `show'
Possible cause: the monomorphism restriction applied to the following:
  f1 :: a0 - String (bound at D:\work\hsOcaml\test.hs:2:2)
Probable fix: give these definition(s) an explicit type signature
  or use -XNoMonomorphismRestriction
In the second argument of `(.)', namely `show'
In the expression: id . show
In an equation for `f1': f1 = id . showD:\work\hsOcaml\test.hs:7:12:
Ambiguous type variable `a1' in the constraint:
  (Ord a1) arising from a use of `f2'
Possible cause: the monomorphism restriction applied to the following:
  f2 :: a1 - a1 - Bool (bound at D:\work\hsOcaml\test.hs:2:6)
Probable fix: give these definition(s) an explicit type signature
  or use -XNoMonomorphismRestriction
In the expression: f2
In the expression: (f1, f2)
In the expression:
  let
f1 = id . show
f2 x = ( x)
  in (f1, f2)
Failed, modules loaded: none. Can anyone show me why this does not work and how 
to fix it (e.g. by adding type signature as the error message suggested)?I 
tried to add type signature by couldn't figure out the right way of doing it. 
Thanks in advance! Ting  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] a code that cannot compile with or without NoMonomorphismRestriction

2012-03-29 Thread Ketil Malde
Ting Lei tin...@hotmail.com writes:

 (f1, f2) =
 let commond_definitions = undefined in
 let f1 = id.show 
 f2 x = ( x) 
 in
   (f1, f2)

I think the type signatures should be:

  f1 :: Show a = a - String

and 

  f2 :: Ord b = b - b - Bool 

When I define these separately, this works:

  f1 :: Show a = a - String
  f1 = id . show

  f2 :: Ord b = b - b - Bool 
  f2 = flip ()


But when I define them as a pair

  f1 :: Show a = a - String
  f2 :: Ord b = b - b - Bool 
  (f1,f2) = (id . show, flip ())

I get an error message:

Line 9: 1 error(s), 0 warning(s)

Couldn't match expected type `forall a. Show a = a - String'
with actual type `a - String'
When checking that `f1'
  has the specified type `forall a1. Show a1 = a1 - String'

Defining the pair at once works:

  p :: (Show a, Ord b) = (a - String, b - b - Bool)
  p = (id . show, flip ())

I guess that didn't help a lot, somebody with deeper GHC-fu than me will
have to step in.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] a code that cannot compile with or without NoMonomorphismRestriction

2012-03-29 Thread Heinrich Apfelmus

Ketil Malde wrote:

Ting Lei tin...@hotmail.com writes:


(f1, f2) =
let commond_definitions = undefined in
let f1 = id.show 
f2 x = ( x) 
in

  (f1, f2)


I think the type signatures should be:

  f1 :: Show a = a - String

and 

  f2 :: Ord b = b - b - Bool 


When I define these separately, this works:

  f1 :: Show a = a - String
  f1 = id . show

  f2 :: Ord b = b - b - Bool 
  f2 = flip ()



But when I define them as a pair

  f1 :: Show a = a - String
  f2 :: Ord b = b - b - Bool 
  (f1,f2) = (id . show, flip ())


I get an error message:

Line 9: 1 error(s), 0 warning(s)

Couldn't match expected type `forall a. Show a = a - String'
with actual type `a - String'
When checking that `f1'
  has the specified type `forall a1. Show a1 = a1 - String'

Defining the pair at once works:

  p :: (Show a, Ord b) = (a - String, b - b - Bool)
  p = (id . show, flip ())

I guess that didn't help a lot, somebody with deeper GHC-fu than me will
have to step in.


The problem is that f1 and f2 are polymorphic functions. To put 
polymorphic functions in a pair, you need *impredicative polymorphism*.



Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


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


Re: [Haskell-cafe] a code that cannot compile with or without NoMonomorphismRestriction

2012-03-29 Thread Haisheng Wu
I think the error message tell you how to fix:
   use -XNoMonomorphismRestriction
One approach is add following line into top of your hs file and it works for me.
   {-# LANGUAGE NoMonomorphismRestriction #-}

Regarding the deeper reason, I think you would be able to find via GHC
user guide and google.

-Haisheng


On Thu, Mar 29, 2012 at 2:42 PM, Ting Lei tin...@hotmail.com wrote:
 Hi

 I have met a piece of code that cannot be compiled whether I add or remove
 the NoMonomorphismRestriction flag (as of GHC 7.0.4, Haskell platform
 2011.4.0.0).
 I have extracted a minimal example below:



 {-# LANGUAGE NoMonomorphismRestriction #-}
 (f1, f2) =
     let commond_definitions = undefined in
     let f1 = id.show
     f2 x = ( x)
     in
   (f1, f2)

 I needed this format because there are many shared definitions in
 common_definitions for f1 and f2, and I want to keep them local.

 If I compile them with NoMonomorphismRestriction, I get:

 D:\work\test.hs:7:8:
     Ambiguous type variable `a0' in the constraint:
   (Show a0) arising from a use of `f1'
     Possible cause: the monomorphism restriction applied to the following:
   f1 :: a0 - String (bound at D:\work\hsOcaml\test.hs:2:2)
     Probable fix: give these definition(s) an explicit type signature
     In the expression: f1
     In the expression: (f1, f2)
     In the expression:
   let
     f1 = id . show
     f2 x = ( x)
   in (f1, f2)
 D:\work\test.hs:7:12:
     Ambiguous type variable `a1' in the constraint:
   (Ord a1) arising from a use of `f2'
     Possible cause: the monomorphism restriction applied to the following:
   f2 :: a1 - a1 - Bool (bound at D:\work\hsOcaml\test.hs:2:6)
     Probable fix: give these definition(s) an explicit type signature
     In the expression: f2
     In the expression: (f1, f2)
     In the expression:
   let
     f1 = id . show
     f2 x = ( x)
   in (f1, f2)
 Failed, modules loaded: none.

 If I comment out
 -- {-# LANGUAGE NoMonomorphismRestriction #-}
 I get:

 D:\work\hsOcaml\test.hs:4:17:
     Ambiguous type variable `a0' in the constraint:
   (Show a0) arising from a use of `show'
     Possible cause: the monomorphism restriction applied to the following:
   f1 :: a0 - String (bound at D:\work\hsOcaml\test.hs:2:2)
     Probable fix: give these definition(s) an explicit type signature
   or use -XNoMonomorphismRestriction
     In the second argument of `(.)', namely `show'
     In the expression: id . show
     In an equation for `f1': f1 = id . show
 D:\work\hsOcaml\test.hs:7:12:
     Ambiguous type variable `a1' in the constraint:
   (Ord a1) arising from a use of `f2'
     Possible cause: the monomorphism restriction applied to the following:
   f2 :: a1 - a1 - Bool (bound at D:\work\hsOcaml\test.hs:2:6)
     Probable fix: give these definition(s) an explicit type signature
   or use -XNoMonomorphismRestriction
     In the expression: f2
     In the expression: (f1, f2)
     In the expression:
   let
     f1 = id . show
     f2 x = ( x)
   in (f1, f2)
 Failed, modules loaded: none.

 Can anyone show me why this does not work and how to fix it (e.g. by adding
 type signature as the error message suggested)?
 I tried to add type signature by couldn't figure out the right way of doing
 it.

 Thanks in advance!

 Ting


 ___
 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


Re: [Haskell-cafe] a code that cannot compile with or without NoMonomorphismRestriction

2012-03-29 Thread Ting Lei

Ketil, Thanks for the response. It seems that defining them as a pair only 
postphones the error.GHC will give an error when you extract the components of 
the pair, no matter whether you addthe NoMonomorphismRestriction flag or not. 
--{-# LANGUAGE NoMonomorphismRestriction #-}p :: (Show a, Ord b) = (a - 
String, b - b - Bool)
p = (id . show, flip ())f1 = fst p
f2 = snd p---Without NoMonomorphismRestriction, I got:
D:\work\test1.hs:6:10:
Ambiguous type variable `a0' in the constraint:
  (Show a0) arising from a use of `p'
Possible cause: the monomorphism restriction applied to the following:
  f1 :: a0 - String (bound at D:\work\hsOcaml\test1.hs:6:1)
Probable fix: give these definition(s) an explicit type signature
  or use -XNoMonomorphismRestriction
In the first argument of `fst', namely `p'
In the expression: fst p
In an equation for `f1': f1 = fst pD:\work\hsOcaml\test1.hs:6:10:
Ambiguous type variable `b0' in the constraint:
  (Ord b0) arising from a use of `p'
Probable fix: add a type signature that fixes these type variable(s)
.. Failed, modules loaded: none. --With 
NoMonomorphismRestriction, I got: 
D:\work\test1.hs:6:10:
Ambiguous type variable `b0' in the constraint:
  (Ord b0) arising from a use of `p'
Probable fix: add a type signature that fixes these type variable(s)
In the first argument of `fst', namely `p'
In the expression: fst p
In an equation for `f1': f1 = fst pD:\work\test1.hs:7:10:
Ambiguous type variable `a0' in the constraint:
  (Show a0) arising from a use of `p'
Probable fix: add a type signature that fixes these type variable(s)
In the first argument of `snd', namely `p'
In the expression: snd p
In an equation for `f2': f2 = snd p
Failed, modules loaded: none.  Thanks,
 Ting  From: ke...@malde.org
 To: tin...@hotmail.com
 CC: haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] a code that cannot compile with or without 
 NoMonomorphismRestriction
 Date: Thu, 29 Mar 2012 12:27:04 +0200
 
 Ting Lei tin...@hotmail.com writes:
 
  (f1, f2) =
  let commond_definitions = undefined in
  let f1 = id.show 
  f2 x = ( x) 
  in
(f1, f2)
 
 I think the type signatures should be:
 
   f1 :: Show a = a - String
 
 and 
 
   f2 :: Ord b = b - b - Bool 
 
 When I define these separately, this works:
 
   f1 :: Show a = a - String
   f1 = id . show
 
   f2 :: Ord b = b - b - Bool 
   f2 = flip ()
 
 
 But when I define them as a pair
 
   f1 :: Show a = a - String
   f2 :: Ord b = b - b - Bool 
   (f1,f2) = (id . show, flip ())
 
 I get an error message:
 
 Line 9: 1 error(s), 0 warning(s)
 
 Couldn't match expected type `forall a. Show a = a - String'
 with actual type `a - String'
 When checking that `f1'
   has the specified type `forall a1. Show a1 = a1 - String'
 
 Defining the pair at once works:
 
   p :: (Show a, Ord b) = (a - String, b - b - Bool)
   p = (id . show, flip ())
 
 I guess that didn't help a lot, somebody with deeper GHC-fu than me will
 have to step in.
 
 -k
 -- 
 If I haven't seen further, it is by standing in the footprints of giants
  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe