Safe Haskell | None |
---|
Snaplets allow you to build web applications out of composable parts. This allows you to build self-contained units and glue them together to make your overall application.
A snaplet has a few moving parts, some user-defined and some provided by the snaplet API:
- each snaplet has its own configuration given to it at startup.
- each snaplet is given its own directory on the filesystem, from which it reads its configuration and in which it can store files.
- each snaplet comes with an
Initializer
which defines how to create an instance of the Snaplet at startup. The initializer decides how to interpret the snaplet configuration, which URLs to handle (and how), sets up the initial snaplet state, tells the snaplet runtime system how to clean the snaplet up, etc. - each snaplet contains some user-defined in-memory state; for instance, a
snaplet that talks to a database might contain a reference to a connection
pool. The snaplet state is an ordinary Haskell record, with a datatype
defined by the snaplet author. The initial state record is created during
initialization and is available to snaplet
Handler
s when serving HTTP requests.
NOTE: This documentation is written as a prose tutorial of the snaplets API. Don't be scared by the fact that it's auto-generated and is filled with type signatures. Just keep reading.
- data Snaplet s
- data SnapletConfig
- snapletConfig :: Lens (Snaplet a) SnapletConfig
- snapletValue :: Lens (Snaplet a) a
- subSnaplet :: Lens a (Snaplet b) -> Lens (Snaplet a) (Snaplet b)
- class MonadSnaplet m where
- with :: Lens v (Snaplet v') -> m b v' a -> m b v a
- withTop :: Lens b (Snaplet v') -> m b v' a -> m b v a
- with' :: Lens (Snaplet v) (Snaplet v') -> m b v' a -> m b v a
- withTop' :: Lens (Snaplet b) (Snaplet v') -> m b v' a -> m b v a
- getLens :: m b v (Lens (Snaplet b) (Snaplet v))
- getOpaqueConfig :: m b v SnapletConfig
- getSnapletAncestry :: (Monad (m b v), MonadSnaplet m) => m b v [Text]
- getSnapletFilePath :: (Monad (m b v), MonadSnaplet m) => m b v FilePath
- getSnapletName :: (Monad (m b v), MonadSnaplet m) => m b v (Maybe Text)
- getSnapletDescription :: (Monad (m b v), MonadSnaplet m) => m b v Text
- getSnapletUserConfig :: (Monad (m b v), MonadSnaplet m) => m b v Config
- getSnapletRootURL :: (Monad (m b v), MonadSnaplet m) => m b v ByteString
- getRoutePattern :: Handler b v (Maybe ByteString)
- setRoutePattern :: ByteString -> Handler b v ()
- getSnapletState :: Handler b v (Snaplet v)
- putSnapletState :: Snaplet v -> Handler b v ()
- modifySnapletState :: (Snaplet v -> Snaplet v) -> Handler b v ()
- getsSnapletState :: (Snaplet v -> b) -> Handler b1 v b
- data Initializer b v a
- data SnapletInit b v
- makeSnaplet :: Text -> Text -> Maybe (IO FilePath) -> Initializer b v v -> SnapletInit b v
- nestSnaplet :: ByteString -> Lens v (Snaplet v1) -> SnapletInit b v1 -> Initializer b v (Snaplet v1)
- embedSnaplet :: ByteString -> Lens v (Snaplet v1) -> SnapletInit v1 v1 -> Initializer b v (Snaplet v1)
- nameSnaplet :: Text -> SnapletInit b v -> SnapletInit b v
- onUnload :: IO () -> Initializer b v ()
- addPostInitHook :: (v -> IO v) -> Initializer b v ()
- addPostInitHookBase :: (Snaplet b -> IO (Snaplet b)) -> Initializer b v ()
- printInfo :: Text -> Initializer b v ()
- addRoutes :: [(ByteString, Handler b v ())] -> Initializer b v ()
- wrapHandlers :: (Handler b v () -> Handler b v ()) -> Initializer b v ()
- wrapSite :: (Handler b v () -> Handler b v ()) -> Initializer b v ()
- data Handler b v a
- reloadSite :: Handler b v ()
- bracketHandler :: IO a -> (a -> IO x) -> (a -> Handler b v c) -> Handler b v c
- runSnaplet :: Maybe String -> SnapletInit b b -> IO (Text, Snap (), IO ())
- combineConfig :: Config Snap a -> Snap () -> IO (Config Snap a, Snap ())
- serveSnaplet :: Config Snap AppConfig -> SnapletInit b b -> IO ()
Snaplet
The heart of the snaplets infrastructure is state management. (Note: when
we say "state" here, we mean in-memory Haskell objects, not external data
storage or databases; how you deal with persisted data is up to you.) Most
nontrivial pieces of a web application need some kind of runtime state or
environment data. The datatype we use to handle this is called Snaplet
:
Snaplet's type parameter s
here is user-defined and can be any Haskell
type. A value of type Snaplet s
countains a couple of things:
- a value of type
s
, called the "user state". - some bookkeeping data the framework uses to plug things together, like the snaplet's configuration, the snaplet's root directory on the filesystem, the snaplet's root URL, and so on.
MonadReader (Lens (Snaplet b) (Snaplet v)) (SnapletHeist b v) |
data SnapletConfig Source
An opaque data type holding internal snaplet configuration data. It is exported publicly because the getOpaqueConfig function in MonadSnaplet makes implementing new instances of MonadSnaplet more convenient.
Snaplet Helper Functions
Your web application will itself get wrapped in a Snaplet
, and the
top-level user state of your application (which will likely contain other
snaplets nested inside it) will look something like this:
data App = App { _foo :: Snaplet Foo , _bar :: Snaplet Bar , _someNonSnapletData :: String }
Every web application using snaplets has a top-most user state which contains all of the application state; we call this state the "base" state.
We provide a couple of helper functions for working with Snaplet types.
snapletConfig :: Lens (Snaplet a) SnapletConfigSource
A lens referencing the opaque SnapletConfig data type held inside Snaplet.
snapletValue :: Lens (Snaplet a) aSource
A lens referencing the user-defined state type wrapped by a Snaplet.
subSnaplet :: Lens a (Snaplet b) -> Lens (Snaplet a) (Snaplet b)Source
Transforms a lens of the type you get from makeLenses to an similar lens that is more suitable for internal use.
Lenses
In the example above, the Foo
snaplet has to be written to work with any
base state (otherwise it wouldn't be reusable!), but functions written to
work with the Foo
snaplet want to be able to modify the Foo
record
within the context of the base state. Given that Haskell datatypes are
pure, how do you allow for this?
Our solution is to use lenses, as defined in the data-lens
library
(http://hackage.haskell.org/package/data-lens). A lens, notated as
follows:
Lens a b
is a "getter" and a "setter" rolled up into one. The data-lens
library provides the following functions:
getL :: (Lens a b) -> a -> b setL :: (Lens a b) -> b -> a -> a modL :: (Lens a b) -> (b -> b) -> a -> a
which allow you to get, set, and modify a value of type b
within the
context of type of type a
. The data-lens
package comes with a Template
Haskell function called makeLenses
, which auto-magically defines a lens
for every record field having a name beginning with an underscore. In the
App
example above, adding the declaration:
makeLenses [''App]
would define lenses:
foo :: Lens App (Snaplet Foo) bar :: Lens App (Snaplet Bar) someNonSnapletData :: Lens App String
The coolest thing about data-lens
lenses is that they compose, using
the Control.Category's generalization of the (.)
operator. If the Foo
type had a field of type Quux
within it with a lens quux :: Lens Foo
Quux
, then you could create a lens of type Lens App Quux
by composition:
import Control.Category import Prelude hiding ((.)) -- you have to hide (.) from the Prelude -- to use Control.Category.(.) data Foo = Foo { _quux :: Quux } makeLenses [''Foo] -- snapletValue is defined in the framework: snapletValue :: Lens (Snaplet a) a appQuuxLens :: Lens App Quux appQuuxLens = quux . snapletValue . foo
Lens composition is very similar to function composition, but it gives you a composed getter and setter at the same time.
MonadSnaplet
The primary abstraction in the snaplet infrastructure is a combination of
the reader and state monads. The state monad holds the top level
application data type (from now on referred to as the base state). The
reader monad holds a lens from the base state to the current snaplet's
state. This allows quux snaplet functions to access and modify the Quux
data structure without knowing anything about the App or Foo data
structures. It also lets other snaplets call functions from the quux
snaplet if they have the quux snaplet's lens Lens App (Snaplet Quux)
.
We can view our application as a tree of snaplets and other pieces of data.
The lenses are like pointers to nodes of the tree. If you have a pointer to
a node, you can access the node and all of its children without knowing
anything about the rest of the tree.
Several monads use this infrastructure. These monads need at least three type parameters. Two for the lens type, and the standard 'a' denoting the monad return value. You will usually see this written in type signatures as "m b v a" or some variation. The 'm' is the type variable of the MonadSnaplet type class. 'b' is the base state, and 'v' is the state of the current "view" snaplet (or simply, current state).
The MonadSnaplet type class distills the essence of the operations used with this pattern. Its functions define fundamental methods for navigating snaplet trees.
class MonadSnaplet m whereSource
The m type parameter used in the MonadSnaplet type signatures will usually be either Initializer or Handler, but other monads may sometimes be useful.
Minimal complete definition:
-
withTop'
,with'
,getLens
, andgetOpaqueConfig
.
:: Lens v (Snaplet v') | A relative lens identifying a snaplet |
-> m b v' a | Action from the lense's snaplet |
-> m b v a |
Runs a child snaplet action in the current snaplet's context. If you think about snaplet lenses using a filesystem path metaphor, the lens supplied to this snaplet must be a relative path. In other words, the lens's base state must be the same as the current snaplet.
:: Lens b (Snaplet v') | An "absolute" lens identifying a snaplet |
-> m b v' a | Action from the lense's snaplet |
-> m b v a |
Like with
but doesn't impose the requirement that the action
being run be a descendant of the current snaplet. Using our filesystem
metaphor again, the lens for this function must be an absolute
path--it's base must be the same as the current base.
with' :: Lens (Snaplet v) (Snaplet v') -> m b v' a -> m b v aSource
A variant of with
accepting a lens from snaplet to snaplet. Unlike
the lens used in the above with
function, this lens formulation has
an identity, which makes it useful in certain circumstances. The
lenses generated by makeLenses
will not work with this function,
however the lens returned by getLens
will.
with = with' . subSnaplet
withTop' :: Lens (Snaplet b) (Snaplet v') -> m b v' a -> m b v aSource
The absolute version of with'
getLens :: m b v (Lens (Snaplet b) (Snaplet v))Source
Gets the lens for the current snaplet.
getOpaqueConfig :: m b v SnapletConfigSource
Gets the current snaplet's opaque config data type. You'll only use this function when writing MonadSnaplet instances.
MonadSnaplet Initializer | |
MonadSnaplet Handler | |
MonadSnaplet SnapletHeist | MonadSnaplet instance gives us access to the snaplet infrastructure. |
getSnapletAncestry :: (Monad (m b v), MonadSnaplet m) => m b v [Text]Source
Gets a list of the names of snaplets that are direct ancestors of the current snaplet.
getSnapletFilePath :: (Monad (m b v), MonadSnaplet m) => m b v FilePathSource
Gets the snaplet's path on the filesystem.
getSnapletName :: (Monad (m b v), MonadSnaplet m) => m b v (Maybe Text)Source
Gets the current snaple's name.
getSnapletDescription :: (Monad (m b v), MonadSnaplet m) => m b v TextSource
Gets a human readable description of the snaplet.
getSnapletUserConfig :: (Monad (m b v), MonadSnaplet m) => m b v ConfigSource
Gets the config data structure for the current snaplet.
getSnapletRootURL :: (Monad (m b v), MonadSnaplet m) => m b v ByteStringSource
Gets the base URL for the current snaplet. Directories get added to
the current snaplet path by calls to nestSnaplet
.
getRoutePattern :: Handler b v (Maybe ByteString)Source
Gets the route pattern that matched for the handler. This lets you find out exactly which of the strings you used in addRoutes matched.
setRoutePattern :: ByteString -> Handler b v ()Source
Sets the route pattern that matched for the handler. Use this when to override the default pattern which is the key to the alist passed to addRoutes.
Snaplet state manipulation
MonadSnaplet instances will typically have MonadState v
instances. We
provide the following convenience functions which give the equivalent to
MonadState (Snaplet v)
for the less common cases where you need to work
with the Snaplet wrapper.
getSnapletState :: Handler b v (Snaplet v)Source
Gets the Snaplet v
from the current snaplet's state.
putSnapletState :: Snaplet v -> Handler b v ()Source
Puts a new Snaplet v
in the current snaplet's state.
modifySnapletState :: (Snaplet v -> Snaplet v) -> Handler b v ()Source
Modifies the Snaplet v
in the current snaplet's state.
getsSnapletState :: (Snaplet v -> b) -> Handler b1 v bSource
Gets the Snaplet v
from the current snaplet's state and applies a
function to it.
Initializer
The Initializer monad is where your application's initialization happens. Initializers are run at startup and any time a site reload is triggered. The Initializer's job is to construct a snaplet's routes and initial state, set up filesystem data, read config files, etc.
In order to initialize its state, a snaplet needs to initialize all the
Snaplet a
state for each of its subsnaplets. The only way to construct
a Snaplet a
type is by calling nestSnaplet
or embedSnaplet
from
within an initializer.
data Initializer b v a Source
Monad used for initializing snaplets.
MonadSnaplet Initializer | |
Monad (Initializer b v) | |
Functor (Initializer b v) | |
Applicative (Initializer b v) | |
MonadIO (Initializer b v) |
data SnapletInit b v Source
Opaque newtype which gives us compile-time guarantees that the user is using makeSnaplet and either nestSnaplet or embedSnaplet correctly.
:: Text | A default id for this snaplet. This is only used when the end-user has not already set an id using the nameSnaplet function. |
-> Text | A human readable description of this snaplet. |
-> Maybe (IO FilePath) | The path to the directory holding the snaplet's reference filesystem content. This will almost always be the directory returned by Cabal's getDataDir command, but it has to be passed in because it is defined in a package-specific import. Setting this value to Nothing doesn't preclude the snaplet from having files in in the filesystem, it just means that they won't be copied there automatically. |
-> Initializer b v v | Snaplet initializer. |
-> SnapletInit b v |
All snaplet initializers must be wrapped in a call to makeSnaplet
,
which handles standardized housekeeping common to all snaplets.
Common usage will look something like
this:
fooInit :: SnapletInit b Foo fooInit = makeSnaplet "foo" "An example snaplet" Nothing $ do -- Your initializer code here return $ Foo 42
Note that you're writing your initializer code in the Initializer monad, and makeSnaplet converts it into an opaque SnapletInit type. This allows us to use the type system to ensure that the API is used correctly.
:: ByteString | The root url for all the snaplet's routes. An empty string gives the routes the same root as the parent snaplet's routes. |
-> Lens v (Snaplet v1) | Lens identifying the snaplet |
-> SnapletInit b v1 | The initializer function for the subsnaplet. |
-> Initializer b v (Snaplet v1) |
Runs another snaplet's initializer and returns the initialized Snaplet value. Calling an initializer with nestSnaplet gives the nested snaplet access to the same base state that the current snaplet has. This makes it possible for the child snaplet to make use of functionality provided by sibling snaplets.
:: ByteString | The root url for all the snaplet's routes. An empty string gives the routes the same root as the parent snaplet's routes. NOTE: Because of the stronger isolation provided by embedSnaplet, you should be more careful about using an empty string here. |
-> Lens v (Snaplet v1) | Lens identifying the snaplet |
-> SnapletInit v1 v1 | The initializer function for the subsnaplet. |
-> Initializer b v (Snaplet v1) |
Runs another snaplet's initializer and returns the initialized Snaplet value. The difference between this and nestSnaplet is the first type parameter in the third argument. The "v1 v1" makes the child snaplet think that it is top-level, which means that it will not be able to use functionality provided by snaplets included above it in the snaplet tree. This strongly isolates the child snaplet, and allows you to eliminate the b type variable. The embedded snaplet can still get functionality from other snaplets, but only if it nests or embeds the snaplet itself.
:: Text | The snaplet name |
-> SnapletInit b v | The snaplet initializer function |
-> SnapletInit b v |
Sets a snaplet's name. All snaplets have a default name set by the snaplet author. This function allows you to override that name. You will have to do this if you have more than one instance of the same kind of snaplet because snaplet names must be unique. This function must immediately surround the snaplet's initializer. For example:
fooState <- nestSnaplet "fooA" $ nameSnaplet "myFoo" $ fooInit
onUnload :: IO () -> Initializer b v ()Source
Attaches an unload handler to the snaplet. The unload handler will be called when the server shuts down, or is reloaded.
addPostInitHook :: (v -> IO v) -> Initializer b v ()Source
Adds an IO action that modifies the current snaplet state to be run at
the end of initialization on the state that was created. This makes it
easier to allow one snaplet's state to be modified by another snaplet's
initializer. A good example of this is when a snaplet has templates that
define its views. The Heist snaplet provides the addTemplates
function
which allows other snaplets to set up their own templates. addTemplates
is implemented using this function.
addPostInitHookBase :: (Snaplet b -> IO (Snaplet b)) -> Initializer b v ()Source
Variant of addPostInitHook for when you have things wrapped in a Snaplet.
printInfo :: Text -> Initializer b v ()Source
Initializers should use this function for all informational or error messages to be displayed to the user. On application startup they will be sent to the console. When executed from the reloader, they will be sent back to the user in the HTTP response.
Routes
Snaplet initializers are also responsible for setting up any routes defined
by the snaplet. To do that you'll usually use either addRoutes
or
wrapHandlers
.
addRoutes :: [(ByteString, Handler b v ())] -> Initializer b v ()Source
Adds routing to the current Handler
. The new routes are merged with
the main routing section and take precedence over existing routing that was
previously defined.
wrapHandlers :: (Handler b v () -> Handler b v ()) -> Initializer b v ()Source
This function has been renamed to wrapSite
and is deprecated. It will
be removed in the next major Snap release. Fix your code now!
Wraps the snaplet's routing. When all is said and done, a snaplet's
routes end up getting combined into a single Handler
action. This
function allows you to modify that Handler before it actually gets served.
This allows you to do things that need to happen for every request handled
by your snaplet. Here are some examples of things you might do:
wrapSite (site -> removePathTrailingSlashes >> site)
wrapSite (site -> logHandlerStart >> site >> logHandlerFinished)
wrapSite (site -> ensureAdminUser >> site)
Handlers
Snaplet infrastructure is available during runtime request processing
through the Handler monad. There aren't very many standalone functions to
read about here, but this is deceptive. The key is in the type class
instances. Handler is an instance of MonadSnap
, which means it is the
monad you will use to write all your application routes. It also has a
MonadSnaplet
instance, which gives you all the functionality described
above.
MonadSnaplet Handler | |
MonadState v (Handler b v) | The MonadState instance gives you access to the current snaplet's state. |
Monad (Handler b v) | |
Functor (Handler b v) | |
MonadPlus (Handler b v) | |
Applicative (Handler b v) | |
MonadCatchIO (Handler b v) | |
Alternative (Handler b v) | |
MonadIO (Handler b v) | |
MonadSnap (Handler b v) |
reloadSite :: Handler b v ()Source
Handler that reloads the site.
bracketHandler :: IO a -> (a -> IO x) -> (a -> Handler b v c) -> Handler b v cSource
This function brackets a Handler action in resource acquisition and
release. Like bracketSnap
, this is provided because MonadCatchIO's
bracket
function doesn't work properly in the case of a short-circuit
return from the action being bracketed.
In order to prevent confusion regarding the effects of the aquisition and release actions on the Handler state, this function doesn't accept Handler actions for the acquire or release actions.
This function will run the release action in all cases where the acquire action succeeded. This includes the following behaviors from the bracketed Snap action.
- Normal completion
- Short-circuit completion, either from calling
fail
orfinishWith
- An exception being thrown.
Serving Applications
runSnaplet :: Maybe String -> SnapletInit b b -> IO (Text, Snap (), IO ())Source
Given an envirnoment and a Snaplet initializer, produce the set of messages generated during initialization, a snap handler, and a cleanup action. The environment is an arbitrary string such as devel or production. This string is used to determine the name of the config files used each snaplet. If an environment of Nothing is used, then runSnaplet defaults to devel.
combineConfig :: Config Snap a -> Snap () -> IO (Config Snap a, Snap ())Source
Given a configuration and a snap handler, complete it and produce the completed configuration as well as a new toplevel handler with things like compression and a 500 handler set up.
serveSnaplet :: Config Snap AppConfig -> SnapletInit b b -> IO ()Source
Serves a top-level snaplet as a web application. Reads command-line arguments. FIXME: document this.