
We already could write and compile next code: {-# LANGUAGE PolyKinds, FlexibleContexts, TypeFamilies #-} {-# LANGUAGE FlexibleInstances, UndecidableInstances #-} class Monoid (a :: k) where type Pr a :: * mempty :: PA a mappend :: Pr a -> Pr a -> Pr a instance Monoid [b] where type Pr [b] = [b] mempty = [] mappend = (++) instance (Monad m, MonadPlus m) => Monoid ( m :: * -> * ) where type Pr m = m Int -- Unfortunally, we can't write now type Pr m = forall b. m b --Illegal polymorphic or qualified type: forall b. m b mempty = mzero mappend = mplus This code is already valid. But we can't use any written instance at all, the ambiguity problem. Wvv 29 / 06 / 2013 17:39:25 user Ben Franksen [via Haskell] (ml-node+s1045720n5732210h49@n5.nabble.com) wrote: This is a kind error. The m in Monoid has kind *, while the one in Monad has kind * -> *. I suggest you (try to) rewrite your proposal to eliminate these kind errors before any further elaboration. Cheers -- Ben Franksen () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachm€nts _______________________________________________ Haskell-prime mailing list [hidden email] http://www.haskell.org/mailman/listinfo/haskell-prime ---------------------------------------------------------------------------- If you reply to this email, your message will be added to the discussion below:http://haskell.1045720.n5.nabble.com/Interfaces-the-Golden-Path-of-Haskell-t... To unsubscribe from Interfaces - the Golden Path of Haskell?, click here. NAML -- View this message in context: http://haskell.1045720.n5.nabble.com/Interfaces-the-Golden-Path-of-Haskell-t... Sent from the Haskell - Haskell-prime mailing list archive at Nabble.com.