mvc-1.1.7: Model-view-controller

Safe HaskellSafe
LanguageHaskell98

MVC

Contents

Description

Use the Model - View - Controller pattern to separate impure inputs and outputs from pure application logic so that you can:

  • Equationally reason about your model
  • Exercise your model with property-based testing (like QuickCheck)
  • Reproducibly replay your model

The mvc library uses the type system to statically enforce the separation of impure Views and Controllers from the pure Model.

Here's a small example program written using the mvc library to illustrate the core types and concepts:

import MVC
import qualified MVC.Prelude as MVC
import qualified Pipes.Prelude as Pipes

external :: Managed (View String, Controller String)
external = do
    c1 <- MVC.stdinLines
    c2 <- MVC.tick 1
    return (MVC.stdoutLines, c1 <> fmap show c2)

model :: Model () String String
model = asPipe (Pipes.takeWhile (/= "quit"))
    
main :: IO ()
main = runMVC () model external

This program has three components:

  • A Controller that interleaves lines from standard input with periodic ticks
  • A View that writes lines to standard output
  • A pure Model, which forwards lines until the user inputs "quit"

runMVC connects them into a complete program, which outputs a () every second and also echoes standard input to standard output until the user enters "quit":

>>> main
()
Test<Enter>
Test
()
()
42<Enter>
42
()
quit<enter>
>>> 

The following sections give extended guidance for how to structure mvc programs. Additionally, there is an MVC.Prelude module, which provides several utilities and provides a more elaborate code example using the sdl library.

Synopsis

Controllers

Controllers represent concurrent inputs to your system. Use the Functor and Monoid instances for Controller and Managed to unify multiple Managed Controllers together into a single Managed Controller:

controllerA :: Managed (Controller A)
controllerB :: Managed (Controller B)
controllerC :: Managed (Controller C)

data TotalInput = InA A | InB B | InC C

controllerTotal :: Managed (Controller TotalInput)
controllerTotal =
        fmap (fmap InA) controllerA
    <>  fmap (fmap InB) controllerB
    <>  fmap (fmap InC) controllerC

Combining Controllers interleaves their values.

data Controller a Source #

A concurrent source

fmap f (c1 <> c2) = fmap f c1 <> fmap f c2

fmap f mempty = mempty
Instances
Functor Controller Source # 
Instance details

Defined in MVC

Methods

fmap :: (a -> b) -> Controller a -> Controller b #

(<$) :: a -> Controller b -> Controller a #

Semigroup (Controller a) Source # 
Instance details

Defined in MVC

Monoid (Controller a) Source # 
Instance details

Defined in MVC

asInput :: Input a -> Controller a Source #

Create a Controller from an Input

keeps Source #

Arguments

:: ((b -> Constant (First b) b) -> a -> Constant (First b) a) 
-> Controller a 
-> Controller b 

Think of the type as one of the following types:

keeps :: Prism'     a b -> Controller a -> Controller b
keeps :: Traversal' a b -> Controller a -> Controller b

(keeps prism controller) only emits values if the prism matches the controller's output.

keeps (p1 . p2) = keeps p2 . keeps p1

keeps id = id
keeps p (c1 <> c2) = keeps p c1 <> keeps p c2

keeps p mempty = mempty

Views

Views represent outputs of your system. Use handles and the Monoid instance of View to unify multiple Views together into a single View:

viewD :: Managed (View D)
viewE :: Managed (View E)
viewF :: Managed (View F)

data TotalOutput = OutD D | OutE E | OutF F

makePrisms ''TotalOutput  -- Generates _OutD, _OutE, and _OutF prisms

viewTotal :: Managed (View TotalOutput)
viewTotal =
        fmap (handles _OutD) viewD
    <>  fmap (handles _OutE) viewE
    <>  fmap (handles _OutF) viewF

Combining Views sequences their outputs.

If a lens dependency is too heavy-weight, then you can manually generate Traversals, which handles will also accept. Here is an example of how you can generate Traversals by hand with no dependencies:

-- _OutD :: Traversal' TotalOutput D
_OutD :: Applicative f => (D -> f D) -> (TotalOutput -> f TotalOutput)
_OutD k (OutD d) = fmap OutD (k d)
_OutD k  t       = pure t

-- _OutE :: Traversal' TotalOutput E
_OutE :: Applicative f => (E -> f E) -> (TotalOutput -> f TotalOutput)
_OutE k (OutE d) = fmap OutE (k d)
_OutE k  t       = pure t

-- _OutF :: Traversal' TotalOutput F
_OutF :: Applicative f => (F -> f F) -> (TotalOutput -> f TotalOutput)
_OutF k (OutF d) = fmap OutF (k d)
_OutF k  t       = pure t

