@@ -395,7 +395,7 @@ module Control.Distributed.Process.FSM
395395 , (~@)
396396 , (~?)
397397 , (^.)
398- -- * Useful / Important Types and Utilities
398+ -- * Types and Utilities
399399 , Event
400400 , FSM
401401 , lift
@@ -426,8 +426,8 @@ import Control.Distributed.Process.FSM.Internal.Types
426426import Control.Distributed.Process.Serializable (Serializable )
427427import Prelude hiding ((*>) )
428428
429- -- | Fluent way to say " yield" when you're building an initial state up (e.g.
430- -- whilst utilising " begin" ).
429+ -- | Fluent way to say ' yield' when you're building an initial state up (e.g.
430+ -- whilst utilising ' begin' ).
431431initState :: forall s d . s -> d -> Step s d
432432initState = yield
433433
@@ -437,13 +437,13 @@ yield :: forall s d . s -> d -> Step s d
437437yield = Yield
438438
439439-- | Creates an @Event m@ for some "Serializable" type @m@. When passed to
440- -- functions that follow the combinator pattern (such as " await" ), will ensure
440+ -- functions that follow the combinator pattern (such as ' await' ), will ensure
441441-- that only messages of type @m@ are processed by the handling expression.
442442--
443443event :: (Serializable m ) => Event m
444444event = Wait
445445
446- -- | A /prioritised/ version of " event" . The server will prioritise messages
446+ -- | A /prioritised/ version of ' event' . The server will prioritise messages
447447-- matching the "Event" type @m@.
448448--
449449-- See "Control.Distributed.Process.ManagedProcess.Server.Priority" for more
@@ -452,8 +452,8 @@ pevent :: (Serializable m) => Int -> Event m
452452pevent = WaitP . setPriority
453453
454454-- | Evaluates to a "Transition" that instructs the process to enter the given
455- -- state @s@. All expressions following evaluation of " enter" will see
456- -- " currentState" containing the updated value, and any future events will be
455+ -- state @s@. All expressions following evaluation of ' enter' will see
456+ -- ' currentState' containing the updated value, and any future events will be
457457-- processed in the new state.
458458--
459459-- In addition, should any events/messages have been postponed in a previous
@@ -486,7 +486,7 @@ putBack = return PutBack
486486nextEvent :: forall s d m . (Serializable m ) => m -> FSM s d (Transition s d )
487487nextEvent m = return $ Push (wrapMessage m)
488488
489- -- | As " nextEvent" , but places the message at the back of the queue by default.
489+ -- | As ' nextEvent' , but places the message at the back of the queue by default.
490490--
491491-- Mailbox priority ordering will still take precedence over insertion order.
492492--
@@ -502,7 +502,7 @@ resume = return Remain
502502-- sending its event to the process.
503503--
504504-- The expression used to produce the reply message must reside in the "FSM" monad.
505- -- The reply is /not/ sent immediately upon evaluating " reply" , however if the
505+ -- The reply is /not/ sent immediately upon evaluating ' reply' , however if the
506506-- sender supplied a reply channel, the reply is guaranteed to be sent prior to
507507-- evaluating the next pass.
508508--
@@ -532,7 +532,7 @@ stop = return . Stop
532532--
533533-- This expression functions as a "Transition" and is not applied immediately.
534534-- To /see/ state data changes in subsequent expressions during a single pass,
535- -- use " yield" instead.
535+ -- use ' yield' instead.
536536set :: forall s d . (d -> d ) -> FSM s d (Transition s d )
537537set f = return $ Eval (processState >>= \ s -> setProcessState $ s { stData = (f $ stData s) })
538538
@@ -543,12 +543,12 @@ set_ f = set f >>= addTransition
543543--
544544-- This expression functions as a "Transition" and is not applied immediately.
545545-- To /see/ state data changes in subsequent expressions during a single pass,
546- -- use " yield" instead.
546+ -- use ' yield' instead.
547547put :: forall s d . d -> FSM s d ()
548548put d = addTransition $ Eval $ do
549549 processState >>= \ s -> setProcessState $ s { stData = d }
550550
551- -- | Synonym for " pick"
551+ -- | Synonym for ' pick'
552552(.|) :: Step s d -> Step s d -> Step s d
553553(.|) = Alternate
554554infixr 9 .|
@@ -558,7 +558,7 @@ infixr 9 .|
558558pick :: Step s d -> Step s d -> Step s d
559559pick = Alternate
560560
561- -- | Synonym for " begin"
561+ -- | Synonym for ' begin'
562562(^.) :: Step s d -> Step s d -> Step s d
563563(^.) = Init
564564infixr 9 ^.
@@ -568,7 +568,7 @@ infixr 9 ^.
568568begin :: Step s d -> Step s d -> Step s d
569569begin = Init
570570
571- -- | Synonym for " join" .
571+ -- | Synonym for ' join' .
572572(|>) :: Step s d -> Step s d -> Step s d
573573(|>) = Sequence
574574infixr 9 |>
@@ -582,10 +582,11 @@ join = Sequence
582582(<|) = flip Sequence
583583-- infixl 9 <|
584584
585+ -- | Join from right to left.
585586reverseJoin :: Step s d -> Step s d -> Step s d
586587reverseJoin = flip Sequence
587588
588- -- | Synonym for " await"
589+ -- | Synonym for ' await'
589590(~>) :: forall s d m . (Serializable m ) => Event m -> Step s d -> Step s d
590591(~>) = Await
591592infixr 9 ~>
@@ -595,27 +596,27 @@ infixr 9 ~>
595596await :: forall s d m . (Serializable m ) => Event m -> Step s d -> Step s d
596597await = Await
597598
598- -- | Synonym for " safeWait"
599+ -- | Synonym for ' safeWait'
599600(*>) :: forall s d m . (Serializable m ) => Event m -> Step s d -> Step s d
600601(*>) = SafeWait
601602infixr 9 *>
602603
603- -- | A /safe/ version of " await" . The FSM will place a @check $ safe@ filter
604+ -- | A /safe/ version of ' await' . The FSM will place a @check $ safe@ filter
604605-- around all messages matching the input type @m@ of the "Event" argument.
605606-- Should an exit signal interrupt the current pass, the input event will be
606607-- re-tried if an exit handler can be found for the exit-reason.
607608--
608- -- In all other respects, this API behaves exactly like " await"
609+ -- In all other respects, this API behaves exactly like ' await'
609610safeWait :: forall s d m . (Serializable m ) => Event m -> Step s d -> Step s d
610611safeWait = SafeWait
611612
612- -- | Synonym for " atState"
613+ -- | Synonym for ' atState'
613614(~@) :: forall s d . (Eq s ) => s -> FSM s d (Transition s d ) -> Step s d
614615(~@) = Perhaps
615616infixr 9 ~@
616617
617618-- | Given a state @s@ and an expression that evaluates to a "Transition",
618- -- proceed with evaluation only if the " currentState" is equal to @s@.
619+ -- proceed with evaluation only if the ' currentState' is equal to @s@.
619620atState :: forall s d . (Eq s ) => s -> FSM s d (Transition s d ) -> Step s d
620621atState = Perhaps
621622
@@ -629,11 +630,11 @@ whenStateIs s = s ~@ resume
629630allState :: forall s d m . (Serializable m ) => (m -> FSM s d (Transition s d )) -> Step s d
630631allState = Always
631632
632- -- | Synonym for " allState" .
633+ -- | Synonym for ' allState' .
633634always :: forall s d m . (Serializable m ) => (m -> FSM s d (Transition s d )) -> Step s d
634635always = Always
635636
636- -- | Synonym for " matching" .
637+ -- | Synonym for ' matching' .
637638(~?) :: forall s d m . (Serializable m ) => (m -> Bool ) -> (m -> FSM s d (Transition s d )) -> Step s d
638639(~?) = Matching
639640
0 commit comments