do-notation-dsl-0.1.0.1: An alternative to monads

Safe HaskellSafe
LanguageHaskell2010

Control.Dsl.State

Description

This module provides the ability to Put and Get the value of multiple mutable variables in a do block.

>>> :set -XTypeApplications
>>> :set -XRebindableSyntax
>>> import Prelude hiding ((>>), (>>=), return)
>>> import Control.Dsl
>>> import Data.Sequence
>>> :set -fprint-potential-instances
>>> :{
formatter :: Double -> Integer -> Seq String -> String
formatter = do
  --
  -- Equivalent of `!Put(!Get[Vector[Any]] :+ "x=")` in Dsl.scala
  tmpBuffer0 <- Get @(Seq String)
  Put $ tmpBuffer0 |> "x="
  --
  -- Equivalent of `!Put(!Get[Vector[Any]] :+ !Get[Double])` in Dsl.scala
  tmpBuffer1 <- Get @(Seq String)
  d <- Get @Double
  Put $ tmpBuffer1 |> show d
  --
  -- Equivalent of `!Put(!Get[Vector[Any]] :+ ",y=")` in Dsl.scala
  tmpBuffer2 <- Get @(Seq String)
  Put $ tmpBuffer2 |> ",y="
  --
  -- Equivalent of `!Put(!Get[Vector[Any]] :+ !Get[Int])` in Dsl.scala
  tmpBuffer3 <- Get @(Seq String)
  i <- Get @Integer
  Put $ tmpBuffer3 |>  show i
  --
  -- Equivalent of `!Return((!Get[Vector[Any]]).mkString)` in Dsl.scala
  tmpBuffer4 <- Get @(Seq String)
  return $ foldl1 (++) tmpBuffer4
:}
>>> formatter 0.5 42 Empty
"x=0.5,y=42"

Documentation

type State a b = a -> b Source #

data Put a r u where Source #

Constructors

Put :: a -> Put a r () 
Instances
Dsl (Put a) (State a b) () Source # 
Instance details

Defined in Control.Dsl.State

Methods

cpsApply :: Put a r0 () -> State a b !! () Source #

data Get r a where Source #

Constructors

Get :: forall a r. Get r a 
Instances
Dsl Get (State a b) a Source # 
Instance details

Defined in Control.Dsl.State

Methods

cpsApply :: Get r0 a -> State a b !! a Source #