Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Provider of the Alternative
and
MonadPlus
instance for Eff
.
Synopsis
- data NonDet :: Effect where
- data OnEmptyPolicy
- runNonDet :: OnEmptyPolicy -> Eff (NonDet : es) a -> Eff es (Either CallStack a)
- emptyEff :: (HasCallStack, NonDet :> es) => Eff es a
- sumEff :: (HasCallStack, Foldable t, NonDet :> es) => t (Eff es a) -> Eff es a
- class Applicative f => Alternative (f :: Type -> Type) where
- type HasCallStack = ?callStack :: CallStack
- data CallStack
- getCallStack :: CallStack -> [([Char], SrcLoc)]
- prettyCallStack :: CallStack -> String
Effect
data NonDet :: Effect where Source #
Provide the ability to use the Alternative
and MonadPlus
instance for
Eff
.
Since: 2.2.0.0
Instances
type DispatchOf NonDet Source # | |
Defined in Effectful.Internal.Monad |
data OnEmptyPolicy Source #
Policy of dealing with modifications to thread local state in the
environment in branches that end up calling the Empty
operation.
Note: OnEmptyKeep
is significantly faster as there is no need to back up
the environment on each call to :<|>:
.
Since: 2.2.0.0
OnEmptyKeep | Keep modifications on |
OnEmptyRollback | Rollback modifications on |
Instances
Generic OnEmptyPolicy Source # | |
Defined in Effectful.NonDet type Rep OnEmptyPolicy :: Type -> Type # from :: OnEmptyPolicy -> Rep OnEmptyPolicy x # to :: Rep OnEmptyPolicy x -> OnEmptyPolicy # | |
Show OnEmptyPolicy Source # | |
Defined in Effectful.NonDet showsPrec :: Int -> OnEmptyPolicy -> ShowS # show :: OnEmptyPolicy -> String # showList :: [OnEmptyPolicy] -> ShowS # | |
Eq OnEmptyPolicy Source # | |
Defined in Effectful.NonDet (==) :: OnEmptyPolicy -> OnEmptyPolicy -> Bool # (/=) :: OnEmptyPolicy -> OnEmptyPolicy -> Bool # | |
Ord OnEmptyPolicy Source # | |
Defined in Effectful.NonDet compare :: OnEmptyPolicy -> OnEmptyPolicy -> Ordering # (<) :: OnEmptyPolicy -> OnEmptyPolicy -> Bool # (<=) :: OnEmptyPolicy -> OnEmptyPolicy -> Bool # (>) :: OnEmptyPolicy -> OnEmptyPolicy -> Bool # (>=) :: OnEmptyPolicy -> OnEmptyPolicy -> Bool # max :: OnEmptyPolicy -> OnEmptyPolicy -> OnEmptyPolicy # min :: OnEmptyPolicy -> OnEmptyPolicy -> OnEmptyPolicy # | |
type Rep OnEmptyPolicy Source # | |
Handlers
runNonDet :: OnEmptyPolicy -> Eff (NonDet : es) a -> Eff es (Either CallStack a) Source #
Run the NonDet
effect with a given OnEmptyPolicy
.
Note: :<|>:
executes the second computation if (and only if) the first
computation calls Empty
.
Since: 2.2.0.0
Utils
emptyEff :: (HasCallStack, NonDet :> es) => Eff es a Source #
Specialized version of empty
with the HasCallStack
constraint for
tracking purposes.
Since: 2.2.0.0
sumEff :: (HasCallStack, Foldable t, NonDet :> es) => t (Eff es a) -> Eff es a Source #
Specialized version of asum
with the HasCallStack
constraint for
tracking purposes.
Since: 2.2.0.0
Re-exports
class Applicative f => Alternative (f :: Type -> Type) where #
A monoid on applicative functors.
If defined, some
and many
should be the least solutions
of the equations:
The identity of <|>
(<|>) :: f a -> f a -> f a infixl 3 #
An associative binary operation
One or more.
Zero or more.
Instances
type HasCallStack = ?callStack :: CallStack #
Request a CallStack.
NOTE: The implicit parameter ?callStack :: CallStack
is an
implementation detail and should not be considered part of the
CallStack
API, we may decide to change the implementation in the
future.
Since: base-4.9.0.0
CallStack
s are a lightweight method of obtaining a
partial call-stack at any point in the program.
A function can request its call-site with the HasCallStack
constraint.
For example, we can define
putStrLnWithCallStack :: HasCallStack => String -> IO ()
as a variant of putStrLn
that will get its call-site and print it,
along with the string given as argument. We can access the
call-stack inside putStrLnWithCallStack
with callStack
.
>>>
:{
putStrLnWithCallStack :: HasCallStack => String -> IO () putStrLnWithCallStack msg = do putStrLn msg putStrLn (prettyCallStack callStack) :}
Thus, if we call putStrLnWithCallStack
we will get a formatted call-stack
alongside our string.
>>>
putStrLnWithCallStack "hello"
hello CallStack (from HasCallStack): putStrLnWithCallStack, called at <interactive>:... in interactive:Ghci...
GHC solves HasCallStack
constraints in three steps:
- If there is a
CallStack
in scope -- i.e. the enclosing function has aHasCallStack
constraint -- GHC will append the new call-site to the existingCallStack
. - If there is no
CallStack
in scope -- e.g. in the GHCi session above -- and the enclosing definition does not have an explicit type signature, GHC will infer aHasCallStack
constraint for the enclosing definition (subject to the monomorphism restriction). - If there is no
CallStack
in scope and the enclosing definition has an explicit type signature, GHC will solve theHasCallStack
constraint for the singletonCallStack
containing just the current call-site.
CallStack
s do not interact with the RTS and do not require compilation
with -prof
. On the other hand, as they are built up explicitly via the
HasCallStack
constraints, they will generally not contain as much
information as the simulated call-stacks maintained by the RTS.
A CallStack
is a [(String, SrcLoc)]
. The String
is the name of
function that was called, the SrcLoc
is the call-site. The list is
ordered with the most recently called function at the head.
NOTE: The intrepid user may notice that HasCallStack
is just an
alias for an implicit parameter ?callStack :: CallStack
. This is an
implementation detail and should not be considered part of the
CallStack
API, we may decide to change the implementation in the
future.
Since: base-4.8.1.0
getCallStack :: CallStack -> [([Char], SrcLoc)] #
Extract a list of call-sites from the CallStack
.
The list is ordered by most recent call.
Since: base-4.8.1.0
prettyCallStack :: CallStack -> String #
Pretty print a CallStack
.
Since: base-4.9.0.0