[Haskell-beginners] Ambogous error in returning value

David McBride toad3k at gmail.com
Tue Sep 26 12:50:57 UTC 2017


The problem in the class is that it doesn't necessarily know that
(allows opts) and (crit a allows opts) necessarily are working on the
exact same Flt instance. (allows opts) could return [Foo], and but
crit is constrainted by the argument passed to it which is the a in
question.  The fact that there is only one possible instance right now
does not change the fact that there could be more in the future.
denied is already constrained because its return value is used as an
argument of crit.  To fix it

{-# LANGUAGE ScopedTypeVariables #-}
class Flt a where
    ....
    where
       allowed = if null $ (allows opts :: [a]) then True else a
`crit` (allows opts)
       denied = if null $ (denies opts :: [a]) then False else (a ::
a) `crit` (denies opts)

When you see an error Flt a1 does not match Flt a, that's a classic
sign that it doesn't know a1 and a are the same type.

As for the instance it has the exact same problem.  If you were to
pull allowed into its own function outside the class you could
constrain both functions at the same time, at the cost of some
verbosity.

{-# LANGUAGE ScopedTypeVariables #-}
class Flt a where
  ...
  flt opts a = allowed2 opts a && not denied

instance Flt MyType where
  ...
  flt opts a = allowed2 opts a && not denied

allowed2 :: forall a. Flt a => FltOpts -> a -> Bool
allowed2 opts a = if null $ (allows opts :: [a]) then True else a
`crit` (allows opts)


On Mon, Sep 25, 2017 at 6:06 AM, Baa <aquagnu at gmail.com> wrote:
> Hello, everyone.
>
> Considering, I have a class:
>
>   class Flt a where
>     allows :: FltOpts -> [a]
>     denies :: FltOpts -> [a]
>     crit :: a -> [a] -> Bool
>     flt :: FltOpts -> a -> Bool
>     flt opts a = allowed && not denied
>       where allowed = if null $ allows opts then True else a `crit` (allows opts)
>             denied = if null $ denies opts then False else a `crit` (denies opts)
>
> I get error here:
>
>      • Could not deduce (Flt a1) arising from a use of ‘allows’
>        from the context: Flt a
>          bound by the class declaration for ‘Flt’
>          at .../.stack-work/intero/intero5319V42.hs:(31,1)-(38,97)
>        The type variable ‘a1’ is ambiguous
>        These potential instance exist:
>          instance Flt MyType
>            -- Defined at ...
>      • In the second argument of ‘($)’, namely ‘allows opts’
>        ....................................................
>
> As I understand, GHC can not deduce type if it's a return's value
> (contraposition?). OK, but it knows its type: it is `[a]`! What is the
> problem to keep `flt` method as a generic, i.e. without concreate type,
> but only `[a]` ?
>
> Second, I implemented instance:
>
>   instance Flt MyType where
>     allows = ...
>     denies = ...
>     flt opts a = allowed && not denied
>       where allowed = if null $ (allows opts::[MyType]) then True else a `crit` (allows opts)
>             denied = if null $ (denies opts::[MyType]) then False else a `crit` (denies opts)
>
> and without this explicite type annotation of `allows opts` I get again
> ambigous error. But why? GHC knows that `allows` returns `[a]` and `a`
> is `MyType`, so `[a]` is `[MyType]`. Why I need to write it explicitly?
> May be I need some extension here?
>
>
> ===
> Best regards, Paul
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


More information about the Beginners mailing list