web-plugins-0.2.0: 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

Constructors

Cleanup When (IO ()) 

data PluginsState theme n hook config st Source

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

we don't really want to give the Plugin unrestricted access to modify the PluginsState TVar. So we will use a newtype?

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

destroyPluginsSource

Arguments

:: When

should be OnFailure or OnNormal

-> Plugins theme m hook config st

handle to the plugins

-> IO () 

shutdown the plugins system

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

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

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

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

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

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

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

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 :: [Text]

plugins which much be initialized before this one can be

pluginToPathInfo :: url -> Text
 
pluginPostHook :: hook
 

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

serve :: Plugins theme n hook config st -> Text -> [Text] -> IO (Either String n)Source