web-plugins-0.2.4: dynamic plugin system for web applications

Safe HaskellNone

Web.Plugins.Core

Description

web-plugins is a very general purpose plugin system for web applications.

It provides facilities for loading multiple plugins and a single theme. In the future, the web-plugins-dynamic library will allow plugins and themes to be loaded and unloaded at runtime.

A key aspect of web-plugins is that all plugins for a particular system have the same type signature. This is what makes it possible to load new plugins at runtime.

This plugin system is not tied to any particular web server framework or template engine.

There are four steps to using web-plugins:

  1. initialize the plugins system
  2. initialize the individual plugins
  3. set the theme
  4. route incoming requests to the correct plugin

To use web-plugins, you first initialize a Plugins handle.

The Plugins handle is heavily parameterized:

 newtype Plugins theme m hook config st = ...
theme
is (not suprisingly) the type for you theme.
m
is the monad that your plugin handlers will run in. (e.g., ServerPart)
hook
is additional actions that should be called after the plugins have been initialized
config
provides read-only configuration information
st
provides mutable state that is shared between all plugins. (There is a separate mechanism for plugin-local state.)

The plugin system is typically started by using withPlugins. Though, if needed, you can call initPlugins and destroyPlugins instead.

The Plugin record is used to create a plugin:

data Plugin url theme n hook config st = Plugin
    { pluginName         :: PluginName
    , pluginInit         :: Plugins theme n hook config st -> IO (Maybe Text)
    , pluginDepends      :: [PluginName]   -- ^ plugins which much be initialized before this one can be
    , pluginToPathInfo   :: url -> Text
    , pluginPostHook     :: hook
    }

You will note that it has the same type parameters as Plugins plus an additional url parameter.

pluginName
is a simple Text value which should uniquely identify the plugin.
pluginInit
will be called automatically when the plugin is loaded.
pluginDepends
is a list of plugins which must be loaded before this plugin can be initialized.
pluginToPathInfo
is the function that is used to convert the url type to an actual URL.
pluginPostHook
is the hook that you want called after the system has been initialized.

A Plugin is initialized using the initPlugin function (which calls the pluginInit field among other things).

-- | initialize a plugin
initPlugin :: (Typeable url) =>
              Plugins theme n hook config st    -- ^ Plugins handle
           -> Text                              -- ^ base URI to prepend to generated URLs
           -> Plugin url theme n hook config st -- ^ Plugin to initialize
           -> IO (Maybe Text)                   -- ^ possible error message

A lot of the magic happens in the pluginInit function in the Plugin record. Let's look at a simple example. We will use the following type aliases to parameterize the Plugins and Plugin type:

type ExamplePlugins    = Plugins    Theme (ServerPart Response) (IO ()) () ()
type ExamplePlugin url = Plugin url Theme (ServerPart Response) (IO ()) () ()

Here is the initialization function for myPlugin:

myInit :: ExamplePlugins -> IO (Maybe Text)
myInit plugins =
    do (Just clckShowFn) <- getPluginRouteFn plugins (pluginName clckPlugin)
       (Just myShowFn)   <- getPluginRouteFn plugins (pluginName myPlugin)
       acid <- liftIO $ openLocalState MyState
       addCleanup plugins OnNormal  (putStrLn myPlugin: normal shutdown  >> createCheckpointAndClose acid)
       addCleanup plugins OnFailure (putStrLn myPlugin: failure shutdown >> closeAcidState acid)
       addHandler plugins (pluginName myPlugin) (myPluginHandler acid clckShowFn myShowFn)
       putStrLn myInit completed.
       return Nothing

There are a few things to note here:

getPluginRouteFn is used to retrieve the the URL route showing function for various plugins. In this case, the plugin needs to generate routes for itself and also routes in the clckPlugin.

Next it opens up an AcidState. It then registers two different cleanup functions. The OnNormal cleanup will only be called if the system is shutdown normally. The OnFailure will be called if the system is shutdown due to some error condition. If we wanted to perform the same shutdown procedure regardless of termination cause, we could use the Always condition instead.

the addHandler then registers the function which route requests for this plugin:

addHandler :: MonadIO m =>
              Plugins theme n hook config st
            -> PluginName -- plugin name / prefix
            -> (Plugins theme n hook config st -> [Text] -> n)
            -> m ()

Each plugin should be registered using a unique prefix. When the handler is called it will be passed the Plugins handle and a list of Text values. In practice, the list Text values is typically the unconsumed path segments from the URL.

Setting the theme is done by calling the setTheme function:

-- | set the current theme
setTheme :: (MonadIO m) =>
            Plugins theme n hook config st
         -> Maybe theme
         -> m ()

Setting the theme to Nothing will unload the theme but not load a new one.

Incoming requests are routed to the various plugins via the serve function:

-- | serve requests using the Plugins handle
serve :: Plugins theme n hook config st -- ^ Plugins handle
      -> PluginName -- ^ name of the plugin to handle this request
      -> [Text]     -- ^ unconsume path segments to pass to handler
      -> IO (Either String n)

The expected usage is that you are going to have request with a url such as:

 /my/extra/path/segments

The code will treat the first path segment as the plugin to be called and pass in the remaining segments as the [Text] arguments:

 serve plugins "my" ["extra","path","segments"]

the serve function itself knows nothing about the web -- it is framework agnostic. Here is a simple main function that shows how to tie everything together:

 main :: IO ()
 main =
   withPlugins () () $ \plugins ->
     do initPlugin plugins "" clckPlugin
        initPlugin plugins "" myPlugin
        setTheme plugins (Just theme)
        hooks <- getPostHooks plugins
        sequence_ hooks
        simpleHTTP nullConf $ path $ \p -> do
          ps <- fmap rqPaths askRq
          r <- liftIO $ serve plugins p (map Text.pack ps)
          case r of
            (Left e) -> internalServerError $ toResponse e
            (Right sp) -> sp

