Problem with multi param typeclasses and Monoid deduction

Hi all, sorry for the bad title, I was unable to finde a better one.

I have problems making an idea work which I think should be possible, but maybe my mental model of types, type classes, Haskell or GHC is wrong.

Something that works

I have a type class HasText a which says that Text can be extracted from an a, a type class Sections a b which says that a section list of bs can be extracted from a:

class HasText a where
 text :: a -> Text

-- MultiParamTypeClasses enabled
class Sections a b where
 sections :: a -> [b]

and these trivial instances:

newtype PlainText   = PT {plainText :: Text}
newtype SectionText = ST {textSections :: [PlainText]}

instance HasText PlainText where
  text = plainText
instance Sections SectionText PlainText where
  sections = textSections

I’d like to have a HasText instance for SectionText too, by external concatenation:

instance Semigroup PlainText where
  pt1 <> pt2 = PT $ plainText pt1 <> plainText pt2
instance Monoid PlainText where
  mempty = PT empty

instance HasText SectionText where
  text = text . mconcat . (sections :: SectionText -> [PlainText])

This does the right thing™:

λ> text $ ST $ PT . pack <$> Prelude.words "foo bar baz"
"foobarbaz"

What I would like to have

What happens with other HasText and Sections instances? I thought I would be able to define a generalized HasText for everything that has Sections with HasText and Monoid:

instance (Sections a b, HasText b, Monoid b) => HasText a where
  text = text . mconcat . (sections :: a -> [b])

How it fails

HLS first tells me to enable FlexibleInstances, UndecidableInstances, AllowAmbiguousTypes and finally tells me

• Could not deduce (Sections a1 b1)
    arising from a use of ‘sections’
  from the context: (Sections a b, HasText b, Monoid b)
    bound by the instance declaration
    at HasText.hs:33:10-57
  Possible fix:
    add (Sections a1 b1) to the context of
      an expression type signature:
        forall a1 b1. a1 -> [b1]
• In the second argument of ‘(.)’, namely ‘(sections :: a -> [b])’
  In the second argument of ‘(.)’, namely
    ‘mconcat . (sections :: a -> [b])’
  In the expression: text . mconcat . (sections :: a -> [b])

I don’t understand the error neither the possible fix. Can someone explain this to me? :slight_smile: Thank you very much!

I think the problem is that a and b in the annotation of sections are not the same a and b in the type class instance. To allow this, activate ScopedTypeVariables extension. i’ve tried and it compiles

To clarify a little bit. Without scoped type variables, your code is equivalent to this:

instance (Sections a b, HasText b, Monoid b) => HasText a where
  text = text . mconcat . (sections :: c -> [d])

So c and d are completely unkown, therefore it can’t deduce instances for them, which is the error shown by ghc

2 Likes

Indeed, it works and your explanation makes sense to me! Thank you!

However, trying to use this instance (without the explicit HasText SectionText instance), I get this error message and I don’t know how to fix this without an explicit type annotation.

λ> text $ ST $ PT . pack <$> Prelude.words "foo bar baz"

<interactive>:1:1: error:
    • Ambiguous type variable ‘b0’ arising from a use of ‘text’
      prevents the constraint ‘(Sections
                                  SectionText b0)’ from being solved.
      Probable fix: use a type annotation to specify what ‘b0’ should be.
      These potential instance exist:
        instance [safe] Sections SectionText PlainText
          -- Defined at HasText.hs:22:10
    • In the first argument of ‘($)’, namely ‘text’
      In the expression:
        text $ ST $ PT . pack <$> Prelude.words "foo bar baz"
      In an equation for ‘it’:
          it = text $ ST $ PT . pack <$> Prelude.words "foo bar baz"

I am ot that expert on ghc type system (even less, with all the extensions, so double check my answer) but I think a type annotation is unavoiable here, since you may have different instances. For example

-- you could have defined SectionText with more fields
newtype PlainText   = PT {plainText :: Text}
data SectionText = ST {textSections :: [PlainText], unpackedSections :: [String]}

-- and define instances for them
instance HasText String where
  text = Text.pack
instance Sections SectionText String where
  sections = unpackedSections

-- which section must this function choose? 
-- the one on the first field or the second field?
value :: Text
value = text (some_section_text :: SectionText)

-- here is clear that we want the second section
value' :: Sections SectionText String => Text
value' = text (some_section_text :: SectionText)

It happens that your current code has one and only one possible option, but I don’t think the compiler is happy saying this could be many things, but because at this precise moment in time there is one possible choice, then I am gonna pick that one. I think you can do this using FunctionalDependencies extension which actually serve to this purpose, but at the cost of not being able to define more sections for your data type

The only possible instance is actually shown by the compiler:

My strong advice to anyone is to not define type classes unless absolutely necessary. I don’t see any need here. Just define

textPlain :: PlainText -> Text
textSection :: SectionText -> Text
sections :: SectionText -> [PlainText]
liftText :: Monoid b => (a -> [b]) -> (b -> Text) -> a -> Text
liftText sections text = text . mconcat . sections

and then compose those as needed. You’ll just tie yourself in knots if you try to use the type class system for this.

Once you’ve succeeded with the type-class-free approach you may find that it’s necessary to introduce type classes to reduce boilerplate. But by then you’ll have plenty of experience doing the plumbing by hand so you’ll be able to design the type classes more effectively.

2 Likes

Thank you very much! That sounds reasonable, but I have to investigate. :slight_smile:

Thank you. I understand, but of course the situation presented by me is a little bit simplified. These are type classes because in the future there will be many concrete types and it would feel wrong to define instances for all of them with the same code.