{-# LANGUAGE CPP #-}{-# LANGUAGE DefaultSignatures #-}{-# LANGUAGE DeriveDataTypeable #-}{-# LANGUAGE DeriveGeneric #-}{-# LANGUAGE FlexibleContexts #-}{-# LANGUAGE GeneralizedNewtypeDeriving #-}{-# LANGUAGE PolyKinds #-}{-# LANGUAGE ScopedTypeVariables #-}{-# LANGUAGE Trustworthy #-}{-# LANGUAGE TypeOperators #-}------------------------------------------------------------------------------- |-- Module : Data.Semigroup-- Copyright : (C) 2011-2015 Edward Kmett-- License : BSD-style (see the file LICENSE)---- Maintainer : libraries@haskell.org-- Stability : provisional-- Portability : portable---- In mathematics, a semigroup is an algebraic structure consisting of a-- set together with an associative binary operation. A semigroup-- generalizes a monoid in that there might not exist an identity-- element. It also (originally) generalized a group (a monoid with all-- inverses) to a type where every element did not have to have an inverse,-- thus the name semigroup.---- The use of @(\<\>)@ in this module conflicts with an operator with the same-- name that is being exported by Data.Monoid. However, this package-- re-exports (most of) the contents of Data.Monoid, so to use semigroups-- and monoids in the same package just---- > import Data.Semigroup---- @since 4.9.0.0----------------------------------------------------------------------------moduleData.Semigroup(Semigroup (..),stimesMonoid ,stimesIdempotent ,stimesIdempotentMonoid ,mtimesDefault -- * Semigroups,Min (..),Max (..),First (..),Last (..),WrappedMonoid (..)-- * Re-exported monoids from Data.Monoid,Dual (..),Endo (..),All (..),Any (..),Sum (..),Product (..)-- * A better monoid for Maybe,Option (..),option -- * Difference lists of a semigroup,diff ,cycle1 -- * ArgMin, ArgMax,Arg (..),ArgMin ,ArgMax )whereimportPrelude hiding(foldr1 )importGHC.Base (Semigroup (..))importData.Semigroup.Internal importControl.Applicative importControl.Monad importControl.Monad.Fix importData.Bifoldable importData.Bifunctor importData.Bitraversable importData.Coerce importData.Data importData.Monoid (All (..),Any (..),Dual (..),Endo (..),Product (..),Sum (..))-- import qualified Data.Monoid as MonoidimportGHC.Generics -- | A generalization of 'Data.List.cycle' to an arbitrary 'Semigroup'.-- May fail to terminate for some values in some semigroups.cycle1::Semigroup m =>m ->m cycle1 xs =xs' wherexs' =xs <> xs' -- | This lets you use a difference list of a 'Semigroup' as a 'Monoid'.diff::Semigroup m =>m ->Endo m diff =Endo . (<> )newtypeMin a =Min {getMin ::a }deriving(Bounded -- ^ @since 4.9.0.0,Eq-- ^ @since 4.9.0.0,Ord-- ^ @since 4.9.0.0,Show -- ^ @since 4.9.0.0,Read -- ^ @since 4.9.0.0,Data -- ^ @since 4.9.0.0,Generic -- ^ @since 4.9.0.0,Generic1 -- ^ @since 4.9.0.0)-- | @since 4.9.0.0instanceEnum a =>Enum (Min a )wheresucc (Min a )=Min (succ a )pred (Min a )=Min (pred a )toEnum =Min . toEnum fromEnum =fromEnum . getMinenumFrom (Min a )=Min <$> enumFrom a enumFromThen (Min a )(Min b )=Min <$> enumFromThen a b enumFromTo (Min a )(Min b )=Min <$> enumFromTo a b enumFromThenTo (Min a )(Min b )(Min c )=Min <$> enumFromThenTo a b c -- | @since 4.9.0.0instanceOrda =>Semigroup (Min a )where(<> )=coerce(min::a ->a ->a )stimes =stimesIdempotent -- | @since 4.9.0.0instance(Orda ,Bounded a )=>Monoid (Min a )wheremempty =maxBound -- | @since 4.9.0.0instanceFunctor Min wherefmap f (Min x )=Min (f x )-- | @since 4.9.0.0instanceFoldable Min wherefoldMap f (Min a )=f a -- | @since 4.9.0.0instanceTraversable Min wheretraverse f (Min a )=Min <$> f a -- | @since 4.9.0.0instanceApplicative Min wherepure =Min a <* _=a _*> a =a (<*> )=coerceliftA2 =coerce-- | @since 4.9.0.0instanceMonad Min where(>> )=(*> )Min a >>= f =f a -- | @since 4.9.0.0instanceMonadFix Min wheremfix f =fix (f . getMin)-- | @since 4.9.0.0instanceNum a =>Num (Min a )where(Min a )+ (Min b )=Min (a + b )(Min a )* (Min b )=Min (a * b )(Min a )-(Min b )=Min (a -b )negate (Min a )=Min (negate a )abs (Min a )=Min (abs a )signum (Min a )=Min (signum a )fromInteger =Min . fromInteger newtypeMax a =Max {getMax ::a }deriving(Bounded -- ^ @since 4.9.0.0,Eq-- ^ @since 4.9.0.0,Ord-- ^ @since 4.9.0.0,Show -- ^ @since 4.9.0.0,Read -- ^ @since 4.9.0.0,Data -- ^ @since 4.9.0.0,Generic -- ^ @since 4.9.0.0,Generic1 -- ^ @since 4.9.0.0)-- | @since 4.9.0.0instanceEnum a =>Enum (Max a )wheresucc (Max a )=Max (succ a )pred (Max a )=Max (pred a )toEnum =Max . toEnum fromEnum =fromEnum . getMaxenumFrom (Max a )=Max <$> enumFrom a enumFromThen (Max a )(Max b )=Max <$> enumFromThen a b enumFromTo (Max a )(Max b )=Max <$> enumFromTo a b enumFromThenTo (Max a )(Max b )(Max c )=Max <$> enumFromThenTo a b c -- | @since 4.9.0.0instanceOrda =>Semigroup (Max a )where(<> )=coerce(max::a ->a ->a )stimes =stimesIdempotent -- | @since 4.9.0.0instance(Orda ,Bounded a )=>Monoid (Max a )wheremempty =minBound -- | @since 4.9.0.0instanceFunctor Max wherefmap f (Max x )=Max (f x )-- | @since 4.9.0.0instanceFoldable Max wherefoldMap f (Max a )=f a -- | @since 4.9.0.0instanceTraversable Max wheretraverse f (Max a )=Max <$> f a -- | @since 4.9.0.0instanceApplicative Max wherepure =Max a <* _=a _*> a =a (<*> )=coerceliftA2 =coerce-- | @since 4.9.0.0instanceMonad Max where(>> )=(*> )Max a >>= f =f a -- | @since 4.9.0.0instanceMonadFix Max wheremfix f =fix (f . getMax)-- | @since 4.9.0.0instanceNum a =>Num (Max a )where(Max a )+ (Max b )=Max (a + b )(Max a )* (Max b )=Max (a * b )(Max a )-(Max b )=Max (a -b )negate (Max a )=Max (negate a )abs (Max a )=Max (abs a )signum (Max a )=Max (signum a )fromInteger =Max . fromInteger -- | 'Arg' isn't itself a 'Semigroup' in its own right, but it can be-- placed inside 'Min' and 'Max' to compute an arg min or arg max.dataArg a b =Arg a b deriving(Show -- ^ @since 4.9.0.0,Read -- ^ @since 4.9.0.0,Data -- ^ @since 4.9.0.0,Generic -- ^ @since 4.9.0.0,Generic1 -- ^ @since 4.9.0.0)typeArgMin a b =Min (Arg a b )typeArgMax a b =Max (Arg a b )-- | @since 4.9.0.0instanceFunctor (Arg a )wherefmap f (Arg x a )=Arg x (f a )-- | @since 4.9.0.0instanceFoldable (Arg a )wherefoldMap f (Arg _a )=f a -- | @since 4.9.0.0instanceTraversable (Arg a )wheretraverse f (Arg x a )=Arg x <$> f a -- | @since 4.9.0.0instanceEqa =>Eq(Arg a b )whereArg a _== Arg b _=a ==b -- | @since 4.9.0.0instanceOrda =>Ord(Arg a b )whereArg a _`compare `Arg b _=comparea b min x @(Arg a _)y @(Arg b _)|a <=b =x |otherwise =y max x @(Arg a _)y @(Arg b _)|a >=b =x |otherwise =y -- | @since 4.9.0.0instanceBifunctor Arg wherebimap f g (Arg a b )=Arg (f a )(g b )-- | @since 4.10.0.0instanceBifoldable Arg wherebifoldMap f g (Arg a b )=f a <> g b -- | @since 4.10.0.0instanceBitraversable Arg wherebitraverse f g (Arg a b )=Arg <$> f a <*> g b -- | Use @'Option' ('First' a)@ to get the behavior of-- 'Data.Monoid.First' from "Data.Monoid".newtypeFirst a =First {getFirst ::a }deriving(Bounded -- ^ @since 4.9.0.0,Eq-- ^ @since 4.9.0.0,Ord-- ^ @since 4.9.0.0,Show -- ^ @since 4.9.0.0,Read -- ^ @since 4.9.0.0,Data -- ^ @since 4.9.0.0,Generic -- ^ @since 4.9.0.0,Generic1 -- ^ @since 4.9.0.0)-- | @since 4.9.0.0instanceEnum a =>Enum (First a )wheresucc (First a )=First (succ a )pred (First a )=First (pred a )toEnum =First . toEnum fromEnum =fromEnum . getFirstenumFrom (First a )=First <$> enumFrom a enumFromThen (First a )(First b )=First <$> enumFromThen a b enumFromTo (First a )(First b )=First <$> enumFromTo a b enumFromThenTo (First a )(First b )(First c )=First <$> enumFromThenTo a b c -- | @since 4.9.0.0instanceSemigroup (First a )wherea <> _=a stimes =stimesIdempotent -- | @since 4.9.0.0instanceFunctor First wherefmap f (First x )=First (f x )-- | @since 4.9.0.0instanceFoldable First wherefoldMap f (First a )=f a -- | @since 4.9.0.0instanceTraversable First wheretraverse f (First a )=First <$> f a -- | @since 4.9.0.0instanceApplicative First wherepure x =First x a <* _=a _*> a =a (<*> )=coerceliftA2 =coerce-- | @since 4.9.0.0instanceMonad First where(>> )=(*> )First a >>= f =f a -- | @since 4.9.0.0instanceMonadFix First wheremfix f =fix (f . getFirst)-- | Use @'Option' ('Last' a)@ to get the behavior of-- 'Data.Monoid.Last' from "Data.Monoid"newtypeLast a =Last {getLast ::a }deriving(Bounded -- ^ @since 4.9.0.0,Eq-- ^ @since 4.9.0.0,Ord-- ^ @since 4.9.0.0,Show -- ^ @since 4.9.0.0,Read -- ^ @since 4.9.0.0,Data -- ^ @since 4.9.0.0,Generic -- ^ @since 4.9.0.0,Generic1 -- ^ @since 4.9.0.0)-- | @since 4.9.0.0instanceEnum a =>Enum (Last a )wheresucc (Last a )=Last (succ a )pred (Last a )=Last (pred a )toEnum =Last . toEnum fromEnum =fromEnum . getLastenumFrom (Last a )=Last <$> enumFrom a enumFromThen (Last a )(Last b )=Last <$> enumFromThen a b enumFromTo (Last a )(Last b )=Last <$> enumFromTo a b enumFromThenTo (Last a )(Last b )(Last c )=Last <$> enumFromThenTo a b c -- | @since 4.9.0.0instanceSemigroup (Last a )where_<> b =b stimes =stimesIdempotent -- | @since 4.9.0.0instanceFunctor Last wherefmap f (Last x )=Last (f x )a <$ _=Last a -- | @since 4.9.0.0instanceFoldable Last wherefoldMap f (Last a )=f a -- | @since 4.9.0.0instanceTraversable Last wheretraverse f (Last a )=Last <$> f a -- | @since 4.9.0.0instanceApplicative Last wherepure =Last a <* _=a _*> a =a (<*> )=coerceliftA2 =coerce-- | @since 4.9.0.0instanceMonad Last where(>> )=(*> )Last a >>= f =f a -- | @since 4.9.0.0instanceMonadFix Last wheremfix f =fix (f . getLast)-- | Provide a Semigroup for an arbitrary Monoid.---- __NOTE__: This is not needed anymore since 'Semigroup' became a superclass of-- 'Monoid' in /base-4.11/ and this newtype be deprecated at some point in the future.newtypeWrappedMonoid m =WrapMonoid {unwrapMonoid ::m }deriving(Bounded -- ^ @since 4.9.0.0,Eq-- ^ @since 4.9.0.0,Ord-- ^ @since 4.9.0.0,Show -- ^ @since 4.9.0.0,Read -- ^ @since 4.9.0.0,Data -- ^ @since 4.9.0.0,Generic -- ^ @since 4.9.0.0,Generic1 -- ^ @since 4.9.0.0)-- | @since 4.9.0.0instanceMonoid m =>Semigroup (WrappedMonoid m )where(<> )=coerce(mappend ::m ->m ->m )-- | @since 4.9.0.0instanceMonoid m =>Monoid (WrappedMonoid m )wheremempty =WrapMonoid mempty -- | @since 4.9.0.0instanceEnum a =>Enum (WrappedMonoid a )wheresucc (WrapMonoid a )=WrapMonoid (succ a )pred (WrapMonoid a )=WrapMonoid (pred a )toEnum =WrapMonoid . toEnum fromEnum =fromEnum . unwrapMonoidenumFrom (WrapMonoid a )=WrapMonoid <$> enumFrom a enumFromThen (WrapMonoid a )(WrapMonoid b )=WrapMonoid <$> enumFromThen a b enumFromTo (WrapMonoid a )(WrapMonoid b )=WrapMonoid <$> enumFromTo a b enumFromThenTo (WrapMonoid a )(WrapMonoid b )(WrapMonoid c )=WrapMonoid <$> enumFromThenTo a b c -- | Repeat a value @n@ times.---- > mtimesDefault n a = a <> a <> ... <> a -- using <> (n-1) times---- Implemented using 'stimes' and 'mempty'.---- This is a suitable definition for an 'mtimes' member of 'Monoid'.mtimesDefault::(Integral b ,Monoid a )=>b ->a ->a mtimesDefault n x |n ==0=mempty |otherwise =unwrapMonoid(stimes n (WrapMonoid x ))-- | 'Option' is effectively 'Maybe' with a better instance of-- 'Monoid', built off of an underlying 'Semigroup' instead of an-- underlying 'Monoid'.---- Ideally, this type would not exist at all and we would just fix the-- 'Monoid' instance of 'Maybe'.---- In GHC 8.4 and higher, the 'Monoid' instance for 'Maybe' has been-- corrected to lift a 'Semigroup' instance instead of a 'Monoid'-- instance. Consequently, this type is no longer useful. It will be-- marked deprecated in GHC 8.8 and removed in GHC 8.10.newtypeOption a =Option {getOption ::Maybe a }deriving(Eq-- ^ @since 4.9.0.0,Ord-- ^ @since 4.9.0.0,Show -- ^ @since 4.9.0.0,Read -- ^ @since 4.9.0.0,Data -- ^ @since 4.9.0.0,Generic -- ^ @since 4.9.0.0,Generic1 -- ^ @since 4.9.0.0)-- | @since 4.9.0.0instanceFunctor Option wherefmap f (Option a )=Option (fmap f a )-- | @since 4.9.0.0instanceApplicative Option wherepure a =Option (Just a )Option a <*> Option b =Option (a <*> b )liftA2 f (Option x )(Option y )=Option (liftA2 f x y )Option Nothing *> _=Option Nothing _*>b =b -- | @since 4.9.0.0instanceMonad Option whereOption (Just a )>>= k =k a _>>=_=Option Nothing (>> )=(*> )-- | @since 4.9.0.0instanceAlternative Option whereempty =Option Nothing Option Nothing <|> b =b a <|>_=a -- | @since 4.9.0.0instanceMonadPlus Option -- | @since 4.9.0.0instanceMonadFix Option wheremfix f =Option (mfix (getOption. f ))-- | @since 4.9.0.0instanceFoldable Option wherefoldMap f (Option (Just m ))=f m foldMap_(Option Nothing )=mempty -- | @since 4.9.0.0instanceTraversable Option wheretraverse f (Option (Just a ))=Option . Just <$> f a traverse_(Option Nothing )=pure (Option Nothing )-- | Fold an 'Option' case-wise, just like 'maybe'.option::b ->(a ->b )->Option a ->b option n j (Option m )=maybe n j m -- | @since 4.9.0.0instanceSemigroup a =>Semigroup (Option a )where(<> )=coerce((<> )::Maybe a ->Maybe a ->Maybe a )#if !defined(__HADDOCK_VERSION__) -- workaround https://github.com/haskell/haddock/issues/680stimes_(OptionNothing)=OptionNothingstimesn(Option(Justa))=casecomparen0ofLT->errorWithoutStackTrace"stimes: Option, negative multiplier"EQ->OptionNothingGT->Option(Just(stimesna))#endif -- | @since 4.9.0.0instanceSemigroup a =>Monoid (Option a )wheremempty =Option Nothing