In this example, we do not use the config or st parameters so we just set them to ().

Note that we are responsible for calling the hooks after we have initialized all the plugins.

Synopsis

Documentation

data When Source

When indicates when a clean up action should be run

Constructors

Always

always run this action when destroyPlugins is called

OnFailure

only run this action if destroyPlugins is called with a failure present

OnNormal

only run this action when destroyPlugins is called with a normal shutdown

Instances

data Cleanup Source

A Cleanup is an IO action to run when the server shuts down. The server can either shutdown normally or due to a failure. The When parameter indicates when an action should run.

Constructors

Cleanup When (IO ()) 

type PluginName = TextSource

The PluginName should uniquely identify a plugin -- though we currently have no way to enforce that.

data PluginsState theme n hook config st Source

The PluginsState record holds all the record keeping information needed for loading, unloading, and invoking plugins. In theory you should not be modifying or inspecting this structure directly -- only calling the helper functions that modify or read it.

Constructors

PluginsState 

Fields

pluginsHandler :: Map PluginName (Plugins theme n hook config st -> [Text] -> n)
 
pluginsOnShutdown :: [Cleanup]
 
pluginsRouteFn :: Map PluginName Dynamic
 
pluginsPluginState :: Map PluginName (TVar Dynamic)

per-plugin state

pluginsTheme :: Maybe theme
 
pluginsPostHooks :: [hook]
 
pluginsConfig :: config
 
pluginsState :: st
 

newtype Plugins theme m hook config st Source

The Plugins type is the handle to the plugins system. Generally you will have exactly one Plugins value in your app.

see also withPlugins

Constructors

Plugins 

Fields

ptv :: TVar (PluginsState theme m hook config st)
 

initPluginsSource

Arguments

:: config

initial value for the config field of PluginsState

-> st

initial value for the state field of the PluginsState

-> IO (Plugins theme n hook config st) 

initialize the plugins system

see also withPlugins

destroyPluginsSource

Arguments

:: When

should be OnFailure or OnNormal

-> Plugins theme m hook config st

handle to the plugins

-> IO () 

shutdown the plugins system

see also withPlugins

withPluginsSource

Arguments

:: config

initial config value

-> st

initial state value

-> (Plugins theme m hook config st -> IO a) 
-> IO a 

a bracketed combination of initPlugins and destroyPlugins. Takes care of passing the correct termination condition.

getPluginsSt :: MonadIO m => Plugins theme n hook config st -> m stSource

get the current st value from Plugins

putPluginsSt :: MonadIO m => Plugins theme n hook config st -> st -> m ()Source

put the current st value from Plugins

addPluginState :: (MonadIO m, Typeable state) => Plugins theme n hook config st -> PluginName -> state -> m ()Source

add a new plugin-local state

getPluginState :: (MonadIO m, Typeable state) => Plugins theme n hook config st -> Text -> m (Maybe state)Source

Get the state for a particular plugin

per-plugin state is optional. This will return Nothing if the plugin did not register any local state.

modifyPluginsSt :: MonadIO m => Plugins theme n hook config st -> (st -> st) -> m ()Source

modify the current st value from Plugins

addHandlerSource

Arguments

:: MonadIO m 
=> Plugins theme n hook config st 
-> PluginName

prefix which this route handles

-> (Plugins theme n hook config st -> [Text] -> n) 
-> m () 

add a new route handler

addCleanup :: MonadIO m => Plugins theme n hook config st -> When -> IO () -> m ()Source

add a new cleanup action to the top of the stack

addPostHook :: MonadIO m => Plugins theme n hook config st -> hook -> m ()Source

add a new post initialization hook

getPostHooks :: MonadIO m => Plugins theme n hook config st -> m [hook]Source

get all the post initialization hooks

addPluginRouteFn :: (MonadIO m, Typeable url) => Plugins theme n hook config st -> PluginName -> (url -> [(Text, Maybe Text)] -> Text) -> m ()Source

add the routing function for a plugin

see also: getPluginRouteFn

getPluginRouteFnSource

Arguments

:: (MonadIO m, Typeable url) 
=> Plugins theme n hook config st 
-> PluginName

name of plugin

-> m (Maybe (url -> [(Text, Maybe Text)] -> Text)) 

get the plugin routing function for the named plugin

see also: addPluginRouteFn

setTheme :: MonadIO m => Plugins theme n hook config st -> Maybe theme -> m ()Source

set the current theme

getTheme :: MonadIO m => Plugins theme n hook config st -> m (Maybe theme)Source

get the current theme

getConfig :: MonadIO m => Plugins theme n hook config st -> m configSource

get the config value from the Plugins type

data Plugin url theme n hook config st Source

NOTE: it is possible to set the URL type incorrectly here and not get a type error. How can we fix that ?

Constructors

Plugin 

Fields

pluginName :: PluginName
 
pluginInit :: Plugins theme n hook config st -> IO (Maybe Text)
 
pluginDepends :: [PluginName]

plugins which much be initialized before this one can be

pluginToPathInfo :: url -> Text
 
pluginPostHook :: hook
 

initPluginSource

Arguments

:: Typeable url 
=> Plugins theme n hook config st

Plugins handle

-> Text

base URI to prepend to generated URLs

-> Plugin url theme n hook config st

Plugin to initialize

-> IO (Maybe Text)

possible error message

initialize a plugin

serveSource

Arguments

:: Plugins theme n hook config st

Plugins handle

-> PluginName

name of the plugin to handle this request

-> [Text]

unconsume path segments to pass to handler

-> IO (Either String n) 

serve requests using the Plugins handle