| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell98 | 
MVC
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 - mvclibrary 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 - mvclibrary to illustrate the core types and concepts:
- Exercise your model with property-based testing (like 
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 externalThis program has three components:
- A - Controllerthat interleaves lines from standard input with periodic ticks- A Viewthat writes lines to standard output
- A pure Model, which forwards lines until the user inputs "quit"
 - runMVCconnects them into a complete program, which outputs a- ()every second and also echoes standard input to standard output until the user enters "quit":
- A 
>>>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.
- data Controller a
- asInput :: Input a -> Controller a
- keeps :: ((b -> Constant (First b) b) -> a -> Constant (First b) a) -> Controller a -> Controller b
- data View a
- asSink :: (a -> IO ()) -> View a
- asFold :: FoldM IO a () -> View a
- handles :: HandlerM IO a b -> View b -> View a
- data Model s a b
- asPipe :: Pipe a b (State s) () -> Model s a b
- runMVC :: s -> Model s a b -> Managed (View b, Controller a) -> IO s
- data Managed a :: * -> *
- managed :: (forall r. (a -> IO r) -> IO r) -> Managed a
- loop :: Monad m => (a -> ListT m b) -> Pipe a b m r
- module Data.Functor.Constant
- module Data.Functor.Contravariant
- module Data.Monoid
- module Pipes
- module Pipes.Concurrent
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) controllerCCombining 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
asInput :: Input a -> Controller a Source
Create a Controller from an Input
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) viewFCombining 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
An effectful sink
contramap f (v1 <> v2) = contramap f v1 <> contramap f v2 contramap f mempty = mempty
Instances
| Contravariant View | |
| Monoid (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.
A (Model s a b) converts a stream of (a)s into a stream of (b)s while
    interacting with a state (s)
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.
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.
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.
ListT
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 cOther 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  _      = FalseSo 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
module Data.Functor.Constant
module Data.Functor.Contravariant
module Data.Monoid
module Pipes
module Pipes.Concurrent