Send Beginners mailing list submissions to
        [email protected]

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        [email protected]

You can reach the person managing the list at
        [email protected]

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  type class functions as function arguments (Christopher Howard)
   2. Re:  type class functions as function arguments (Karl Voelker)
   3.  Problem building monte-carlo package. (Libor Wagner)


----------------------------------------------------------------------

Message: 1
Date: Thu, 13 Sep 2012 19:23:50 -0800
From: Christopher Howard <[email protected]>
Subject: [Haskell-beginners] type class functions as function
        arguments
To: Haskell Beginners <[email protected]>
Message-ID: <[email protected]>
Content-Type: text/plain; charset="iso-8859-1"

In my app, I am trying to save a whole bunch of code duplication by
leverage the fact that functions can be passed in to other functions as
arguments. However, I run into a kink when I try to use functions from
type classes, and then apply those functions to different types of
arguments after the functions have been passed in.

My actual code is rather long and somewhat complicated, so I will use
this simpler example: Obviously both the following functions work fine:

code:
--------
g :: (Integer, Double)
g = ((+) 1 2, (+) 2.0 3.0)

g' :: (Integer, Double)
g' = ((-) 1 2, (-) 2.0 3.0)

*Main> g
(3,5.0)
*Main> g'
(-1,-1.0)
--------

However, what if I want to create a single function, where I just pass
in the (+) or the (-) function? I not sure the right way to do that,
exactly, but I tried something like this:

code:
--------
gCore :: Num a => (a -> a -> a) -> (Integer, Double)
gCore f = (f 1 2, f 2.0 3.0)
--------

The resulting error is:

code:
--------
    Couldn't match type `Double' with `Integer'
    In the return type of a call of `f'
    In the expression: f 1 2
    In the expression: (f 1 2, f 2.0 3.0)
--------

It is as though the function "forgot" that it could be used on different
types, and just picked one, and now is complaining that is being used
with the wrong type in the other case.

-- 
frigidcode.com
indicium.us

-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 551 bytes
Desc: OpenPGP digital signature
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120913/9e9e79df/attachment-0001.pgp>

------------------------------

Message: 2
Date: Thu, 13 Sep 2012 21:16:56 -0700
From: Karl Voelker <[email protected]>
Subject: Re: [Haskell-beginners] type class functions as function
        arguments
To: Christopher Howard <[email protected]>
Cc: Haskell Beginners <[email protected]>
Message-ID:
        <CAFfow0xRd7g=8jhi+G2+vRSXrts=lwukxqhpwc9fwhricdc...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

On Thu, Sep 13, 2012 at 8:23 PM, Christopher Howard <
[email protected]> wrote:

> code:
> --------
> gCore :: Num a => (a -> a -> a) -> (Integer, Double)
> gCore f = (f 1 2, f 2.0 3.0)
> --------
>
> The resulting error is:
>     Couldn't match type `Double' with `Integer'
>     In the return type of a call of `f'
>     In the expression: f 1 2
>     In the expression: (f 1 2, f 2.0 3.0)
>

In standard Haskell, when you write a type signature, there's an implicit
universal quantification of all its type variables:

gCore :: forall a. (Num a => (a -> a -> a) -> (Integer, Double))

The problem comes from the parentheses. You have to get past the forall,
and you can only do that by picking a value for the type variable. Another
way of looking at it is that you aren't actually required to have a
function (a -> a -> a) that works for *all* types a in Num; it only has to
work for whatever type you happened to choose for a. In this case, that's
not useful to you, since (+) is defined for all types a in Num, but
according to this type signature, the caller is able to pick a type a = Foo
and then provide a function of type Foo -> Foo -> Foo.

To get what you want, you need this type signature instead:

gCore :: (forall a. (Num a => (a -> a -> a))) -> (Integer, Double)

Since the forall only covers the type of the parameter, not gCore, the body
of gCore isn't committed to a particular value of a. You only have to
commit to a value of a when using the parameter. This also means that the
person calling gCore has to pass in a function that works for all types a
in Num, rather than just for one, because when they pass that parameter,
the value of a hasn't been chosen yet, since we didn't have to go inside
that forall to get to the point of passing that parameter.

