{-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE LambdaCase #-} module Connection where import Control.Applicative import Control.Arrow import Control.Concurrent.STM import qualified Data.Map as Map ;import Data.Map (Map) import PingMachine -- | This type indicates the current status of a connection. The type -- parameter indicates protocol-specific status information. To present -- information as a user-comprehensible string, use 'showStatus'. data Status status = Dormant | InProgress status | Established deriving (Show,Eq,Ord,Functor) -- | A policy indicates a desired connection status. data Policy = RefusingToConnect -- ^ We desire no connection. | OpenToConnect -- ^ We will cooperate if a remote side initiates. | TryingToConnect -- ^ We desire to be connected. deriving (Eq,Ord,Show) -- | Information obtained via the 'connectionStatus' interface to -- 'Manager'. data Connection status = Connection { connStatus :: Status status , connPolicy :: Policy } deriving Functor -- | This is an interface to make or query status information about connections -- of a specific kind. -- -- Type parameters: -- -- /k/ names a connection. It should implement Ord, and can be parsed and -- displayed using 'stringToKey' and 'showKey'. -- -- /status/ indicates the progress of a connection. It is intended as a -- parameter to the 'InProgress' constructor of 'Status'. -- data Manager status k = Manager { -- | Connect or disconnect a connection. setPolicy :: k -> Policy -> IO () -- | Lookup a connection status. , status :: k -> STM (Connection status) -- | Obtain a list of all known connections. , connections :: STM [k] -- | Parse a connection key out of a string. Inverse of 'showKey'. , stringToKey :: String -> Maybe k -- | Convert a progress value to a string. , showProgress :: status -> String -- | Show a connection key as a string. , showKey :: k -> String } -- | Present status information (visible in a UI) for a connection. showStatus :: Manager status k -> Status status -> String showStatus mgr Dormant = "dormant" showStatus mgr Established = "established" showStatus mgr (InProgress s) = "in progress ("++showProgress mgr s++")" -- | Combine two different species of 'Manager' into a single interface using -- 'Either' to combine key and status types. addManagers :: (Ord kA, Ord kB) => Manager statusA kA -> Manager statusB kB -> Manager (Either statusA statusB) (Either kA kB) addManagers mgrA mgrB = Manager { setPolicy = either (setPolicy mgrA) (setPolicy mgrB) , status = \case Left k -> fmap Left <$> status mgrA k Right k -> fmap Right <$> status mgrB k , connections = do as <- connections mgrA bs <- connections mgrB return $ map Left as ++ map Right bs , stringToKey = \str -> Left <$> stringToKey mgrA str <|> Right <$> stringToKey mgrB str , showProgress = either (showProgress mgrA) (showProgress mgrB) , showKey = either (showKey mgrA) (showKey mgrB) }