data View a Source #

An effectful sink

contramap f (v1 <> v2) = contramap f v1 <> contramap f v2

contramap f mempty = mempty
Instances
Contravariant View Source # 
Instance details

Defined in MVC

Methods

contramap :: (a -> b) -> View b -> View a #

(>$) :: b -> View b -> View a #

Semigroup (View a) Source # 
Instance details

Defined in MVC

Methods

(<>) :: View a -> View a -> View a #

sconcat :: NonEmpty (View a) -> View a #

stimes :: Integral b => b -> View a -> View a #

Monoid (View a) Source # 
Instance details

Defined in MVC

Methods

mempty :: View a #

mappend :: View a -> View a -> View a #

mconcat :: [View a] -> View a #

asSink :: (a -> IO ()) -> View a Source #

Create a View from a sink

asFold :: FoldM IO a () -> View a Source #

Create a View from a FoldM

handles Source #

Arguments

:: HandlerM IO a b 
-> View b 
-> View a 

Think of the type as one of the following types:

handles :: Prism'     a b -> View b -> View a
handles :: Traversal' a b -> View b -> View a

(handles prism view) only runs the view if the prism matches the input.

handles (p1 . p2) = handles p1 . handles p2

handles id = id
handles p (v1 <> v2) = handles p v1 <> handles p v2

handles p mempty = mempty

Models

Models are stateful streams and they sit in between Controllers and Views.

Use State to internally communicate within the Model.

Read the "ListT" section which describes why you should prefer ListT over Pipe when possible.

Also, try to defer converting your Pipe to a Model until you call runMVC, because the conversion is not reversible and Pipe is strictly more featureful than Model.

data ModelM m s a b Source #

A (Model s a b) converts a stream of (a)s into a stream of (b)s while interacting with a state (s)

Instances
Monad m => Category (ModelM m s :: * -> * -> *) Source # 
Instance details

Defined in MVC

Methods

id :: ModelM m s a a #

(.) :: ModelM m s b c -> ModelM m s a b -> ModelM m s a c #

asPipe :: Pipe a b (StateT s m) () -> ModelM m s a b Source #

Create a Model from a Pipe

asPipe (p1 <-< p2) = asPipe p1 . asPipe p2

asPipe cat = id

MVC

Connect a Model, View, and Controller and an initial state together using runMVC to complete your application.

runMVC is the only way to consume Views and Controllers. The types forbid you from mixing View and Controller logic with your Model logic.

Note that runMVC only accepts one View and one Controller. This enforces a single entry point and exit point for your Model so that you can cleanly separate your Model logic from your View logic and Controller logic. The way you add more Views and Controllers to your program is by unifying them into a single View or Controller by using their Monoid instances. See the "Controllers" and "Views" sections for more details on how to do this.

runMVC Source #

Arguments

:: s

Initial state

-> Model s a b

Program logic

-> Managed (View b, Controller a)

Effectful output and input

-> IO s

Returns final state

Connect a Model, View, and Controller and initial state into a complete application.

generalizeMVC Source #

Arguments

:: Monad m 
=> (forall x. m x -> IO x)

Monad morphism

-> s

Initial state

-> ModelM m s a b

Program logic

-> Managed (View b, Controller a)

Effectful output and input

-> IO s

Returns final state

Connect a Model, View, and Controller and initial state into a complete application over arbitrary monad given a morphism to IO.

Managed resources

Use managed to create primitive Managed resources and use the Functor, Applicative, Monad, and Monoid instances for Managed to bundle multiple Managed resources into a single Managed resource.

See the source code for the "Utilities" section below for several examples of how to create Managed resources.

data Managed a #

A managed resource that you acquire using with

Instances
Monad Managed 
Instance details

Defined in Control.Monad.Managed

Methods

(>>=) :: Managed a -> (a -> Managed b) -> Managed b #

(>>) :: Managed a -> Managed b -> Managed b #

return :: a -> Managed a #

fail :: String -> Managed a #

Functor Managed 
Instance details

Defined in Control.Monad.Managed

Methods

fmap :: (a -> b) -> Managed a -> Managed b #

(<$) :: a -> Managed b -> Managed a #

Applicative Managed 
Instance details

Defined in Control.Monad.Managed

Methods

pure :: a -> Managed a #

(<*>) :: Managed (a -> b) -> Managed a -> Managed b #

liftA2 :: (a -> b -> c) -> Managed a -> Managed b -> Managed c #

(*>) :: Managed a -> Managed b -> Managed b #

