Skip to content
This repository was archived by the owner on Feb 15, 2025. It is now read-only.

Commit 1bf48e6

Browse files
committed
docs
1 parent ae55627 commit 1bf48e6

File tree

4 files changed

+61
-26
lines changed

4 files changed

+61
-26
lines changed

src/Control/Distributed/Process/FSM.hs

Lines changed: 23 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -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
426426
import Control.Distributed.Process.Serializable (Serializable)
427427
import 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').
431431
initState :: forall s d . s -> d -> Step s d
432432
initState = yield
433433

@@ -437,13 +437,13 @@ yield :: forall s d . s -> d -> Step s d
437437
yield = 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
--
443443
event :: (Serializable m) => Event m
444444
event = 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
452452
pevent = 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
486486
nextEvent :: forall s d m . (Serializable m) => m -> FSM s d (Transition s d)
487487
nextEvent 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.
536536
set :: forall s d . (d -> d) -> FSM s d (Transition s d)
537537
set 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.
547547
put :: forall s d . d -> FSM s d ()
548548
put 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
554554
infixr 9 .|
@@ -558,7 +558,7 @@ infixr 9 .|
558558
pick :: Step s d -> Step s d -> Step s d
559559
pick = Alternate
560560

561-
-- | Synonym for "begin"
561+
-- | Synonym for 'begin'
562562
(^.) :: Step s d -> Step s d -> Step s d
563563
(^.) = Init
564564
infixr 9 ^.
@@ -568,7 +568,7 @@ infixr 9 ^.
568568
begin :: Step s d -> Step s d -> Step s d
569569
begin = Init
570570

571-
-- | Synonym for "join".
571+
-- | Synonym for 'join'.
572572
(|>) :: Step s d -> Step s d -> Step s d
573573
(|>) = Sequence
574574
infixr 9 |>
@@ -582,10 +582,11 @@ join = Sequence
582582
(<|) = flip Sequence
583583
-- infixl 9 <|
584584

585+
-- | Join from right to left.
585586
reverseJoin :: Step s d -> Step s d -> Step s d
586587
reverseJoin = 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
591592
infixr 9 ~>
@@ -595,27 +596,27 @@ infixr 9 ~>
595596
await :: forall s d m . (Serializable m) => Event m -> Step s d -> Step s d
596597
await = 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
601602
infixr 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'
609610
safeWait :: forall s d m . (Serializable m) => Event m -> Step s d -> Step s d
610611
safeWait = 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
615616
infixr 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@.
619620
atState :: forall s d . (Eq s) => s -> FSM s d (Transition s d) -> Step s d
620621
atState = Perhaps
621622

@@ -629,11 +630,11 @@ whenStateIs s = s ~@ resume
629630
allState :: forall s d m . (Serializable m) => (m -> FSM s d (Transition s d)) -> Step s d
630631
allState = Always
631632

632-
-- | Synonym for "allState".
633+
-- | Synonym for 'allState'.
633634
always :: forall s d m . (Serializable m) => (m -> FSM s d (Transition s d)) -> Step s d
634635
always = 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

src/Control/Distributed/Process/FSM/Client.hs

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -44,6 +44,8 @@ import Control.Distributed.Process.FSM.Internal.Types (baseErr)
4444
import Control.Distributed.Process.Serializable (Serializable)
4545
import Control.Monad.Catch (bracket)
4646

47+
-- | Initiate a 'call' and if an exit signal arrives, return it as
48+
-- @Left reason@, otherwise evaluate to @Right result@.
4749
safeCall :: (Serializable m, Serializable r)
4850
=> ProcessId
4951
-> m
@@ -57,6 +59,9 @@ safeCall pid msg = do
5759
weFailed a b (ExitOther _) = a == b
5860
weFailed _ _ _ = False
5961

