Search code examples
haskelltypeclassmonoids

Why is my Semigroup/Monoid instance overlapping?


I'm trying to implement a way to lazily construct nondeterministic finite automata (NFAs). I did this years ago in F# and now want to try it with Haskell while leveraging the Monoid typeclass.

{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}

module NFA where

data State = State Match State | Split State State | Final deriving (Show)
data Match = Any | Char Char | ... deriving (Show)

type StateF = State -> State

complete :: StateF -> State -> State
complete statef exit = statef exit

connect :: StateF -> StateF -> StateF
connect fst snd = complete fst . complete snd

empty :: StateF
empty = id

instance Semigroup StateF where
  (<>) = connect

instance Monoid StateF where
  mempty = empty

This code doesn't compile, because my Semigroup and Monoid instances are overlapping with instance Semigroup b => Semigroup (a -> b) and instance Monoid b => Monoid (a -> b) from GHC.Base, but I don't understand why.

I see that there is a Monoid instance on functions a -> b, where b is a Monoid itself. But State doesn't have a Monoid instance, so how can StateF (State -> State) overlap?

Is it because someone might implement Monoid for State elsewhere?

Also, how can I fix this?

I'm aware that a could just define StateF as...

data StateF = StateF (State -> State)

...but that would also increase syntax noise when pattern matching and constructing StateFs.

The comiler errors:

src\NFA.hs:10:10: error:
    * Overlapping instances for Semigroup StateF
        arising from a use of `GHC.Base.$dmsconcat'
      Matching instances:
        instance Semigroup b => Semigroup (a -> b) -- Defined in `GHC.Base'
        instance Semigroup StateF -- Defined at src\NFA.hs:10:10
    * In the expression: GHC.Base.$dmsconcat @(StateF)
      In an equation for `GHC.Base.sconcat':
          GHC.Base.sconcat = GHC.Base.$dmsconcat @(StateF)
      In the instance declaration for `Semigroup StateF'
   |
10 | instance Semigroup StateF where
   |          ^^^^^^^^^^^^^^^^

src\NFA.hs:10:10: error:
    * Overlapping instances for Semigroup StateF
        arising from a use of `GHC.Base.$dmstimes'
      Matching instances:
        instance Semigroup b => Semigroup (a -> b) -- Defined in `GHC.Base'
        instance Semigroup StateF -- Defined at src\NFA.hs:10:10
    * In the expression: GHC.Base.$dmstimes @(StateF)
      In an equation for `GHC.Base.stimes':
          GHC.Base.stimes = GHC.Base.$dmstimes @(StateF)
      In the instance declaration for `Semigroup StateF'
   |
10 | instance Semigroup StateF where
   |          ^^^^^^^^^^^^^^^^

src\NFA.hs:13:10: error:
    * Overlapping instances for Semigroup StateF
        arising from the superclasses of an instance declaration
      Matching instances:
        instance Semigroup b => Semigroup (a -> b) -- Defined in `GHC.Base'
        instance Semigroup StateF -- Defined at src\NFA.hs:10:10
    * In the instance declaration for `Monoid StateF'
   |
13 | instance Monoid StateF where
   |          ^^^^^^^^^^^^^

src\NFA.hs:13:10: error:
    * Overlapping instances for Monoid StateF
        arising from a use of `GHC.Base.$dmmappend'
      Matching instances:
        instance Monoid b => Monoid (a -> b) -- Defined in `GHC.Base'
        instance Monoid StateF -- Defined at src\NFA.hs:13:10
    * In the expression: GHC.Base.$dmmappend @(StateF)
      In an equation for `mappend':
          mappend = GHC.Base.$dmmappend @(StateF)
      In the instance declaration for `Monoid StateF'
   |
13 | instance Monoid StateF where
   |          ^^^^^^^^^^^^^

src\NFA.hs:13:10: error:
    * Overlapping instances for Monoid StateF
        arising from a use of `GHC.Base.$dmmconcat'
      Matching instances:
        instance Monoid b => Monoid (a -> b) -- Defined in `GHC.Base'
        instance Monoid StateF -- Defined at src\NFA.hs:13:10
    * In the expression: GHC.Base.$dmmconcat @(StateF)
      In an equation for `mconcat':
          mconcat = GHC.Base.$dmmconcat @(StateF)
      In the instance declaration for `Monoid StateF'
   |
13 | instance Monoid StateF where
   |          ^^^^^^^^^^^^^

Solution

  • At least for the code shown, changing StateF from a type alias to a newtype introduces minimal changes and no runtime overhead.

    module NFA where
    
    data State = State Match State | Split State State | Final deriving (Show)
    data Match = Any | Char Char | ... deriving (Show)
    
    newtype StateF = StateF (State -> State)
    
    -- This is one change
    complete :: StateF -> State -> State
    complete (StateF f) = f
    
    -- This is another
    connect :: StateF -> StateF -> StateF
    connect fst snd = StateF $ complete fst . complete snd
    
    -- This is a third
    empty :: StateF
    empty = StateF id
    
    instance Semigroup StateF where
      (<>) = connect
    
    instance Monoid StateF where
      mempty = empty
    

    If you use record syntax, you won't even need pattern-matching for complete:

    newtype StateF  = StateF { runStateF :: State -> State }
    
    complete :: StateF -> State -> State
    -- complete statef exit = runStateF statef exit
    -- complete statef = runStateF statef
    complete = runStateF
    

    (Don't think of complete as actually applying the state transformer to a state, but rather extracting the state transformer so that it can be applied to a state.)