caps-0.1: Monadic capabilities with late binding
Safe HaskellNone
LanguageHaskell2010

Monad.Capabilities

Description

Monadic capabilities are additional methods for a base monad. For instance, when our base monad is IO, our capabilities might include logging, networking, database access, and so on.

This framework allows mutually recursive late-bound capabilities with runtime dispatch and a type-safe interface.

A capability is defined as a record type with methods parametrized over a base monad:

data Logging m =
  Logging
    { _logError :: String -> m (),
      _logDebug :: String -> m ()
    }

We can define implementations as values of this record type:

loggingDummy :: Monad m => CapImpl Logging '[] m
loggingDummy = CapImpl $ Logging (\_ -> return ()) (\_ -> return ())

loggingIO :: MonadIO m => CapImpl Logging '[] m
loggingIO = CapImpl $
  Logging
    { _logError = \msg -> liftIO . putStrLn $ "[Error] " ++ msg
      _logDebug = \msg -> liftIO . putStrLn $ "[Debug] " ++ msg
    }

The dictionary is wrapped in CapImpl to guarantee that it is sufficiently polymorphic (this is required to support simultaneous use of monadic actions in negative position and capability extension).

Then we want to use this capability in the CapsT monad (which is nothing more but a synonym for ReaderT of Capabilities), and for this we define a helper per method:

logError :: HasCap Logging caps => String -> CapsT caps m ()
logError message = withCap $ \cap -> _logError cap message

logDebug :: HasCap Logging caps => String -> CapsT caps m ()
logDebug message = withCap $ \cap -> _logDebug cap message

We can define other capabilities in a similar manner:

data Networking m =
  Networking
    { _sendRequest :: ByteString -> m ByteString }

data FileStorage m =
  FileStorage
    { _readFile :: FilePath -> m ByteString,
      _writeFile :: FilePath -> ByteString -> m ()
    }

Implementations of capabilities may depend on other capabilities, which are listed in their signature. For instance, this is how we can define the FileStorage capability using the Logging capability:

fileStorageIO :: MonadIO m => CapImpl FileStorage '[Logging] m
fileStorageIO = CapImpl $
  FileStorage
    { _readFile = \path -> do
        logDebug $ "readFile " ++ path
        lift $ ByteString.readFile path
      _writeFile = \path content -> do
        logDebug $
          "writeFile " ++ path ++
          " (" ++ show (ByteString.length content) ++
          " bytes)"
        lift $ ByteString.writeFile path content
    }

Here the fileStorageIO implementation requires a logging capability, but it's not specified which one.

When we decided what set of capabilities our application needs, we can put them together in a Capabilities map and run the application with this map in a ReaderT context:

caps = buildCaps $
  AddCap loggingIO $
  AddCap fileStorageIO $
  BaseCaps emptyCaps

flip runReaderT caps $ do
  config <- readFile "config.yaml"
  ...

Capabilities passed to buildCaps can depend on each other. The order does not matter (although it is reflected in the types), and duplicate capabilities are disallowed.

We can override a capability locally:

do
  config <- readFile "config.yaml"
  withReaderT (overrideCap loggingDummy) $ do
    -- logging is disabled here
    writeFile "config-backup.yaml" config
    ...

or we can add more capabilities:

do
  config <- readFile "config.yaml"
  networkingImpl <- parseNetworkingConfig config
  withReaderT (addCap networkingImpl) $ do
    -- networking capability added
    resp <- sendRequest req
    ...
Synopsis

Capabilities

data Capabilities (caps :: [CapK]) (m :: MonadK) Source #

Capabilities caps m is a map of capabilities caps over a base monad m. Consider the following capabilities:

data X m = X (String -> m String)
data Y m = Y (Int -> m Bool)

We can construct a map of capabilities with the following type:

capsXY :: Capabilities '[X, Y] IO

In this case, capsXY would be a map with two elements, one at key X and one at key Y. The types of capabilities themselves serve as keys.