62+
-- | As 'call' but times out if the response does not arrive without the
63+
-- specified "TimeInterval". If the call times out, the caller's mailbox
64+
-- is not affected (i.e. no message will arrive at a later time).
6065
callTimeout :: (Serializable m, Serializable r)
6166
=> ProcessId
6267
-> m
@@ -77,6 +82,11 @@ callTimeout pid msg ti = bracket (monitor pid) unmonitor $ \mRef -> do
7782
Just r -> return $ Just r
7883
_ -> die $ ExitOther $ baseErr ++ ".Client:InvalidResponseType"
7984

85+
-- | Make a synchronous /call/ to the FSM process at "ProcessId". If a
86+
-- "Step" exists that upon receiving an event of type @m@ will eventually
87+
-- reply to the caller, the reply will be the result of evaluating this
88+
-- function. If not, or if the types do not match up, this function will
89+
-- block indefinitely.
8090
call :: (Serializable m, Serializable r) => ProcessId -> m -> Process r
8191
call pid msg = bracket (monitor pid) unmonitor $ \mRef -> do
8292
(sp, rp) <- newChan :: Process (SendPort Message, ReceivePort Message)

src/Control/Distributed/Process/FSM/Internal/Process.hs

Lines changed: 14 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,20 @@
22
{-# LANGUAGE ScopedTypeVariables #-}
33
{-# LANGUAGE PatternGuards #-}
44
{-# LANGUAGE RecordWildCards #-}
5-
5+
-----------------------------------------------------------------------------
6+
-- |
7+
-- Module : Control.Distributed.Process.FSM.Internal.Process
8+
-- Copyright : (c) Tim Watson 2017
9+
-- License : BSD3 (see the file LICENSE)
10+
--
11+
-- Maintainer : Tim Watson <[email protected]>
12+
-- Stability : experimental
13+
-- Portability : non-portable (requires concurrency)
14+
--
15+
-- The /Managed Process/ implementation of an FSM process.
16+
--
17+
-- See "Control.Distributed.Process.ManagedProcess".
18+
-----------------------------------------------------------------------------
619
module Control.Distributed.Process.FSM.Internal.Process
720
( start
821
, run

src/Control/Distributed/Process/FSM/Internal/Types.hs

Lines changed: 14 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,18 @@
88
{-# LANGUAGE MultiParamTypeClasses #-}
99
{-# LANGUAGE GADTs #-}
1010
{-# LANGUAGE RankNTypes #-}
11-
11+
-----------------------------------------------------------------------------
12+
-- |
13+
-- Module : Control.Distributed.Process.FSM.Internal.Types
14+
-- Copyright : (c) Tim Watson 2017
15+
-- License : BSD3 (see the file LICENSE)
16+
--
17+
-- Maintainer : Tim Watson <[email protected]>
18+
-- Stability : experimental
19+
-- Portability : non-portable (requires concurrency)
20+
--
21+
-- Types and common functionality.
22+
-----------------------------------------------------------------------------
1223
module Control.Distributed.Process.FSM.Internal.Types
1324
( apply
1425
, applyTransitions
@@ -219,11 +230,11 @@ stateData = ST.get >>= return . stData
219230
currentMessage :: forall s d . FSM s d P.Message
220231
currentMessage = ST.get >>= return . fromJust . stInput
221232

222-
-- | Retrieve the "currentMessage" and attempt to decode it to type @m@
233+
-- | Retrieve the 'currentMessage' and attempt to decode it to type @m@
223234
currentInput :: forall s d m . (Serializable m) => FSM s d (Maybe m)
224235
currentInput = currentMessage >>= \m -> lift (unwrapMessage m :: Process (Maybe m))
225236

226-
-- | A a "Transition" to be evaluated once the current pass completes.
237+
-- | Add a "Transition" to be evaluated once the current pass completes.
227238
addTransition :: Transition s d -> FSM s d ()
228239
addTransition t = ST.modify (\s -> fromJust $ enqueue s (Just t) )
229240

0 commit comments

Comments
 (0)