{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, GeneralizedNewtypeDeriving #-}
{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
module Data.Semigroup.Self
( Self(..)
) where
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative
import Data.Foldable
import Data.Traversable
#endif
#if !(MIN_VERSION_base(4,11,0))
import Data.Semigroup
#endif
import Data.Semigroup.Foldable
import Data.Semigroup.Traversable
import Data.Semigroup.Reducer (Reducer(..))
newtype Self m = Self { getSelf :: m } deriving (Semigroup, Monoid)
instance Semigroup m => Reducer m (Self m) where
unit = Self
instance Functor Self where
fmap f (Self x) = Self (f x)
instance Foldable Self where
foldMap f (Self x) = f x
instance Traversable Self where
traverse f (Self x) = Self <$> f x
instance Foldable1 Self where
foldMap1 f (Self x) = f x
instance Traversable1 Self where
traverse1 f (Self x) = Self <$> f x