monoid-subclasses-1.2: Subclasses of Monoid
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Monoid.Instances.Stateful

Description

This module defines the monoid transformer data type Stateful.

> let s = setState [4] $ pure "data" :: Stateful [Int] String
> s
Stateful ("data",[4])
> factors s
[Stateful ("d",[]),Stateful ("a",[]),Stateful ("t",[]),Stateful ("a",[]),Stateful ("",[4])]
Synopsis

Documentation

newtype Stateful a b Source #

Stateful a b is a wrapper around the Monoid b that carries the state a along. The state type a must be a monoid as well if Stateful is to be of any use. In the FactorialMonoid and TextualMonoid class instances, the monoid b has the priority and the state a is left for the end.

Constructors

Stateful (b, a) 

Instances

Instances details
Monoid a => Applicative (Stateful a) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

pure :: a0 -> Stateful a a0 #

(<*>) :: Stateful a (a0 -> b) -> Stateful a a0 -> Stateful a b #

liftA2 :: (a0 -> b -> c) -> Stateful a a0 -> Stateful a b -> Stateful a c #

(*>) :: Stateful a a0 -> Stateful a b -> Stateful a b #

(<*) :: Stateful a a0 -> Stateful a b -> Stateful a a0 #

Functor (Stateful a) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

fmap :: (a0 -> b) -> Stateful a a0 -> Stateful a b #

(<$) :: a0 -> Stateful a b -> Stateful a a0 #

(Data a, Data b) => Data (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Stateful a b -> c (Stateful a b) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Stateful a b) #

toConstr :: Stateful a b -> Constr #

dataTypeOf :: Stateful a b -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Stateful a b)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Stateful a b)) #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> Stateful a b -> Stateful a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Stateful a b -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Stateful a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> Stateful a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Stateful a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Stateful a b -> m (Stateful a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Stateful a b -> m (Stateful a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Stateful a b -> m (Stateful a b) #