(<*) :: Managed a -> Managed b -> Managed a #

MonadIO Managed 
Instance details

Defined in Control.Monad.Managed

Methods

liftIO :: IO a -> Managed a #

MonadManaged Managed 
Instance details

Defined in Control.Monad.Managed

Methods

using :: Managed a -> Managed a #

Floating a => Floating (Managed a) 
Instance details

Defined in Control.Monad.Managed

Methods

pi :: Managed a #

exp :: Managed a -> Managed a #

log :: Managed a -> Managed a #

sqrt :: Managed a -> Managed a #

(**) :: Managed a -> Managed a -> Managed a #

logBase :: Managed a -> Managed a -> Managed a #

sin :: Managed a -> Managed a #

cos :: Managed a -> Managed a #

tan :: Managed a -> Managed a #

asin :: Managed a -> Managed a #

acos :: Managed a -> Managed a #

atan :: Managed a -> Managed a #

sinh :: Managed a -> Managed a #

cosh :: Managed a -> Managed a #

tanh :: Managed a -> Managed a #

asinh :: Managed a -> Managed a #

acosh :: Managed a -> Managed a #

atanh :: Managed a -> Managed a #

log1p :: Managed a -> Managed a #

expm1 :: Managed a -> Managed a #

log1pexp :: Managed a -> Managed a #

log1mexp :: Managed a -> Managed a #

Fractional a => Fractional (Managed a) 
Instance details

Defined in Control.Monad.Managed

Methods

(/) :: Managed a -> Managed a -> Managed a #

recip :: Managed a -> Managed a #

fromRational :: Rational -> Managed a #

Num a => Num (Managed a) 
Instance details

Defined in Control.Monad.Managed

Methods

(+) :: Managed a -> Managed a -> Managed a #

(-) :: Managed a -> Managed a -> Managed a #

(*) :: Managed a -> Managed a -> Managed a #

negate :: Managed a -> Managed a #

abs :: Managed a -> Managed a #

signum :: Managed a -> Managed a #

fromInteger :: Integer -> Managed a #

Semigroup a => Semigroup (Managed a) 
Instance details

Defined in Control.Monad.Managed

Methods

(<>) :: Managed a -> Managed a -> Managed a #

sconcat :: NonEmpty (Managed a) -> Managed a #

stimes :: Integral b => b -> Managed a -> Managed a #

Monoid a => Monoid (Managed a) 
Instance details

Defined in Control.Monad.Managed

Methods

mempty :: Managed a #

mappend :: Managed a -> Managed a -> Managed a #

mconcat :: [Managed a] -> Managed a #

managed :: (forall r. (a -> IO r) -> IO r) -> Managed a #

Build a Managed value

ListT

loop :: Monad m => (a -> ListT m b) -> Pipe a b m r #

Create a Pipe from a ListT transformation

loop (k1 >=> k2) = loop k1 >-> loop k2

loop return = cat

ListT computations can be combined in more ways than Pipes, so try to program in ListT as much as possible and defer converting it to a Pipe as late as possible using loop.

You can combine ListT computations even if their inputs and outputs are completely different:

-- Independent computations

modelAToD :: A -> ListT (State S) D
modelBToE :: B -> ListT (State S) E
modelCToF :: C -> ListT (State s) F

modelInToOut :: TotalInput -> ListT (State S) TotalOutput
modelInToOut totalInput = case totalInput of
    InA a -> fmap OutD (modelAToD a)
    InB b -> fmap OutE (modelBToE b)
    InC c -> fmap OutF (modelCToF c)

Sometimes you have multiple computations that handle different inputs but the same output, in which case you don't need to unify their outputs:

-- Overlapping outputs

modelAToOut :: A -> ListT (State S) Out
modelBToOut :: B -> ListT (State S) Out
modelCToOut :: C -> ListT (State S) Out

modelInToOut :: TotalInput -> ListT (State S) TotalOutput
modelInToOut totalInput = case totalInput of
    InA a -> modelAToOut a
    InB b -> modelBToOut b
    InC c -> modelCToOut c

Other times you have multiple computations that handle the same input but produce different outputs. You can unify their outputs using the Monoid and Functor instances for ListT:

-- Overlapping inputs

modelInToA :: TotalInput -> ListT (State S) A
modelInToB :: TotalInput -> ListT (State S) B
modelInToC :: TotalInput -> ListT (State S) C

modelInToOut :: TotalInput -> ListT (State S) TotalOutput
modelInToOut totalInput =
       fmap OutA (modelInToA totalInput)
    <> fmap OutB (modelInToB totalInput)
    <> fmap OutC (modelInToC totalInput)

