{-# LANGUAGE FlexibleInstances, DerivingVia, GeneralizedNewtypeDeriving #-} module InClassMonoidClass where import Prelude hiding (Monoid(..)) -- -- * Monoid type class -- -- | A monoid is an algebraic structure with: -- 1. an identity element -- 2. an associative binary operator class Monoid a where mempty :: a mappend :: a -> a -> a -- Laws: -- mappend mempty s <=> s -- mappend s mempty <=> s -- mappend (mappend s t) u <=> mappend s (mappend t u) -- | We may want to define a Monoid instance on Numbers with multiplication like -- so. But then we cannot define another Monoid instance on numbers! In ML we -- could use a Functor to do this (a many-to-many relation) -- instance Num a => Monoid a where -- mempty = 1 -- a `mappend` b = a * b -- | We can workaround this one instance per TypeClass, Type pair by using a -- newtype. A newtype is the same as a type synonym but doesn't inherit any of -- the typeclass instances for the type on the right hand side of the =. In this -- case Int -- newtype IntAdd = IA Int -- deriving (Enum, Show, Num, Eq) -- newtype IntMul = IM Int -- deriving (Enum, Show, Num, Eq) -- instance Monoid IntMul where -- mempty = IM 1 -- mappend (IM x) (IM y) = IM (x * y) -- instance Monoid IntAdd where -- mempty = IA 0 -- mappend (IA x) (IA y) = IA (x + y) -- try these examples in ghci -- >>> mconcat [1..10 :: IntAdd] -- >>> mconcat [1..10 :: IntMul] -- | Lists interestingly form a Monoid instance Monoid [a] where mempty = [] mappend xs ys = xs ++ ys -- | Functions also form a monoid! instance Monoid (a -> a) where mempty = id mappend f g = f . g -- >>> mconcat [1..5, 6..10] -- >>> (mconcat [(+2), (+6)]) 10 -- -- * Instances -- -- | With deriving via we make a newtype to represent the type class we want to -- derive newtype Sum a = Sum a -- | Then we make an instance for the newtype directly instance Num a => Monoid (Sum a) where mempty = Sum 0 mappend (Sum a) (Sum b) = Sum (a + b) -- | now we can reuse the instance for different types using deriving via! Here -- adding summation over Integers newtype IntAdd = IA Int deriving (Show, Enum, Num) deriving Monoid via (Sum Int) -- | And here adding summation over Doubles newtype IntDoubleAdd = IDA Double deriving (Show, Enum, Num) deriving Monoid via (Sum Double) -- -- * Derived operations -- -- | Fold mappend over a list of elements. mconcat :: Monoid a => [a] -> a mconcat = foldr mappend mempty -- Now use this in GHCi to do cool things!