Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Documentation
data Return r' r a where Source #
Instances
PolyCont (Return r) r Void Source # | |
Defined in Control.Dsl.Return | |
Applicative m => PolyCont (Return r) (m r) Void Source # | |
Defined in Control.Dsl.Return | |
PolyCont (Return r) (Cont r' r) Void Source # | |
Defined in Control.Dsl.Cont | |
PolyCont (Return r) (State s r) Void Source # | |
Defined in Control.Dsl.State.State |
return :: PolyCont (Return r') r Void => r' -> r Source #
Lift r
to the answer type, similar to return
.
This return
function aims to be used as the last statement of a do
block.
When return
is present in a nested do
block for when
or unless
,
if the r
is not ()
,
it will create a Cont
that performs early return,
skipping the rest statements of the outer do
notation.
Examples
>>>
:set -XTypeOperators
>>>
:set -XRebindableSyntax
>>>
import Prelude hiding ((>>), (>>=), return, fail)
>>>
import Control.Dsl
>>>
import Control.Dsl.Return
>>>
import Control.Dsl.Yield
>>>
import Control.Dsl.Cont
>>>
import Control.Dsl.Empty
>>>
:{
earlyGenerator :: Bool -> Cont [String] Integer earlyGenerator earlyReturn = do Yield "inside earlyGenerator" when earlyReturn $ do Yield "early return" return 1 Yield "normal return" return 0 :}
>>>
:{
earlyGeneratorTest :: [String] earlyGeneratorTest = do Yield "before earlyGenerator" i <- earlyGenerator True Yield "after earlyGenerator" Yield $ "the return value of earlyGenerator is " ++ show i empty :}
>>>
earlyGeneratorTest
["before earlyGenerator","inside earlyGenerator","early return","after earlyGenerator","the return value of earlyGenerator is 1"]