You can also chain ListT computations, feeding the output of the first computation as the input to the next computation:

-- End-to-end

modelInToMiddle  :: TotalInput -> ListT (State S) MiddleStep
modelMiddleToOut :: MiddleStep -> ListT (State S) TotalOutput

modelInToOut :: TotalInput -> ListT (State S) TotalOutput
modelInToOut = modelInToMiddle >=> modelMiddleToOut

... or you can just use do notation if you prefer.

However, the Pipe type is more general than ListT and can represent things like termination. Therefore you should consider mixing Pipes with ListT when you need to take advantage of these extra features:

-- Mix ListT with Pipes

pipe :: Pipe TotalInput TotalOutput (State S) ()
pipe = Pipes.takeWhile (not . isC)) >-> loop modelInToOut
  where
    isC (InC _) = True
    isC  _      = False

So promote your ListT logic to a Pipe when you need to take advantage of these Pipe-specific features.

Re-exports

Data.Functor.Constant re-exports Constant

Data.Functor.Contravariant re-exports Contravariant

Data.Monoid re-exports Monoid, (<>), mconcat, and First (the type only)

Pipes re-exports everything

Pipes.Concurrent re-exports everything

newtype Constant a (b :: k) :: forall k. * -> k -> * #

Constant functor.

Constructors

Constant 

Fields

Instances
Bitraversable (Constant :: * -> * -> *) 
Instance details

Defined in Data.Functor.Constant

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Constant a b -> f (Constant c d) #

Bifoldable (Constant :: * -> * -> *) 
Instance details

Defined in Data.Functor.Constant

Methods

bifold :: Monoid m => Constant m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Constant a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Constant a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Constant a b -> c #

Bifunctor (Constant :: * -> * -> *) 
Instance details

Defined in Data.Functor.Constant

Methods

bimap :: (a -> b) -> (c -> d) -> Constant a c -> Constant b d #

first :: (a -> b) -> Constant a c -> Constant b c #

second :: (b -> c) -> Constant a b -> Constant a c #

Eq2 (Constant :: * -> * -> *) 
Instance details

Defined in Data.Functor.Constant

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Constant a c -> Constant b d -> Bool #

Ord2 (Constant :: * -> * -> *) 
Instance details

Defined in Data.Functor.Constant

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Constant a c -> Constant b d -> Ordering #

Read2 (Constant :: * -> * -> *) 
Instance details

Defined in Data.Functor.Constant

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Constant a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Constant a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Constant a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Constant a b] #

Show2 (Constant :: * -> * -> *) 
Instance details

Defined in Data.Functor.Constant

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Constant a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Constant a b] -> ShowS #

Functor (Constant a :: * -> *) 
Instance details

Defined in Data.Functor.Constant

Methods

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

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

Monoid a => Applicative (Constant a :: * -> *) 
Instance details

Defined in Data.Functor.Constant

Methods

pure :: a0 -> Constant a a0 #

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

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

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

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

Foldable (Constant a :: * -> *) 
Instance details

Defined in Data.Functor.Constant

Methods

fold :: Monoid m => Constant a m -> m #

foldMap :: Monoid m => (a0 -> m) -> Constant a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> Constant a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> Constant a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> Constant a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> Constant a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> Constant a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> Constant a a0 -> a0 #

toList :: Constant a a0 -> [a0] #

null :: Constant a a0 -> Bool #

length :: Constant a a0 -> Int #

elem :: Eq a0 => a0 -> Constant a a0 -> Bool #

maximum :: Ord a0 => Constant a a0 -> a0 #

minimum :: Ord a0 => Constant a a0 -> a0 #

sum :: Num a0 => Constant a a0 -> a0 #

product :: Num a0 => Constant a a0 -> a0 #

Traversable (Constant a :: * -> *) 
Instance details

Defined in Data.Functor.Constant

Methods

traverse :: Applicative f => (a0 -> f b) -> Constant a a0 -> f (Constant a b) #

sequenceA :: Applicative f => Constant a (f a0) -> f (Constant a a0) #

mapM :: Monad m => (a0 -> m b) -> Constant a a0 -> m (Constant a b) #

sequence :: Monad m => Constant a (m a0) -> m (Constant a a0) #

Eq a => Eq1 (Constant a :: * -> *) 
Instance details

Defined in Data.Functor.Constant

Methods

liftEq :: (a0 -> b -> Bool) -> Constant a a0 -> Constant a b -> Bool #

Ord a => Ord1 (Constant a :: * -> *) 
Instance details

Defined in Data.Functor.Constant

Methods

liftCompare :: (a0 -> b -> Ordering) -> Constant a a0 -> Constant a b -> Ordering #