(Monoid a, IsString b) => IsString (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

fromString :: String -> Stateful a b #

(Semigroup a, Semigroup b, Monoid a, Monoid b) => Monoid (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

mempty :: Stateful a b #

mappend :: Stateful a b -> Stateful a b -> Stateful a b #

mconcat :: [Stateful a b] -> Stateful a b #

(Semigroup a, Semigroup b) => Semigroup (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

(<>) :: Stateful a b -> Stateful a b -> Stateful a b #

sconcat :: NonEmpty (Stateful a b) -> Stateful a b #

stimes :: Integral b0 => b0 -> Stateful a b -> Stateful a b #

(Show b, Show a) => Show (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

showsPrec :: Int -> Stateful a b -> ShowS #

show :: Stateful a b -> String #

showList :: [Stateful a b] -> ShowS #

(Eq b, Eq a) => Eq (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

(==) :: Stateful a b -> Stateful a b -> Bool #

(/=) :: Stateful a b -> Stateful a b -> Bool #

(Ord b, Ord a) => Ord (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

compare :: Stateful a b -> Stateful a b -> Ordering #

(<) :: Stateful a b -> Stateful a b -> Bool #

(<=) :: Stateful a b -> Stateful a b -> Bool #

(>) :: Stateful a b -> Stateful a b -> Bool #

(>=) :: Stateful a b -> Stateful a b -> Bool #

max :: Stateful a b -> Stateful a b -> Stateful a b #

min :: Stateful a b -> Stateful a b -> Stateful a b #

(FactorialMonoid a, FactorialMonoid b) => FactorialMonoid (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

splitPrimePrefix :: Stateful a b -> Maybe (Stateful a b, Stateful a b) Source #

splitPrimeSuffix :: Stateful a b -> Maybe (Stateful a b, Stateful a b) Source #

inits :: Stateful a b -> [Stateful a b] Source #

tails :: Stateful a b -> [Stateful a b] Source #

span :: (Stateful a b -> Bool) -> Stateful a b -> (Stateful a b, Stateful a b) Source #

break :: (Stateful a b -> Bool) -> Stateful a b -> (Stateful a b, Stateful a b) Source #

split :: (Stateful a b -> Bool) -> Stateful a b -> [Stateful a b] Source #

takeWhile :: (Stateful a b -> Bool) -> Stateful a b -> Stateful a b Source #

dropWhile :: (Stateful a b -> Bool) -> Stateful a b -> Stateful a b Source #

spanMaybe :: s -> (s -> Stateful a b -> Maybe s) -> Stateful a b -> (Stateful a b, Stateful a b, s) Source #

spanMaybe' :: s -> (s -> Stateful a b -> Maybe s) -> Stateful a b -> (Stateful a b, Stateful a b, s) Source #

splitAt :: Int -> Stateful a b -> (Stateful a b, Stateful a b) Source #

drop :: Int -> Stateful a b -> Stateful a b Source #

take :: Int -> Stateful a b -> Stateful a b Source #

(LeftGCDMonoid a, LeftGCDMonoid b) => LeftGCDMonoid (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

commonPrefix :: Stateful a b -> Stateful a b -> Stateful a b Source #

stripCommonPrefix :: Stateful a b -> Stateful a b -> (Stateful a b, Stateful a b, Stateful a b) Source #

(RightGCDMonoid a, RightGCDMonoid b) => RightGCDMonoid (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

commonSuffix :: Stateful a b -> Stateful a b -> Stateful a b Source #

stripCommonSuffix :: Stateful a b -> Stateful a b -> (Stateful a b, Stateful a b, Stateful a b) Source #

(MonoidNull a, MonoidNull b) => MonoidNull (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

null :: Stateful a b -> Bool Source #

(PositiveMonoid a, PositiveMonoid b) => PositiveMonoid (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

(LeftGCDMonoid a, FactorialMonoid a, TextualMonoid b) => TextualMonoid (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

fromText :: Text -> Stateful a b Source #

singleton :: Char -> Stateful a b Source #

splitCharacterPrefix :: Stateful a b -> Maybe (Char, Stateful a b) Source #

characterPrefix :: Stateful a b -> Maybe Char Source #

map :: (Char -> Char) -> Stateful a b -> Stateful a b Source #

concatMap :: (Char -> Stateful a b) -> Stateful a b -> Stateful a b Source #

toString :: (Stateful a b -> String) -> Stateful a b -> String Source #

toText :: (Stateful a b -> Text) -> Stateful a b -> Text Source #

any :: (Char -> Bool) -> Stateful a b -> Bool Source #

all :: (Char -> Bool) -> Stateful a b -> Bool Source #

foldl :: (a0 -> Stateful a b -> a0) -> (a0 -> Char -> a0) -> a0 -> Stateful a b -> a0 Source #

foldl' :: (a0 -> Stateful a b -> a0) -> (a0 -> Char -> a0) -> a0 -> Stateful a b -> a0 Source #

foldr :: (Stateful a b -> a0 -> a0) -> (Char -> a0 -> a0) -> a0 -> Stateful a b -> a0 Source #

scanl :: (Char -> Char -> Char) -> Char -> Stateful a b -> Stateful a b Source #

scanl1 :: (Char -> Char -> Char) -> Stateful a b -> Stateful a b Source #

scanr :: (Char -> Char -> Char) -> Char -> Stateful a b -> Stateful a b Source #

scanr1 :: (Char -> Char -> Char) -> Stateful a b -> Stateful a b Source #

mapAccumL :: (a0 -> Char -> (a0, Char)) -> a0 -> Stateful a b -> (a0, Stateful a b) Source #

mapAccumR :: (a0 -> Char -> (a0, Char)) -> a0 -> Stateful a b -> (a0, Stateful a b) Source #

takeWhile :: (Stateful a b -> Bool) -> (Char -> Bool) -> Stateful a b -> Stateful a b Source #

dropWhile :: (Stateful a b -> Bool) -> (Char -> Bool) -> Stateful a b -> Stateful a b Source #

break :: (Stateful a b -> Bool) -> (Char -> Bool) -> Stateful a b -> (Stateful a b, Stateful a b) Source #

span :: (Stateful a b -> Bool) -> (Char -> Bool) -> Stateful a b -> (Stateful a b, Stateful a b) Source #

spanMaybe :: s -> (s -> Stateful a b -> Maybe s) -> (s -> Char -> Maybe s) -> Stateful a b -> (Stateful a b, Stateful a b, s) Source #

spanMaybe' :: s -> (s -> Stateful a b -> Maybe s) -> (s -> Char -> Maybe s) -> Stateful a b -> (Stateful a b, Stateful a b, s) Source #

split :: (Char -> Bool) -> Stateful a b -> [Stateful a b] Source #

find :: (Char -> Bool) -> Stateful a b -> Maybe Char Source #

elem :: Char -> Stateful a b -> Bool Source #

foldl_ :: (a0 -> Char -> a0) -> a0 -> Stateful a b -> a0 Source #

foldl_' :: (a0 -> Char -> a0) -> a0 -> Stateful a b -> a0 Source #

foldr_ :: (Char -> a0 -> a0) -> a0 -> Stateful a b -> a0 Source #

takeWhile_ :: Bool -> (Char -> Bool) -> Stateful a b -> Stateful a b Source #

dropWhile_ :: Bool -> (Char -> Bool) -> Stateful a b -> Stateful a b Source #

break_ :: Bool -> (Char -> Bool) -> Stateful a b -> (Stateful a b, Stateful a b) Source #

span_ :: Bool -> (Char -> Bool) -> Stateful a b -> (Stateful a b, Stateful a b) Source #

spanMaybe_ :: s -> (s -> Char -> Maybe s) -> Stateful a b -> (Stateful a b, Stateful a b, s) Source #

spanMaybe_' :: s -> (s -> Char -> Maybe s) -> Stateful a b -> (Stateful a b, Stateful a b, s) Source #

(LeftReductive a, LeftReductive b) => LeftReductive (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

isPrefixOf :: Stateful a b -> Stateful a b -> Bool Source #

stripPrefix :: Stateful a b -> Stateful a b -> Maybe (Stateful a b) Source #

(RightReductive a, RightReductive b) => RightReductive (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

isSuffixOf :: Stateful a b -> Stateful a b -> Bool Source #

stripSuffix :: Stateful a b -> Stateful a b -> Maybe (Stateful a b) Source #

(FactorialMonoid a, FactorialMonoid b) => Factorial (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

Methods

factors :: Stateful a b -> [Stateful a b] Source #

primePrefix :: Stateful a b -> Stateful a b Source #

primeSuffix :: Stateful a b -> Stateful a b Source #

foldl :: (a0 -> Stateful a b -> a0) -> a0 -> Stateful a b -> a0 Source #

foldl' :: (a0 -> Stateful a b -> a0) -> a0 -> Stateful a b -> a0 Source #

foldr :: (Stateful a b -> a0 -> a0) -> a0 -> Stateful a b -> a0 Source #

length :: Stateful a b -> Int Source #

foldMap :: Monoid n => (Stateful a b -> n) -> Stateful a b -> n Source #

reverse :: Stateful a b -> Stateful a b Source #

(FactorialMonoid a, FactorialMonoid b, StableFactorial a, StableFactorial b) => StableFactorial (Stateful a b) Source # 
Instance details

Defined in Data.Monoid.Instances.Stateful

extract :: Stateful a b -> b Source #

state :: Stateful a b -> a Source #

setState :: a -> Stateful a b -> Stateful a b Source #