[Haskell-beginners] Ambiguous type error: multiparam class + type alias
Baa
aquagnu at gmail.com
Thu Sep 28 07:17:23 UTC 2017
David, hello again!
Interesting is that class with one parameter is fine:
class Repr a where
type ReprAs a
reprx :: a -> ReprAs a
instance Repr Int where
type ReprAs Int = Int
reprx n = n
main = do
let n = 5 :: Int
print $ (reprx n)
but when I added 2nd param, I get ambogouse error again:
class Repr a b where
type ReprAs a b
repr :: a -> ReprAs a b
instance Repr Int AsTitle where
type ReprAs Int AsTitle = String
repr n = show n
main = do
let n = 5 :: Int
print $ (repr n::ReprAs Int AsTitle)
which looks the same as with type-alias: GHC says:
30 12 error error:
• Couldn't match type ‘ReprAs Int b0’ with ‘String’
Expected type: ReprAs Int AsTitle
Actual type: ReprAs Int b0
The type variable ‘b0’ is ambiguous
• In the second argument of ‘($)’, namely
‘(repr n :: ReprAs Int AsTitle)’
In a stmt of a 'do' block: print $ (repr n :: ReprAs Int AsTitle)
In the expression:
do { let n = ...;
print $ (repr n :: ReprAs Int AsTitle) } (intero)
looks that `type ReprAs Int AsTitle` is treating type-alias and GHC can
not match resulting `String` with `ReprAs Int AsTitle`.
As I understand, the root of the problem is that class parameters are
not the same as in results' parameters (contraposition types) - they
turn out to be free/unbound (execuse my English).
For example, to avoid this problem in the class I added extension:
{-# LANGUAGE AllowAmbiguousTypes #-}
I don't know is a way in Haskell to say to reuse already bound class
parameters in "methods" bodies... I found this:
https://stackoverflow.com/questions/4174187/reading-and-representing-input-which-specifies-the-data-type-to-use/4174266#4174266
Another variant which is compiling (w/ func-deps):
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
data AsShow
data AsTitle
type ReprAs a = String
class Repr a b | a -> b where
repr :: a -> ReprAs b
instance Repr Int AsTitle where
repr n = "a number '" ++ show n ++ "'"
-- instance Repr Int AsShow where
-- repr n = "a number '" ++ show n ++ "'"
main = do
let n = 5 :: Int
print $ (repr n::ReprAs AsTitle)
print $ (repr n::ReprAs AsShow)
but due to `a -> b` it's impossible to instantiate another `Repr Int`!
So, I think soultion is in:
- func deps
- or type families/associative types
But unfortunately my knowledge of Haskell is limited to find it. I see
only that I need to add another param to func dep of class - to
"extend" dependency which allows to determine result type not only on
one input argument's type...
Thanks David!
===
Best regards, Paul
> The reason is because 'type' is a type alias that changes nothing code
> wise, it is merely a visual clue to the reader of code that these two
> types are the same. You could replace 'Repr AsTitle' with 'String'
> and you would get the exact same error.
>
> That said I do think you can do what you want with type families, but
> I'm not having luck giving you a complete solution at this time. This
> would be a good question to ask on stackoverflow if no one here gives
> a satisfactory answer. Here is the code I had that doesn't quite
> work, although I'm not sure why. Maybe you can figure it out. I
> would love to know.
>
> {-# LANGUAGE TypeFamilies, MultiParamTypeClasses #-}
>
> data AsShow
> data AsTitle
>
> class Repr a b where
> type ReprC a b :: *
> repr :: a -> ReprC a b
>
> instance Repr Int AsTitle where
> type ReprC Int AsTitle = String
> repr n = show n
>
> main = do
> let n = 5 :: Int
> print $ (repr n)
>
> On Wed, Sep 27, 2017 at 11:50 AM, Baa <aquagnu at gmail.com> wrote:
> > Hello, List!
> >
> > The further - the more interesting... For example, I want own
> > `Show` analogue, which will be parameterized with type meaning
> > "context"/"reason". So, to represent title of the value I will call:
> >
> > repr x::TitleRepr
> >
> > or simple `Show`:
> >
> > repr x::ShowRepr
> >
> > or
> >
> > repr x::Repr AsShow
> >
> > etc. I try:
> >
> > {-# LANGUAGE AllowAmbiguousTypes #-}
> > {-# LANGUAGE MultiParamTypeClasses #-}
> >
> > data AsShow
> > data AsTitle
> >
> > type Repr a = String
> >
> > class ReprC a b where
> > repr :: a -> Repr b
> >
> > instance ReprC Int AsTitle where
> > repr n = "a number " ++ show n
> >
> > main = do
> > let n = 5 :: Int
> > print $ (repr n :: Repr AsTitle)
> >
> > and sure I get error:
> >
> > • Ambiguous type variable ‘b0’ arising from a use of ‘repr’
> > prevents the constraint ‘(ReprC Int b0)’ from being solved.
> > Probable fix: use a type annotation to specify what ‘b0’
> > should be. These potential instance exist:
> > instance ReprC Int AsTitle
> > -- Defined
> > at .../.stack-work/intero/intero31144sPV.hs:12:10 • In the second
> > argument of ‘($)’, namely ‘(repr n :: Repr AsTitle)’
> > In a stmt of a 'do' block: print $ (repr n :: Repr AsTitle)
> > In the expression:
> > do { let n = ...;
> > print $ (repr n :: Repr AsTitle) } (intero)
> >
> > Sure, I can use as `Repr` not type-alias but `newtype`. But in this
> > case I will need additional call (show/runRepr/coerce/etc.):
> >
> > coerce $ (repr x::AsTitle)
> >
> > So, what is the reason that GHCI is see that `repr n` is `::Repr
> > AsTitle` (AsTitle!!) and says me that `b0` is ambigous?! It should
> > know what concreate `repr` I mean! :) If I use `newtype` - no
> > problem, so I suppose problem is in the type alias. It's not
> > sterling type for such goal, right?
> >
> > Another question is: how to accomplish such goal, i.e. without to
> > make additional call (coerce/show/runRepr/etc) when `repr` will
> > return `String`, wrapped in newtype?
> >
> >
> > PS. Execuse such silly and training example. Actually, I planned to
> > made such class and to use it instead of `Show`. Sure, it can be
> > splitted to several classed (my current state) but.. example is to
> > learn Haskell and to understand my errors...
> >
> >
> > ===
> > Best regards, Paul
> > _______________________________________________
> > Beginners mailing list
> > Beginners at haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
More information about the Beginners
mailing list