Read a => Read1 (Constant a :: * -> *) 
Instance details

Defined in Data.Functor.Constant

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Constant a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Constant a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Constant a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Constant a a0] #

Show a => Show1 (Constant a :: * -> *) 
Instance details

Defined in Data.Functor.Constant

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Constant a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Constant a a0] -> ShowS #

Contravariant (Constant a :: * -> *) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a0 -> b) -> Constant a b -> Constant a a0 #

(>$) :: b -> Constant a b -> Constant a a0 #

Eq a => Eq (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

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

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

Ord a => Ord (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

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

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

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

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

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

max :: Constant a b -> Constant a b -> Constant a b #

min :: Constant a b -> Constant a b -> Constant a b #

Read a => Read (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Show a => Show (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

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

show :: Constant a b -> String #

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

Semigroup a => Semigroup (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

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

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

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

Monoid a => Monoid (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

mempty :: Constant a b #

mappend :: Constant a b -> Constant a b -> Constant a b #

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

class Contravariant (f :: * -> *) where #

The class of contravariant functors.

Whereas in Haskell, one can think of a Functor as containing or producing values, a contravariant functor is a functor that can be thought of as consuming values.

As an example, consider the type of predicate functions a -> Bool. One such predicate might be negative x = x < 0, which classifies integers as to whether they are negative. However, given this predicate, we can re-use it in other situations, providing we have a way to map values to integers. For instance, we can use the negative predicate on a person's bank balance to work out if they are currently overdrawn:

newtype Predicate a = Predicate { getPredicate :: a -> Bool }

instance Contravariant Predicate where
  contramap f (Predicate p) = Predicate (p . f)
                                         |   `- First, map the input...
                                         `----- then apply the predicate.

overdrawn :: Predicate Person
overdrawn = contramap personBankBalance negative

Any instance should be subject to the following laws:

contramap id = id
contramap f . contramap g = contramap (g . f)

Note, that the second law follows from the free theorem of the type of contramap and the first law, so you need only check that the former condition holds.

Minimal complete definition

contramap

Methods

contramap :: (a -> b) -> f b -> f a #

Instances
Contravariant SettableStateVar 
Instance details

Defined in Data.Functor.Contravariant

Contravariant Predicate

A Predicate is a Contravariant Functor, because contramap can apply its function argument to the input of the predicate.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Predicate b -> Predicate a #

(>$) :: b -> Predicate b -> Predicate a #

Contravariant Comparison

A Comparison is a Contravariant Functor, because contramap can apply its function argument to each input of the comparison function.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Comparison b -> Comparison a #

(>$) :: b -> Comparison b -> Comparison a #

Contravariant Equivalence

Equivalence relations are Contravariant, because you can apply the contramapped function to each input to the equivalence relation.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Equivalence b -> Equivalence a #

(>$) :: b -> Equivalence b -> Equivalence a #

Contravariant Output

This instance is useful for creating new tagged address, similar to elm's Signal.forwardTo. In fact elm's forwardTo is just 'flip contramap'

Instance details

Defined in Pipes.Concurrent

Methods

contramap :: (a -> b) -> Output b -> Output a #

(>$) :: b -> Output b -> Output a #

Contravariant View # 
Instance details

Defined in MVC

Methods

contramap :: (a -> b) -> View b -> View a #

(>$) :: b -> View b -> View a #

Contravariant (V1 :: * -> *) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> V1 b -> V1 a #

(>$) :: b -> V1 b -> V1 a #

Contravariant (U1 :: * -> *) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> U1 b -> U1 a #

(>$) :: b -> U1 b -> U1 a #

Contravariant (Proxy :: * -> *) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Proxy b -> Proxy a #

(>$) :: b -> Proxy b -> Proxy a #

Contravariant (Op a) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a0 -> b) -> Op a b -> Op a a0 #

(>$) :: b -> Op a b -> Op a a0 #

Contravariant m => Contravariant (MaybeT m) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> MaybeT m b -> MaybeT m a #

(>$) :: b -> MaybeT m b -> MaybeT m a #

Contravariant m => Contravariant (ListT m) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> ListT m b -> ListT m a #

(>$) :: b -> ListT m b -> ListT m a #

Contravariant f => Contravariant (Rec1 f) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Rec1 f b -> Rec1 f a #

(>$) :: b -> Rec1 f b -> Rec1 f a #

Contravariant (Const a :: * -> *) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a0 -> b) -> Const a b -> Const a a0 #

(>$) :: b -> Const a b -> Const a a0 #

Contravariant f => Contravariant (Alt f) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Alt f b -> Alt f a #

(>$) :: b -> Alt f b -> Alt f a #

Contravariant f => Contravariant (IdentityT f) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> IdentityT f b -> IdentityT f a #

(>$) :: b -> IdentityT f b -> IdentityT f a #

Contravariant m => Contravariant (ExceptT e m) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> ExceptT e m b -> ExceptT e m a #

(>$) :: b -> ExceptT e m b -> ExceptT e m a #

Contravariant m => Contravariant (ErrorT e m) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> ErrorT e m b -> ErrorT e m a #

(>$) :: b -> ErrorT e m b -> ErrorT e m a #

Contravariant m => Contravariant (StateT s m) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> StateT s m b -> StateT s m a #

(>$) :: b -> StateT s m b -> StateT s m a #

Contravariant m => Contravariant (StateT s m) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> StateT s m b -> StateT s m a #

(>$) :: b -> StateT s m b -> StateT s m a #

Contravariant m => Contravariant (WriterT w m) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> WriterT w m b -> WriterT w m a #

(>$) :: b -> WriterT w m b -> WriterT w m a #

Contravariant m => Contravariant (WriterT w m) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> WriterT w m b -> WriterT w m a #

(>$) :: b -> WriterT w m b -> WriterT w m a #

Contravariant f => Contravariant (Reverse f) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Reverse f b -> Reverse f a #

(>$) :: b -> Reverse f b -> Reverse f a #

Contravariant (Constant a :: * -> *) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a0 -> b) -> Constant a b -> Constant a a0 #

(>$) :: b -> Constant a b -> Constant a a0 #

Contravariant f => Contravariant (Backwards f) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Backwards f b -> Backwards f a #

(>$) :: b -> Backwards f b -> Backwards f a #

Contravariant (K1 i c :: * -> *) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> K1 i c b -> K1 i c a #

(>$) :: b -> K1 i c b -> K1 i c a #

(Contravariant f, Contravariant g) => Contravariant (f :+: g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> (f :+: g) b -> (f :+: g) a #

(>$) :: b -> (f :+: g) b -> (f :+: g) a #

(Contravariant f, Contravariant g) => Contravariant (f :*: g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> (f :*: g) b -> (f :*: g) a #

(>$) :: b -> (f :*: g) b -> (f :*: g) a #

(Contravariant f, Contravariant g) => Contravariant (Product f g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Product f g b -> Product f g a #

(>$) :: b -> Product f g b -> Product f g a #

(Contravariant f, Contravariant g) => Contravariant (Sum f g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Sum f g b -> Sum f g a #

(>$) :: b -> Sum f g b -> Sum f g a #

Contravariant m => Contravariant (ReaderT r m) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> ReaderT r m b -> ReaderT r m a #

(>$) :: b -> ReaderT r m b -> ReaderT r m a #

Contravariant f => Contravariant (M1 i c f) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> M1 i c f b -> M1 i c f a #

(>$) :: b -> M1 i c f b -> M1 i c f a #

(Functor f, Contravariant g) => Contravariant (f :.: g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> (f :.: g) b -> (f :.: g) a #

(>$) :: b -> (f :.: g) b -> (f :.: g) a #

(Functor f, Contravariant g) => Contravariant (Compose f g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Compose f g b -> Compose f g a #

(>$) :: b -> Compose f g b -> Compose f g a #

Contravariant m => Contravariant (RWST r w s m) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> RWST r w s m b -> RWST r w s m a #

(>$) :: b -> RWST r w s m b -> RWST r w s m a #

Contravariant m => Contravariant (RWST r w s m) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> RWST r w s m b -> RWST r w s m a #

(>$) :: b -> RWST r w s m b -> RWST r w s m a #

(<>) :: Semigroup a => a -> a -> a infixr 6 #

An associative operation.

class Semigroup a => Monoid a where #

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:

The method names refer to the monoid of lists under concatenation, but there are many other instances.

Some types can be viewed as a monoid in more than one way, e.g. both addition and multiplication on numbers. In such cases we often define newtypes and make those instances of Monoid, e.g. Sum and Product.

NOTE: Semigroup is a superclass of Monoid since base-4.11.0.0.

Minimal complete definition

mempty

Methods

mempty :: a #

Identity of mappend

mappend :: a -> a -> a #

An associative operation

NOTE: This method is redundant and has the default implementation mappend = '(<>)' since base-4.11.0.0.

mconcat :: [a] -> a #

Fold a list using the monoid.

For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.

Instances
Monoid Ordering

Since: base-2.1

Instance details

Defined in GHC.Base

Monoid ()

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: () #

mappend :: () -> () -> () #

mconcat :: [()] -> () #

Monoid All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid [a]

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: [a] #

mappend :: [a] -> [a] -> [a] #

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

Semigroup a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S."

Since 4.11.0: constraint on inner a value generalised from Monoid to Semigroup.

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

Monoid a => Monoid (IO a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

mempty :: IO a #

mappend :: IO a -> IO a -> IO a #

mconcat :: [IO a] -> IO a #

(Semigroup a, Monoid a) => Monoid (Concurrently a)

Since: async-2.1.0

Instance details

Defined in Control.Concurrent.Async

(Ord a, Bounded a) => Monoid (Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

(Ord a, Bounded a) => Monoid (Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

Monoid m => Monoid (WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Semigroup a => Monoid (Option a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Option a #

mappend :: Option a -> Option a -> Option a #

mconcat :: [Option a] -> Option a #

Monoid a => Monoid (Identity a) 
Instance details

Defined in Data.Functor.Identity

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

Monoid (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

Monoid (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

mconcat :: [Last a] -> Last a #

Monoid a => Monoid (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Dual a #

mappend :: Dual a -> Dual a -> Dual a #

mconcat :: [Dual a] -> Dual a #

Monoid (Endo a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Endo a #

mappend :: Endo a -> Endo a -> Endo a #

mconcat :: [Endo a] -> Endo a #

Num a => Monoid (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

Num a => Monoid (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

Monoid (Predicate a) 
Instance details

Defined in Data.Functor.Contravariant

Monoid (Comparison a) 
Instance details

Defined in Data.Functor.Contravariant

Monoid (Equivalence a) 
Instance details

Defined in Data.Functor.Contravariant

Monoid a => Monoid (Managed a) 
Instance details

Defined in Control.Monad.Managed

Methods

mempty :: Managed a #

mappend :: Managed a -> Managed a -> Managed a #

mconcat :: [Managed a] -> Managed a #

Monoid (Input a) 
Instance details

Defined in Pipes.Concurrent

Methods

mempty :: Input a #

mappend :: Input a -> Input a -> Input a #

mconcat :: [Input a] -> Input a #

Monoid (Output a) 
Instance details

Defined in Pipes.Concurrent

Methods

mempty :: Output a #

mappend :: Output a -> Output a -> Output a #

mconcat :: [Output a] -> Output a #

Monoid (View a) # 
Instance details

Defined in MVC

Methods

mempty :: View a #

mappend :: View a -> View a -> View a #

mconcat :: [View a] -> View a #

Monoid (Controller a) # 
Instance details

Defined in MVC

Monoid b => Monoid (a -> b)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: a -> b #

mappend :: (a -> b) -> (a -> b) -> a -> b #

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

(Monoid a, Monoid b) => Monoid (a, b)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b) #

mappend :: (a, b) -> (a, b) -> (a, b) #

mconcat :: [(a, b)] -> (a, b) #

Monoid a => Monoid (Op a b) 
Instance details

Defined in Data.Functor.Contravariant

Methods

mempty :: Op a b #

mappend :: Op a b -> Op a b -> Op a b #

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

Monoid b => Monoid (Fold a b) 
Instance details

Defined in Control.Foldl

Methods

mempty :: Fold a b #

mappend :: Fold a b -> Fold a b -> Fold a b #

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

Monad m => Monoid (EndoM m a) 
Instance details

Defined in Control.Foldl

Methods

mempty :: EndoM m a #

mappend :: EndoM m a -> EndoM m a -> EndoM m a #

mconcat :: [EndoM m a] -> EndoM m a #

Monad m => Monoid (ListT m a) 
Instance details

Defined in Pipes

Methods

mempty :: ListT m a #

mappend :: ListT m a -> ListT m a -> ListT m a #

mconcat :: [ListT m a] -> ListT m a #

(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c) #

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c) #

mconcat :: [(a, b, c)] -> (a, b, c) #

Monoid a => Monoid (Const a b) 
Instance details

Defined in Data.Functor.Const

Methods

mempty :: Const a b #

mappend :: Const a b -> Const a b -> Const a b #

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

Alternative f => Monoid (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Alt f a #

mappend :: Alt f a -> Alt f a -> Alt f a #

mconcat :: [Alt f a] -> Alt f a #

(Monoid b, Monad m) => Monoid (FoldM m a b) 
Instance details

Defined in Control.Foldl

Methods

mempty :: FoldM m a b #

mappend :: FoldM m a b -> FoldM m a b -> FoldM m a b #

mconcat :: [FoldM m a b] -> FoldM m a b #

Monoid a => Monoid (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

mempty :: Constant a b #

mappend :: Constant a b -> Constant a b -> Constant a b #

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

(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c, d) #

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

mconcat :: [(a, b, c, d)] -> (a, b, c, d) #

(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c, d, e) #

mappend :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) #

(Monad m, Monoid r, Semigroup r) => Monoid (Proxy a' a b' b m r) 
Instance details

Defined in Pipes.Internal

Methods

mempty :: Proxy a' a b' b m r #

mappend :: Proxy a' a b' b m r -> Proxy a' a b' b m r -> Proxy a' a b' b m r #

mconcat :: [Proxy a' a b' b m r] -> Proxy a' a b' b m r #

data First a #

Maybe monoid returning the leftmost non-Nothing value.

First a is isomorphic to Alt Maybe a, but precedes it historically.

>>> getFirst (First (Just "hello") <> First Nothing <> First (Just "world"))
Just "hello"
Instances
Monad First 
Instance details

Defined in Data.Monoid

Methods

(>>=) :: First a -> (a -> First b) -> First b #

(>>) :: First a -> First b -> First b #

return :: a -> First a #

fail :: String -> First a #

Functor First 
Instance details

Defined in Data.Monoid

Methods

fmap :: (a -> b) -> First a -> First b #

(<$) :: a -> First b -> First a #

Applicative First 
Instance details

Defined in Data.Monoid

Methods

pure :: a -> First a #

(<*>) :: First (a -> b) -> First a -> First b #

liftA2 :: (a -> b -> c) -> First a -> First b -> First c #

(*>) :: First a -> First b -> First b #

(<*) :: First a -> First b -> First a #

Foldable First

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => First m -> m #

foldMap :: Monoid m => (a -> m) -> First a -> m #

foldr :: (a -> b -> b) -> b -> First a -> b #

foldr' :: (a -> b -> b) -> b -> First a -> b #

foldl :: (b -> a -> b) -> b -> First a -> b #

foldl' :: (b -> a -> b) -> b -> First a -> b #

foldr1 :: (a -> a -> a) -> First a -> a #

foldl1 :: (a -> a -> a) -> First a -> a #

toList :: First a -> [a] #

null :: First a -> Bool #

length :: First a -> Int #

elem :: Eq a => a -> First a -> Bool #

maximum :: Ord a => First a -> a #

minimum :: Ord a => First a -> a #

sum :: Num a => First a -> a #

product :: Num a => First a -> a #

Traversable First

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> First a -> f (First b) #

sequenceA :: Applicative f => First (f a) -> f (First a) #

mapM :: Monad m => (a -> m b) -> First a -> m (First b) #

sequence :: Monad m => First (m a) -> m (First a) #

Eq a => Eq (First a) 
Instance details

Defined in Data.Monoid

Methods

(==) :: First a -> First a -> Bool #

(/=) :: First a -> First a -> Bool #

Ord a => Ord (First a) 
Instance details

Defined in Data.Monoid

Methods

compare :: First a -> First a -> Ordering #

(<) :: First a -> First a -> Bool #

(<=) :: First a -> First a -> Bool #

(>) :: First a -> First a -> Bool #

(>=) :: First a -> First a -> Bool #

max :: First a -> First a -> First a #

min :: First a -> First a -> First a #

Read a => Read (First a) 
Instance details

Defined in Data.Monoid

Show a => Show (First a) 
Instance details

Defined in Data.Monoid

Methods

showsPrec :: Int -> First a -> ShowS #

show :: First a -> String #

showList :: [First a] -> ShowS #

Generic (First a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (First a) :: * -> * #

Methods

from :: First a -> Rep (First a) x #

to :: Rep (First a) x -> First a #

Semigroup (First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Monoid

Methods

(<>) :: First a -> First a -> First a #

sconcat :: NonEmpty (First a) -> First a #

stimes :: Integral b => b -> First a -> First a #

Monoid (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

Generic1 First 
Instance details

Defined in Data.Monoid

Associated Types

type Rep1 First :: k -> * #

Methods

from1 :: First a -> Rep1 First a #

to1 :: Rep1 First a -> First a #

type Rep (First a) 
Instance details

Defined in Data.Monoid

type Rep (First a) = D1 (MetaData "First" "Data.Monoid" "base" True) (C1 (MetaCons "First" PrefixI True) (S1 (MetaSel (Just "getFirst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe a))))
type Rep1 First 
Instance details

Defined in Data.Monoid

type Rep1 First = D1 (MetaData "First" "Data.Monoid" "base" True) (C1 (MetaCons "First" PrefixI True) (S1 (MetaSel (Just "getFirst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Maybe)))

module Pipes