monoids induced by Applicative/Alternative/Monad/MonadPlus?

Dear Haskellers, are these monoids defined somewhere? import Control.Applicativeimport Data.Monoid newtype AppMonoid m a = AppMonoid (m a)instance (Monoid a, Applicative m) => Monoid (AppMonoid m a) where mempty = AppMonoid $ pure mempty mappend (AppMonoid x) (AppMonoid y) = AppMonoid $ mappend <$> x <*> y-- With the () monoid for `a` this becames the monoid of effects. newtype AltMonoid m a = AltMonoid (m a)instance Alternative m => Monoid (AltMonoid m a) where mempty = AltMonoid empty mappend (AltMonoid x) (AltMonoid y) = AltMonoid $ x <|> y (and similarly for Monad/MonadPlus, until they become subclasses of Applicative?) Best regards, Petr

Or, if there are no such definitions, where would be a good place to add them? Petr Dne 08/20/2013 06:55 PM, Petr Pudlák napsal(a):
Dear Haskellers,
are these monoids defined somewhere?
|import Control.Applicative import Data.Monoid
newtype AppMonoid m a =AppMonoid (m a) instance (Monoid a,Applicative m) =>Monoid (AppMonoid m a)where mempty =AppMonoid $ pure mempty mappend (AppMonoid x) (AppMonoid y) =AppMonoid $ mappend <$> x <*> y -- With the () monoid for `a` this becames the monoid of effects.
newtype AltMonoid m a =AltMonoid (m a) instance Alternative m =>Monoid (AltMonoid m a)where mempty =AltMonoid empty mappend (AltMonoid x) (AltMonoid y) =AltMonoid $ x <|> y|
(and similarly for Monad/MonadPlus, until they become subclasses of Applicative?)
Best regards, Petr

On 13-08-22 04:04 PM, Petr Pudlák wrote:
Or, if there are no such definitions, where would be a good place to add them?
If they are to be added to the base libraries, the Data.Monoid module would be my choice. I did wish I had the AppMonoid instance on several occasions, when using various parser combinator libraries that don't support this reasonable instance of Monoid:
numericLiteral = optionalMonoid (string "+" <|> string "-") <> some digit <> optionalMonoid (string "." <> some digit)
The problem is, the AppMonoid newtype would not help in that situation unless it also implemented Applicative and Alternative class, as well as the parsing primitives. Without the latter, the above code would look like this:
numericLiteral = optionalMonoid (AppMonoid (string "+" <|> string "-")) <> some (AppMonoid digit) <> optionalMonoid (AppMonoid (string ".") <> some (AppMonoid digit))
The point of the above is that I don't think there is enough justification for these newtypes. The Applicative and Alternative instances are typically used because of the primitives they come with, and newtype wrappings like AppMonoid and AltMonoid can't support those easily. Unless ekmett adds the appropriate instances to his parsers package, they would be too clumsy to use.
Petr
Dne 08/20/2013 06:55 PM, Petr Pudlák napsal(a):
Dear Haskellers,
are these monoids defined somewhere?
|import Control.Applicative import Data.Monoid
newtype AppMonoid m a =AppMonoid (m a) instance (Monoid a,Applicative m) =>Monoid (AppMonoid m a)where mempty =AppMonoid $ pure mempty mappend (AppMonoid x) (AppMonoid y) =AppMonoid $ mappend <$> x <*> y -- With the () monoid for `a` this becames the monoid of effects.
newtype AltMonoid m a =AltMonoid (m a) instance Alternative m =>Monoid (AltMonoid m a)where mempty =AltMonoid empty mappend (AltMonoid x) (AltMonoid y) =AltMonoid $ x <|> y|
(and similarly for Monad/MonadPlus, until they become subclasses of Applicative?)
Best regards, Petr
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

See also this thread from two years ago: http://www.haskell.org/pipermail/haskell-cafe/2011-June/091294.html
participants (2)
-
Mario Blažević
-
Petr Pudlák