[Haskell-cafe] <<loop>> as result of SemigroupMonoid changes

Dan Burton danburton.email at gmail.com
Mon Apr 30 14:07:18 UTC 2018


If you’re going to import Data.Semigroup as a sort of backwards
compatibility shim, then I don’t think you should import it qualified. To
avoid the ambiguity error, how about “import Data.Monoid hiding ((<>))”?

On Mon, Apr 30, 2018 at 05:57 Joey Hess <id at joeyh.name> wrote:

> I tried to follow the instructions at
> https://prime.haskell.org/wiki/Libraries/Proposals/SemigroupMonoid
> and I got a <<loop>> when my code runs with ghc 8.2.2.
>
> My code looked like this:
>
> import Data.Monoid
> import Prelude
>
> data InfoVal v = NoInfoVal | InfoVal v
>         deriving (Show)
>
> instance Monoid (InfoVal v) where
>         mempty = NoInfoVal
>         mappend _ v@(InfoVal _) = v
>         mappend v NoInfoVal = v
>
> Following the "recommended variant" for compatible code, I changed that
> too:
>
> {-# LANGUAGE CPP #-}
>
> import Data.Monoid
> import qualified Data.Semigroup as Sem
> import Prelude
>
> data InfoVal v = NoInfoVal | InfoVal v
>         deriving (Show)
>
> instance Monoid (InfoVal v) where
>         mempty = NoInfoVal
> #if !(MIN_VERSION_base(4,11,0))
>         mappend = (<>)
> #endif
>
> instance Sem.Semigroup (InfoVal v) where
>         _ <> v@(InfoVal _) = v
>         v <> NoInfoVal = v
>
> This loops because <> comes from Data.Monoid not from Data.Semigroup,
> so mappend = mappend.
>
> Note that I diverged slightly from the instructions to get to this wrong
> code; I imported Data.Semigroup qualified. Without the qualification,
> the above code fails to compile, with Ambiguous occurrence ‘<>’
>
> So, the transition instructions don't produce code that ghc 8.2.2 can
> build,
> and when the obvious fix is made to get it to compile, it compiles into a
> loop, that is *not* a loop when compiled with newer versions of ghc.
>
> --
> see shy jo
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.

-- 
-- Dan Burton
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20180430/be0f2792/attachment.html>


More information about the Haskell-Cafe mailing list