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


Re: [Haskell-cafe] Are there arithmetic composition of functions?

2012-03-20 Thread Denis Moskvin


 From: Felipe Almeida Lessa felipe.le...@gmail.com
 To: sdiy...@sjtu.edu.cn
 Cc: haskell-cafe@haskell.org
 Date: Mon, 19 Mar 2012 14:24:13 -0300
 Subject: Re: [Haskell-cafe] Are there arithmetic composition of functions?
 import Control.Applicative

 f, g :: Float - Float
 f x = x + 1
 g x = 2 * x

 h = (+) $ f * g


 Cheers, =)

 --
 Felipe.


Monadic version:

import Control.Monad
import Control.Monad.Instances

(+.) :: Num a = (a - a) - (a - a) - a - a
(+.) = liftM2 (+)
(+..) :: Num a = (a - a - a) - (a - a - a) - a - a - a
(+..) = liftM2 $ liftM2 (+)
infixl 6 +., +..


 (sin +. cos) (pi/4)
1.414213562373095
  ((*) +.. (/)) 4 2
10.0

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


[Haskell-cafe] Const vs Constant types

2011-11-19 Thread Denis Moskvin
Is there any rationale for coexistence of

newtype Const a b = Const { getConst :: a }

from Control.Applicative and

newtype Constant a b = Constant { getConstant :: a }

from Data.Functor.Constant (transformers package)?


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