Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- module Control.Dsl.State.Put
- module Control.Dsl.State.Get
- type State = (->)
Documentation
module Control.Dsl.State.Put
module Control.Dsl.State.Get
The type that holds states, which is defined as a plain function.
Examples
>>>
:set -XFlexibleContexts
>>>
:set -XTypeApplications
>>>
:set -XRebindableSyntax
>>>
import Prelude hiding ((>>), (>>=), return, fail)
>>>
import Control.Dsl
>>>
import Control.Dsl.Cont
>>>
import Control.Dsl.Shift
>>>
import Control.Dsl.State
>>>
import Data.Sequence (Seq, (|>))
>>>
import qualified Data.Sequence
>>>
import Data.Foldable
The following append
function Get
s a Seq String
state,
appends s
to the Seq
,
and Put
s the new Seq
to the updated state.
>>>
:{
append s = do buffer <- Get @(Seq String) Put $ buffer |> s Cont ($ ()) :}
($ ())
creates a CPS function ,
which can be then converted to Cont
s.
A formatter
append
s String
to its internal buffer,
and return
the concatenated buffer.
>>>
:{
formatter = do append "x=" d <- Get @Double append $ show d append ",y=" i <- Get @Integer append $ show i buffer <- Get @(Seq String) return $ concat buffer :}
>>>
x = 0.5 :: Double
>>>
y = 42 :: Integer
>>>
initialBuffer = Data.Sequence.empty :: Seq String
>>>
formatter x y initialBuffer :: String
"x=0.5,y=42"
Note that formatter
accepts arbitrary order of the parameters,
or additional unused parameters.
>>>
formatter "unused parameter" initialBuffer y x :: String
"x=0.5,y=42"