This is not standard Haskell, but it is possible with a language extension
supported by GHC called RankNTypes. (Use -XRankNTypes when running ghc or
ghci.) There are downsides to using this feature which I am not qualified
to fully explain, but the most common problem you'll find is that type
inference fails and an explicit signature is required. (There is also an
extension called Rank2Types which covers this particular case, since the
forall is only one level deeper than normally allowed.)

-Karl
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120913/e42530f1/attachment-0001.htm>

------------------------------

Message: 3
Date: Fri, 14 Sep 2012 09:19:31 +0200
From: Libor Wagner <[email protected]>
Subject: [Haskell-beginners] Problem building monte-carlo package.
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset="utf-8"

Hi,

I have problem building the monte-carlo package 
(http://hackage.haskell.org/package/monte-carlo/). Using both the hackage and 
github (https://github.com/patperry/hs-monte-carlo) version, I have got the 
following error:

lib/Control/Monad/MC/Base.hs:23:24:
Expecting one more argument to `m'
In the class declaration for `MonadMC'

I'm using ghc 7.4.2.

Can someone see the what parameter is missing, because I can't.

Thanks,
Libor

Here is the Base.hs:

{-# LANGUAGE TypeFamilies #-}
-----------------------------------------------------------------------------
-- |
-- Module : Control.Monad.MC.Base
-- Copyright : Copyright (c) 2010, Patrick Perry <[email protected]>
-- License : BSD3
-- Maintainer : Patrick Perry <[email protected]>
-- Stability : experimental
--

module Control.Monad.MC.Base
where

import Control.Monad
import qualified Control.Monad.MC.GSLBase as GSL

import qualified Data.Vector.Storable as VS

class HasRNG m where
-- | The random number generator type for the monad.
type RNG m

class (Monad m, HasRNG m) => MonadMC m where
-- | Get the current random number generator.
getRNG :: m (RNG m)

-- | Set the current random number generator.
setRNG :: RNG m -> m ()

-- | @uniform a b@ generates a value uniformly distributed in @[a,b)@.
uniform :: Double -> Double -> m Double

-- | @uniformInt n@ generates an integer uniformly in the range @[0,n-1]@.
-- It is an error to call this function with a non-positive value.
uniformInt :: Int -> m Int

-- | @normal mu sigma@ generates a Normal random variable with mean
-- @mu@ and standard deviation @sigma@.
normal :: Double -> Double -> m Double

-- | @exponential mu@ generates an Exponential variate with mean @mu@.
exponential :: Double -> m Double

-- | @levy c alpha@ gets a Levy alpha-stable variate with scale @c@ and
-- exponent @alpha@. The algorithm only works for @0 < alpha <= 2@.
levy :: Double -> Double -> m Double

-- | @levySkew c alpha beta @ gets a skew Levy alpha-stable variate
-- with scale @c@, exponent @alpha@, and skewness @beta@. The skew
-- parameter must lie in the range @[-1,1]@. The algorithm only works
-- for @0 < alpha <= 2@.
levySkew :: Double -> Double -> Double -> m Double

-- | @poisson mu@ generates a Poisson random variable with mean @mu@.
poisson :: Double -> m Int

-- | @cauchy a@ generates a Cauchy random variable with scale
-- parameter @a@.
cauchy :: Double -> m Double

-- | @beta a b@ generates a beta random variable with
-- parameters @a@ and @b@.
beta :: Double -> Double -> m Double

-- | @logistic a@ generates a logistic random variable with
-- parameter @a@.
logistic :: Double -> m Double

-- | @pareto a b@ generates a Pareto random variable with
-- exponent @a@ and scale @b@.
pareto :: Double -> Double -> m Double

-- | @weibull a b@ generates a Weibull random variable with
-- scale @a@ and exponent @b@.
weibull :: Double -> Double -> m Double

-- | @gamma a b@ generates a gamma random variable with
-- parameters @a@ and @b@.
gamma :: Double -> Double -> m Double

-- | @multinomial n ps@ generates a multinomial random
-- variable with parameters @ps@ formed by @n@ trials.
multinomial :: Int -> VS.Vector Double -> m (VS.Vector Int)

-- | @dirichlet alphas@ generates a Dirichlet random variable
-- with parameters @alphas@.
dirichlet :: VS.Vector Double -> m (VS.Vector Double)

-- | Get the baton from the Monte Carlo monad without performing any
-- computations. Useful but dangerous.
unsafeInterleaveMC :: m a -> m a


-- | Generate 'True' events with the given probability
bernoulli :: (MonadMC m) => Double -> m Bool
bernoulli p = liftM (< p) $ uniform 0 1
{-# INLINE bernoulli #-}

------------------------------- Instances -----------------------------------

instance HasRNG GSL.MC where
type RNG GSL.MC = GSL.RNG

instance MonadMC GSL.MC where
getRNG = GSL.getRNG
{-# INLINE getRNG #-}
setRNG = GSL.setRNG
{-# INLINE setRNG #-}
uniform = GSL.uniform
{-# INLINE uniform #-}
uniformInt = GSL.uniformInt
{-# INLINE uniformInt #-}
normal = GSL.normal
{-# INLINE normal #-}
exponential = GSL.exponential
{-# INLINE exponential #-}
levy = GSL.levy
{-# INLINE levy #-}
levySkew = GSL.levySkew
{-# INLINE levySkew #-}
poisson = GSL.poisson
{-# INLINE poisson #-}
cauchy = GSL.cauchy
{-# INLINE cauchy #-}
beta = GSL.beta
{-# INLINE beta #-}
logistic = GSL.logistic
{-# INLINE logistic #-}
pareto = GSL.pareto
{-# INLINE pareto #-}
weibull = GSL.weibull
{-# INLINE weibull #-}
gamma = GSL.gamma
{-# INLINE gamma #-}
multinomial = GSL.multinomial
{-# INLINE multinomial #-}
dirichlet = GSL.dirichlet
{-# INLINE dirichlet #-}
unsafeInterleaveMC = GSL.unsafeInterleaveMC
{-# INLINE unsafeInterleaveMC #-}

instance (Monad m) => HasRNG (GSL.MCT m) where
type RNG (GSL.MCT m) = GSL.RNG

instance (Monad m) => MonadMC (GSL.MCT m) where
getRNG = GSL.liftMCT GSL.getRNG
{-# INLINE getRNG #-}
setRNG r = GSL.liftMCT $ GSL.setRNG r
{-# INLINE setRNG #-}
uniform a b = GSL.liftMCT $ GSL.uniform a b
{-# INLINE uniform #-}
uniformInt n = GSL.liftMCT $ GSL.uniformInt n
{-# INLINE uniformInt #-}
normal mu sigma = GSL.liftMCT $ GSL.normal mu sigma
{-# INLINE normal #-}
exponential mu = GSL.liftMCT $ GSL.exponential mu
{-# INLINE exponential #-}
levy c alpha = GSL.liftMCT $ GSL.levy c alpha
{-# INLINE levy #-}
levySkew c alpha beta_ = GSL.liftMCT $ GSL.levySkew c alpha beta_
{-# INLINE levySkew #-}
poisson mu = GSL.liftMCT $ GSL.poisson mu
{-# INLINE poisson #-}
cauchy a = GSL.liftMCT $ GSL.cauchy a
{-# INLINE cauchy #-}
beta a b = GSL.liftMCT $ GSL.beta a b
{-# INLINE beta #-}
logistic a = GSL.liftMCT $ GSL.logistic a
{-# INLINE logistic #-}
pareto a b = GSL.liftMCT $ GSL.pareto a b
{-# INLINE pareto #-}
weibull a b = GSL.liftMCT $ GSL.weibull a b
{-# INLINE weibull #-}
gamma a b = GSL.liftMCT $ GSL.gamma a b
{-# INLINE gamma #-}
multinomial n ps = GSL.liftMCT $ GSL.multinomial n ps
{-# INLINE multinomial #-}
dirichlet alphas = GSL.liftMCT $ GSL.dirichlet alphas
{-# INLINE dirichlet #-}
unsafeInterleaveMC = GSL.unsafeInterleaveMCT
{-# INLINE unsafeInterleaveMC #-}







------------------------------

_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 51, Issue 21
*****************************************

Reply via email to