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

Safe HaskellNone

Web.Plugins.Core

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 -> Text -> 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 
-> Text

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
 

initPlugin :: Typeable url => Plugins theme n hook config st -> PluginName -> Plugin url theme n hook config st -> IO (Maybe Text)Source

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