Capabilities is a heterogeneous collection, meaning that its values have different types. The type of a value is determined by the key:

 X:   X (\_ -> return "hi") :: X (CapsT '[X, Y] IO)
 Y:   Y (\_ -> return True) :: Y (CapsT '[X, Y] IO)
----  ---------------------    --------------------
keys         values              types of values

Notice that stored dictionaries are parametrized not just by the base monad IO, but with the CapsT transformer on top. This means that each capability has access to all other capabilities and itself.

Instances

Instances details
Show (Capabilities caps m) Source # 
Instance details

Defined in Monad.Capabilities

Methods

showsPrec :: Int -> Capabilities caps m -> ShowS #

show :: Capabilities caps m -> String #

showList :: [Capabilities caps m] -> ShowS #

type CapsT caps m = ReaderT (Capabilities caps m) m Source #

The CapsT transformer adds access to capabilities. This is a convenience synonym for ReaderT of Capabilities, and all ReaderT functions (runReaderT, withReaderT) can be used with it.

buildCaps :: forall caps m. CapabilitiesBuilder caps caps m -> Capabilities caps m Source #

Build a map of capabilities from individual implementations:

capsXY :: Capabilities '[X, Y] IO
capsXY = buildCaps $
    AddCap xImpl $
    AddCap yImpl $
    BaseCaps emptyCaps

data CapabilitiesBuilder (allCaps :: [CapK]) (caps :: [CapK]) (m :: MonadK) where Source #

CapabilitiesBuilder is a type to extend capabilities.

The allCaps parameter is a list of capabilities that will be provided to buildCaps eventually, when the building process is done. The caps parameter is the part of capabilities that was constructed so far. The builder is considered complete when allCaps ~ caps, only then it can be passed to buildCaps.

Constructors

AddCap :: (Typeable cap, HasCaps icaps allCaps, HasNoCap cap caps) => CapImpl cap icaps m -> CapabilitiesBuilder allCaps caps m -> CapabilitiesBuilder allCaps (cap ': caps) m 
BaseCaps :: Capabilities caps m -> CapabilitiesBuilder allCaps caps m 

data CapImpl cap icaps m where Source #

The CapImpl newtype guarantees that the wrapped capability implementation is sufficiently polymorphic so that required subtyping properties hold in methods that take monadic actions as input (negative position).

This rules out using addCap, insertCap, and buildCaps inside capability implementations in an unsafe manner.

Constructors

CapImpl 

Fields

getCap :: forall cap m caps. (Typeable cap, HasCap cap caps) => Capabilities caps m -> cap (CapsT caps m) Source #

Lookup a capability in a Capabilities map. The HasCap constraint guarantees that the lookup does not fail.

overrideCap :: (Typeable cap, HasCap cap caps, HasCaps icaps caps) => CapImpl cap icaps m -> Capabilities caps m -> Capabilities caps m Source #

Override the implementation of an existing capability.

addCap :: (Typeable cap, HasNoCap cap caps, HasCaps icaps (cap ': caps)) => CapImpl cap icaps m -> Capabilities caps m -> Capabilities (cap ': caps) m Source #

Extend the set of capabilities. In case the capability is already present, a type error occurs.

insertCap :: (Typeable cap, HasCaps icaps (cap ': caps)) => CapImpl cap icaps m -> Capabilities caps m -> Capabilities (cap ': caps) m Source #

Extend the set of capabilities. In case the capability is already present, it will be overriden (as with overrideCap), but occur twice in the type.

withCap :: (Typeable cap, HasCap cap caps) => (cap (CapsT caps m) -> CapsT caps m a) -> CapsT caps m a Source #

Extract a capability from CapsT and provide it to a continuation.

checkCap :: forall cap caps m. Typeable cap => Capabilities caps m -> HasCapDecision cap caps Source #

Determine at runtime whether 'HasCap cap caps' or 'HasNoCap cap caps' holds.

adjustCap :: forall cap caps m. (Typeable cap, HasCap cap caps) => (forall caps'. cap (CapsT caps' m) -> cap (CapsT caps' m)) -> Capabilities caps m -> Capabilities caps m Source #

Override the implementation of an existing capability using the previous implementation. This is a more efficient equivalent to extracting a capability with getCap, adjusting it with a function, and putting it back with overrideCap.

Default capabilities

newtype Context x (m :: MonadK) Source #

The Context capability is used to model the Reader effect within the capabilities framework.

Constructors

Context x 

class (Typeable x, HasCap (Context x) caps) => HasContext x caps Source #

The HasContext constraint is a shorthand for HasCap of Context.

Instances

Instances details
(Typeable x, HasCap (Context x) caps) => HasContext x caps Source # 
Instance details

Defined in Monad.Capabilities

newContext :: forall x m. x -> CapImpl (Context x) '[] m Source #

Initialize a Context capability.

askContext :: (HasContext x caps, Applicative m) => CapsT caps m x Source #

Retrieve the context value. Moral equivalent of ask.

localContext :: forall x caps m a. HasContext x caps => (x -> x) -> CapsT caps m a -> CapsT caps m a Source #

Execute a computation with a modified context value. Moral equivalent of local.

Type-level checks

type family HasCap cap caps :: Constraint where ... Source #

Ensure that the caps list has an element cap.

Equations

HasCap cap (cap ': _) = () 
HasCap cap (cap' ': caps) = HasCap cap caps 
HasCap cap '[] = TypeError ((Text "Capability " :<>: ShowType cap) :<>: Text " must be available") 

type family HasCaps icaps caps :: Constraint where ... Source #

Ensure that the caps list subsumes icaps. It is equivalent to a HasCap icap caps constraint for each icap in icaps.

Equations

HasCaps '[] _ = () 
HasCaps (icap ': icaps) caps = (HasCap icap caps, HasCaps icaps caps) 

type family HasNoCap cap caps :: Constraint where ... Source #

Ensure that the caps list does not have an element cap.

Equations

HasNoCap cap (cap ': _) = TypeError ((Text "Capability " :<>: ShowType cap) :<>: Text " is already present") 
HasNoCap cap (cap' ': caps) = HasNoCap cap caps 
HasNoCap cap '[] = () 

data HasCapDecision cap caps where Source #

Evidence that cap is present or absent in caps.

Constructors

HasNoCap :: HasNoCap cap caps => HasCapDecision cap caps 
HasCap :: HasCap cap caps => HasCapDecision cap caps 

Instances

Instances details
Show (HasCapDecision cap caps) Source # 
Instance details

Defined in Monad.Capabilities

Methods

showsPrec :: Int -> HasCapDecision cap caps -> ShowS #

show :: HasCapDecision cap caps -> String #

showList :: [HasCapDecision cap caps] -> ShowS #

Utils