
Hello, Sylvain. Your solution assumes that I need to pass `@_ @AsTitle` anywhere where I call `repr`? So, instead of `repr n::AsTitle` or `repr n::Something AsTitle` (depends on implementation) I'll write `repr @_ @AsTitle n`, right?
You only add a constraint as follows: repr n :: forall b. (Repr b ~ Repr AsTitle, ReprC Int b) => Repr b
Yes... So, `b` is unbound/free type param. But I can bind it with func. deps, yes? === Best regards, Paul
But as we have seen, it doesn't imply (b ~ AsTitle) and b remains ambiguous.
A solution is to fix b explicitly with a type application:
{-# LANGUAGE TypeApplications #-} ... repr @_ @AsTitle n
Best regards, Sylvain
On 27/09/2017 17:50, Baa 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@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