module Control.Distributed.Process.Supervisor.Types
(
ChildSpec(..)
, ChildKey
, ChildType(..)
, ChildTerminationPolicy(..)
, ChildStart(..)
, RegisteredName(LocalName, GlobalName, CustomRegister)
, RestartPolicy(..)
, ChildRef(..)
, isRunning
, isRestarting
, Child
, StaticLabel
, SupervisorPid
, ChildPid
, StarterPid
, MaxRestarts(..)
, maxRestarts
, RestartLimit(..)
, limit
, defaultLimits
, RestartMode(..)
, RestartOrder(..)
, RestartStrategy(..)
, ShutdownMode(..)
, restartOne
, restartAll
, restartLeft
, restartRight
, AddChildResult(..)
, StartChildResult(..)
, TerminateChildResult(..)
, DeleteChildResult(..)
, RestartChildResult(..)
, SupervisorStats(..)
, StartFailure(..)
, ChildInitFailure(..)
) where
import GHC.Generics
import Data.Typeable (Typeable)
import Data.Binary
import Control.DeepSeq (NFData)
import Control.Distributed.Process hiding (call)
import Control.Distributed.Process.Serializable()
import Control.Distributed.Process.Extras.Time
import Control.Distributed.Process.Extras.Internal.Primitives hiding (monitor)
import Control.Exception (Exception)
type SupervisorPid = ProcessId
type ChildPid = ProcessId
type StarterPid = ProcessId
newtype MaxRestarts = MaxR { maxNumberOfRestarts :: Int }
deriving (Typeable, Generic, Show)
instance Binary MaxRestarts where
instance NFData MaxRestarts where
maxRestarts :: Int -> MaxRestarts
maxRestarts r | r >= 0 = MaxR r
| otherwise = error "MaxR must be >= 0"
data RestartLimit =
RestartLimit
{ maxR :: !MaxRestarts
, maxT :: !TimeInterval
}
deriving (Typeable, Generic, Show)
instance Binary RestartLimit where
instance NFData RestartLimit where
limit :: MaxRestarts -> TimeInterval -> RestartLimit
limit mr = RestartLimit mr
defaultLimits :: RestartLimit
defaultLimits = limit (MaxR 1) (seconds 1)
data RestartOrder = LeftToRight | RightToLeft
deriving (Typeable, Generic, Eq, Show)
instance Binary RestartOrder where
instance NFData RestartOrder where
data RestartMode =
RestartEach { order :: !RestartOrder }
| RestartInOrder { order :: !RestartOrder }
| RestartRevOrder { order :: !RestartOrder }
deriving (Typeable, Generic, Show, Eq)
instance Binary RestartMode where
instance NFData RestartMode where
data ShutdownMode = SequentialShutdown !RestartOrder
| ParallelShutdown
deriving (Typeable, Generic, Show, Eq)
instance Binary ShutdownMode where
instance NFData ShutdownMode where
data RestartStrategy =
RestartOne
{ intensity :: !RestartLimit
}
| RestartAll
{ intensity :: !RestartLimit
, mode :: !RestartMode
}
| RestartLeft
{ intensity :: !RestartLimit
, mode :: !RestartMode
}
| RestartRight
{ intensity :: !RestartLimit
, mode :: !RestartMode
}
deriving (Typeable, Generic, Show)
instance Binary RestartStrategy where
instance NFData RestartStrategy where
restartOne :: RestartStrategy
restartOne = RestartOne defaultLimits
restartAll :: RestartStrategy
restartAll = RestartAll defaultLimits (RestartEach LeftToRight)
restartLeft :: RestartStrategy
restartLeft = RestartLeft defaultLimits (RestartEach LeftToRight)
restartRight :: RestartStrategy
restartRight = RestartRight defaultLimits (RestartEach LeftToRight)
type ChildKey = String
data ChildRef =
ChildRunning !ChildPid
| ChildRunningExtra !ChildPid !Message
| ChildRestarting !ChildPid
| ChildStopped
| ChildStartIgnored
deriving (Typeable, Generic, Show)
instance Binary ChildRef where
instance NFData ChildRef where
instance Eq ChildRef where
ChildRunning p1 == ChildRunning p2 = p1 == p2
ChildRunningExtra p1 _ == ChildRunningExtra p2 _ = p1 == p2
ChildRestarting p1 == ChildRestarting p2 = p1 == p2
ChildStopped == ChildStopped = True
ChildStartIgnored == ChildStartIgnored = True
_ == _ = False
isRunning :: ChildRef -> Bool
isRunning (ChildRunning _) = True
isRunning (ChildRunningExtra _ _) = True
isRunning _ = False
isRestarting :: ChildRef -> Bool
isRestarting (ChildRestarting _) = True
isRestarting _ = False
instance Resolvable ChildRef where
resolve (ChildRunning pid) = return $ Just pid
resolve (ChildRunningExtra pid _) = return $ Just pid
resolve _ = return Nothing
instance Routable ChildRef where
sendTo (ChildRunning addr) = sendTo addr
sendTo _ = error "invalid address for child process"
unsafeSendTo (ChildRunning ch) = unsafeSendTo ch
unsafeSendTo _ = error "invalid address for child process"
data ChildType = Worker | Supervisor
deriving (Typeable, Generic, Show, Eq)
instance Binary ChildType where
instance NFData ChildType where
data RestartPolicy =
Permanent
| Temporary
| Transient
| Intrinsic
deriving (Typeable, Generic, Eq, Show)
instance Binary RestartPolicy where
instance NFData RestartPolicy where
data ChildTerminationPolicy =
TerminateTimeout !Delay
| TerminateImmediately
deriving (Typeable, Generic, Eq, Show)
instance Binary ChildTerminationPolicy where
instance NFData ChildTerminationPolicy where
data RegisteredName =
LocalName !String
| GlobalName !String
| CustomRegister !(Closure (ChildPid -> Process ()))
deriving (Typeable, Generic)
instance Binary RegisteredName where
instance NFData RegisteredName where
instance Show RegisteredName where
show (CustomRegister _) = "Custom Register"
show (LocalName n) = n
show (GlobalName n) = "global::" ++ n
data ChildStart =
RunClosure !(Closure (Process ()))
| CreateHandle !(Closure (SupervisorPid -> Process (ChildPid, Message)))
| StarterProcess !StarterPid
deriving (Typeable, Generic, Show)
instance Binary ChildStart where
instance NFData ChildStart where
data ChildSpec = ChildSpec {
childKey :: !ChildKey
, childType :: !ChildType
, childRestart :: !RestartPolicy
, childStop :: !ChildTerminationPolicy
, childStart :: !ChildStart
, childRegName :: !(Maybe RegisteredName)
} deriving (Typeable, Generic, Show)
instance Binary ChildSpec where
instance NFData ChildSpec where
data ChildInitFailure =
ChildInitFailure !String
| ChildInitIgnore
deriving (Typeable, Generic, Show)
instance Exception ChildInitFailure where
data SupervisorStats = SupervisorStats {
_children :: Int
, _supervisors :: Int
, _workers :: Int
, _running :: Int
, _activeSupervisors :: Int
, _activeWorkers :: Int
, totalRestarts :: Int
} deriving (Typeable, Generic, Show)
instance Binary SupervisorStats where
instance NFData SupervisorStats where
type StaticLabel = String
data StartFailure =
StartFailureDuplicateChild !ChildRef
| StartFailureAlreadyRunning !ChildRef
| StartFailureBadClosure !StaticLabel
| StartFailureDied !DiedReason
deriving (Typeable, Generic, Show, Eq)
instance Binary StartFailure where
instance NFData StartFailure where
data DeleteChildResult =
ChildDeleted
| ChildNotFound
| ChildNotStopped !ChildRef
deriving (Typeable, Generic, Show, Eq)
instance Binary DeleteChildResult where
instance NFData DeleteChildResult where
type Child = (ChildRef, ChildSpec)
data AddChildResult =
ChildAdded !ChildRef
| ChildFailedToStart !StartFailure
deriving (Typeable, Generic, Show, Eq)
instance Binary AddChildResult where
instance NFData AddChildResult where
data StartChildResult =
ChildStartOk !ChildRef
| ChildStartFailed !StartFailure
| ChildStartUnknownId
| ChildStartInitIgnored
deriving (Typeable, Generic, Show, Eq)
instance Binary StartChildResult where
instance NFData StartChildResult where
data RestartChildResult =
ChildRestartOk !ChildRef
| ChildRestartFailed !StartFailure
| ChildRestartUnknownId
| ChildRestartIgnored
deriving (Typeable, Generic, Show, Eq)
instance Binary RestartChildResult where
instance NFData RestartChildResult where
data TerminateChildResult =
TerminateChildOk
| TerminateChildUnknownId
deriving (Typeable, Generic, Show, Eq)
instance Binary TerminateChildResult where
instance NFData TerminateChildResult where