Better alternative for implementing a Monoid

I was playing around with implementing a simple parser for some stuff in Haskell and got to the point where most o the basic functionality works (more or less) and I wanted to add some extra stuff for displaying the errors.

Long story short, I realized that for implementing the Monoid type class I first needed to implement the Semigroup, and this is the best way to implement it that I could come up with. I like it, but it feels kind of ugly having to reference mempty from inside the Semigroup instance definition. Is there a prettier way to implement those type classes?

Appreciate all comments in advance!

data ParserError = ExpectedChar Char Char          -- expected CHAR(1) but was CHAR(2)
                 | ExpectedEOL Char                -- expected EOL but was CHAR(1)
                 | UnexpectedEOL Char              -- expected CHAR(1) but was EOL
                 -- Special errors:
                 | EmptyError                      -- for the applicative to work
                 | AggregationError [ParserError]  -- several errors occured (ex. during alternative)

instance Semigroup ParserError where
    mempty <> e = e
    e <> mempty = e
    (AggregationError e1) <> (AggregationError e2) = AggregationError (e1 ++ e2)
    (AggregationError e1) <> e2 = AggregationError (e1 ++ [e2])
    e1 <> (AggregationError e2) = AggregationError (e1 : e2)
    e1 <> e2 = AggregationError [e1, e2]

instance Monoid ParserError where
    mempty = EmptyError
1 Like

I don’t think your Semigroup definitions do what you think they do.
The first definition of <> matches on everything.

instance Semigroup ParserError where
    mempty <> e = ...
    ^^^^^^ -- This is the name of the left argument,
           -- not a pattern match on your `mempty` definition.
           -- Might as well have been called `memptyArg` or `_`.

You can only pattern match on data constructors, so you’ll have to use the constructor which will act as the mempty. In this case the EmptyError. (i.e. EmptyError <> e = e)

2 Likes

Yeah, that makes sense. A previous version of my code used EmptyError but i changed it later, because I thought that would work as well. I should have checked that my “tests” kept working before changing that.

Apart from that, is there something else I can do to make that look/feel better?

I would suggest, if you can, changing your types to take advantage of an existing Monoid instead of implementing your own:

data SingleParserError
  = ExpectedChar Char Char          -- expected CHAR(1) but was CHAR(2)
  | ExpectedEOL Char                -- expected EOL but was CHAR(1)
  | UnexpectedEOL Char              -- expected CHAR(1) but was EOL
type ParserError = [SingleParserError]

p.s. If you need ParserError to have instances that [] doesn’t have, use a newtype instead:

newtype ParserError = ParserError [SingleParserError]
  deriving (Semigroup, Monoid)
2 Likes

It sounds like you want something like Data.Validation, though I’m not sure how your parser is defined, so I’m not sure how to adjust it to get it to do what you want it to do.

If you’re just trying to make a Semigroup/Monoid instance for the heck of it, then yeah, go for it (though you’ve not defined all the possibilities yet, e.g. ExpectedEOL c <> UnexpectedEOL c = ???)

Like @rhendric mentioned, it feels like you’d want to just have the type of error your parser can give and put it in a collection that makes sense for your parser. (e.g. [], DList, Seq, etc.)

1 Like

Using your original definition,

(<>) = \x y -> AggregationError [x,y]
mempty = AggregationError []

is fine as long as you deem nested AggregationErrors as semantically equivalent to an aggregation flattened into a single list. You can remove EmptyError and use AggregationError [] instead, or make a pattern out of it.

flattenError :: ParseError -> ParseError
flattenError (AggregationError agg) = AggregationError (go =<< agg)
  where 
    go :: ParseError -> [ParseError]
    go (AggregationError agg') = go =<< agg'
    go e = [e]
flattenError e = e

Assuming your parser type is something like Parser = StateT UnparsedInput (Except ParseError), observe that there are instances

(Functor m, MonadPlus m) => Alternative (StateT s m)
(Monad m, Monoid e) => MonadPlus (ExceptT e m)

so the mtl package provides all the instances you need.

1 Like