Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

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


Today's Topics:

   1.  why is ScopedTypeVariables not fixing this       error? (Dennis Raddle)
   2. Re:  why is ScopedTypeVariables not fixing this   error?
      (Michael Snoyman)
   3. Re:  why is ScopedTypeVariables not fixing this   error?
      (Dennis Raddle)


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

Message: 1
Date: Tue, 9 Oct 2018 01:45:18 -0700
From: Dennis Raddle <dennis.rad...@gmail.com>
To: Haskell Beginners <beginners@haskell.org>
Subject: [Haskell-beginners] why is ScopedTypeVariables not fixing
        this    error?
Message-ID:
        <CAKxLvoqky5U=5jgkbtjaavaf_f-ckgbmipktww_6xrgyh2q...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

In the following snippet from a program in progress (designed to compute
percentile rank for arbitrary lists of values) , I was hoping to declare
types of functions within the main function just as a way of helping myself
catch type errors. I'm getting the error "Can't match 'a' with 'a1'....
where 'a' is rigid type variable... etc. etc." on the line indicated in the
comment below. The usual error I get when I try to do this without
ScopedTypeVariables. So, I thought that ScopedTypeVariables was supposed to
allow this kind of usage. What am I doing wrong?


{-# LANGUAGE ScopedTypeVariables #-}

import qualified Data.Map as M
import qualified Data.List as L
import Data.Map(Map)
import Data.Function

-- <percent at or below> <percent below>
data PercentileData = PercentileData Double Double

-- new attempt, October 2018: using new PercentileData construct to
-- represent percentile in both ways. (at/below, or below)
computePercentile :: Ord a => Map a Double -> Map a PercentileData
computePercentile dataIn = error "foo"
  where
    pairs :: [(a,Double)]  -- THIS IS THE LINE GETTING THE ERROR
    pairs = L.sortBy (compare `on` snd) $ M.toList dataIn
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20181009/43a118c2/attachment-0001.html>

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

Message: 2
Date: Tue, 9 Oct 2018 11:48:56 +0300
From: Michael Snoyman <mich...@snoyman.com>
To: Beginners <beginners@haskell.org>
Subject: Re: [Haskell-beginners] why is ScopedTypeVariables not fixing
        this    error?
Message-ID:
        <CAKT9ecPqA=2BTk594SL5rHun=gl-0zjuthxy9zzcqohdboe...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

You need to put a `forall a.` in front of the `Ord a` constraint. To quote
the manual on the language extension[1]

> Enable lexical scoping of type variables explicitly introduced with forall
.

If it helps, the requirement of forall to be able to refer to the variable
was non-obvious to me the first time I tried to use the extension.

[1]
https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html#ghc-flag--XScopedTypeVariables

On Tue, Oct 9, 2018 at 11:45 AM Dennis Raddle <dennis.rad...@gmail.com>
wrote:

> In the following snippet from a program in progress (designed to compute
> percentile rank for arbitrary lists of values) , I was hoping to declare
> types of functions within the main function just as a way of helping myself
> catch type errors. I'm getting the error "Can't match 'a' with 'a1'....
> where 'a' is rigid type variable... etc. etc." on the line indicated in the
> comment below. The usual error I get when I try to do this without
> ScopedTypeVariables. So, I thought that ScopedTypeVariables was supposed to
> allow this kind of usage. What am I doing wrong?
>
>
> {-# LANGUAGE ScopedTypeVariables #-}
>
> import qualified Data.Map as M
> import qualified Data.List as L
> import Data.Map(Map)
> import Data.Function
>
> -- <percent at or below> <percent below>
> data PercentileData = PercentileData Double Double
>
> -- new attempt, October 2018: using new PercentileData construct to
> -- represent percentile in both ways. (at/below, or below)
> computePercentile :: Ord a => Map a Double -> Map a PercentileData
> computePercentile dataIn = error "foo"
>   where
>     pairs :: [(a,Double)]  -- THIS IS THE LINE GETTING THE ERROR
>     pairs = L.sortBy (compare `on` snd) $ M.toList dataIn
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20181009/49432b69/attachment-0001.html>

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

Message: 3
Date: Tue, 9 Oct 2018 01:55:00 -0700
From: Dennis Raddle <dennis.rad...@gmail.com>
To: Haskell Beginners <beginners@haskell.org>
Subject: Re: [Haskell-beginners] why is ScopedTypeVariables not fixing
        this    error?
Message-ID:
        <CAKxLvorVN2Def+2QsZdDiH7ao-6f=ibj=drr3nrwdwq189w...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

That was easy. Thanks. I actually tried putting forall a in front of the
line getting the error, but to no avail. Now fixed.

D

On Tue, Oct 9, 2018 at 1:49 AM Michael Snoyman <mich...@snoyman.com> wrote:

> You need to put a `forall a.` in front of the `Ord a` constraint. To quote
> the manual on the language extension[1]
>
> > Enable lexical scoping of type variables explicitly introduced with
> forall.
>
> If it helps, the requirement of forall to be able to refer to the variable
> was non-obvious to me the first time I tried to use the extension.
>
> [1]
> https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html#ghc-flag--XScopedTypeVariables
>
> On Tue, Oct 9, 2018 at 11:45 AM Dennis Raddle <dennis.rad...@gmail.com>
> wrote:
>
>> In the following snippet from a program in progress (designed to compute
>> percentile rank for arbitrary lists of values) , I was hoping to declare
>> types of functions within the main function just as a way of helping myself
>> catch type errors. I'm getting the error "Can't match 'a' with 'a1'....
>> where 'a' is rigid type variable... etc. etc." on the line indicated in the
>> comment below. The usual error I get when I try to do this without
>> ScopedTypeVariables. So, I thought that ScopedTypeVariables was supposed to
>> allow this kind of usage. What am I doing wrong?
>>
>>
>> {-# LANGUAGE ScopedTypeVariables #-}
>>
>> import qualified Data.Map as M
>> import qualified Data.List as L
>> import Data.Map(Map)
>> import Data.Function
>>
>> -- <percent at or below> <percent below>
>> data PercentileData = PercentileData Double Double
>>
>> -- new attempt, October 2018: using new PercentileData construct to
>> -- represent percentile in both ways. (at/below, or below)
>> computePercentile :: Ord a => Map a Double -> Map a PercentileData
>> computePercentile dataIn = error "foo"
>>   where
>>     pairs :: [(a,Double)]  -- THIS IS THE LINE GETTING THE ERROR
>>     pairs = L.sortBy (compare `on` snd) $ M.toList dataIn
>>
>> _______________________________________________
>> Beginners mailing list
>> Beginners@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20181009/49b31e67/attachment-0001.html>

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

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


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

End of Beginners Digest, Vol 124, Issue 6
*****************************************

Reply via email to