| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Polysemy.Operators
Description
Operators meant as replacements for traditional Sem type and Member /
 Members constraints, that allow you to specify types of your actions and
 interpreters in more concise way, without mentioning unnecessary details:
foo ::Member(EmbedIO) r =>String->Int->Semr ()
can be written simply as:
foo ::String->Int->IO~@>()
Working example with operators:
import Data.Function import Polysemy import Polysemy.Operators import Polysemy.Random data ConsoleIO m a where WriteStrLn ::String-> ConsoleIO m () ReadStrLn :: ConsoleIO mStringShowStrLn ::Showa => a -> ConsoleIO m ()makeSem''ConsoleIO -- runConsoleIO :: Member (Embed IO) r => Sem (ConsoleIO : r) a -> Sem r a runConsoleIO :: ConsoleIO : r@>a ->IO~@r@>a runConsoleIO =interpret\case WriteStrLn s ->sendM$putStrLns ReadStrLn ->sendMgetLineShowStrLn v ->sendM$IO() main = program&runConsoleIO&runRandomIO&runM-- program :: Members '[Random, ConsoleIO] r => Sem r () program :: '[Random, ConsoleIO]>@>() program = do writeStrLn "It works! Write something:" val <- readStrLn writeStrLn$"Here it is!: "++val num <-random@IntwriteStrLn$"Some random number:" showStrLn num
Please keep in mind that constraints created through these operators are limited to the action they are being used on, for example:
foo :: (forall x. r@>x ->IOx) ->IO(forall a. Foo : r@>a ->IO~@r@>a)
The first argument in the signature above won't have access to the
 ( constraint in the result - in such cases, use a normal
 constraint instead:IO ~@)
foo ::Member(EmbedIO) r => (forall x. r@>x ->IOx) ->IO(forall a. Foo : r@>a -> r@>a)
See the documentation of specific operators for more details.
Synopsis
- type (@>) = Sem
- type (@-) e = Sem '[e]
- type (@~) m = Sem '[Embed m]
- type (>@) es s = Members es (SemList s) => s
- type (-@) e s = Member e (SemList s) => s
- type (~@) m s = Member (Embed m) (SemList s) => s
- type (>@>) es a = forall r. Members es r => Sem r a
- type (-@>) e a = forall r. Member e r => Sem r a
- type (~@>) m a = forall r. Member (Embed m) r => Sem r a
Sem operators
Infix equivalents of Sem with versions for specifiying list of effects
 (@>), single effect (@-) and single monad (@~) as effects of union.
 Use (>@>), (-@>) or (~@>) instead if you are not making any
 transformations on union and just want to use some members instead.
Examples:
Sem with list of multiple effects:
foo ::Sem(StateInt: r) ()
can be written as:
foo ::StateInt: r@>()
Sem with list of one effect:
foo ::Sem'[StateInt] ()
can be written as both (with the latter preferred):
foo :: '[StateInt]@>()
and:
foo ::StateInt@-()
where effect without list gets put into one automatically.
Sem with exactly one, lifted monad:
foo ::Sem'[EmbedIO] ()
can be written simply as:
foo ::IO@~()
and will be automatically lifted and put into list.
Member operators
Infix equivalents of Member(s) constraint used directly in return type,
 specifiying list of members (>@), single member (-@) or single monad
 (~@), meant to be paired with some of the Sem operators ((@>), (@-)
 and (@~)). Use (>@>), (-@>) or (~@>) instead if you are not making
 any transformations on union and just want to use some members instead.
Examples:
List of multiple members:
foo ::Members'[StateInt,InputString] r =>Sem(Output[String] : r) () ->Semr ()
can be written as:
foo ::Output[String] : r@>() -> '[StateInt,InputString]>@r@>()
One member:
foo ::Member(StateInt) r =>Sem(Output[String] : r) () ->Semr ()
can be written as both (with the latter preferred):
foo ::Output[String] : r@>() -> '[StateInt]>@r@>()
and:
foo ::Output[String] : r@>() ->StateInt-@r@>()
Exactly one, lifted monad as a member:
foo ::Member(EmbedIO) r =>Sem(Output[String] : r) () ->Semr ()
can be written simply as:
foo ::Output[String] : r@>() ->IO~@r@>()
Combined operators
Joined versions of one of (>@), (-@), (~@) and (@>) with implicit,
 hidden list of effects in union --- suited for actions that only use one
 Sem in their type.
Examples:
List of members over some Sem:
foo ::Members'[StateString,InputInt] r =>String->Int->Semr ()
can be written as:
foo ::String->Int-> '[StateString,InputInt]>@>()
Single member:
foo ::Member(InputInt) r =>String->Int->Semr ()
can be written as both (with the latter preferred):
foo ::String->Int-> '[InputInt]>@>()
and:
foo ::String->Int->InputInt-@>()
Exactly one, lifted monad as a member:
foo ::Member(EmbedIO) r =>Semr ()
can be written simply as:
foo ::IO~@>()