| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Snap.Snaplet
Contents
Description
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 Initializerwhich 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 Handlers 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.
Synopsis
- data Snaplet s
- data SnapletConfig
- snapletConfig :: forall s. Lens' (Snaplet s) SnapletConfig
- snapletValue :: forall s. Lens' (Snaplet s) s
- subSnaplet :: SnapletLens a b -> SnapletLens (Snaplet a) b
- class MonadSnaplet m where- with :: SnapletLens v v' -> m b v' a -> m b v a
- withTop :: SnapletLens b v' -> m b v' a -> m b v a
- with' :: SnapletLens (Snaplet v) v' -> m b v' a -> m b v a
- withTop' :: SnapletLens (Snaplet b) v' -> m b v' a -> m b v a
- getLens :: m b v (SnapletLens (Snaplet b) 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
- snapletURL :: (Monad (m b v), MonadSnaplet m) => ByteString -> 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 -> SnapletLens v v1 -> SnapletInit b v1 -> Initializer b v (Snaplet v1)
- embedSnaplet :: ByteString -> SnapletLens v 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 (Either Text v)) -> Initializer b v ()
- addPostInitHookBase :: (Snaplet b -> IO (Either Text (Snaplet b))) -> Initializer b v ()
- printInfo :: Text -> Initializer b v ()
- getRoutes :: Initializer b v [ByteString]
- getEnvironment :: Initializer b v String
- addRoutes :: [(ByteString, Handler b v ())] -> Initializer b v ()
- wrapSite :: (Handler b v () -> Handler b v ()) -> Initializer b v ()
- data Handler b v a
- failIfNotLocal :: MonadSnap m => m b -> m b
- reloadSite :: Handler b v ()
- modifyMaster :: v -> 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 ()
- serveSnapletNoArgParsing :: Config Snap AppConfig -> SnapletInit b b -> IO ()
- loadAppConfig :: FileName -> FilePath -> IO Config
- type SnapletLens s a = ALens' s (Snaplet a)
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.
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.
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 Edward Kmett's lens
 library (http://hackage.haskell.org/package/lens). A lens, notated
 as follows:
SimpleLens a b
is conceptually a "getter" and a "setter" rolled up into one. The
 lens library provides the following functions:
view :: (SimpleLens a b) -> a -> b set :: (SimpleLens a b) -> b -> a -> a over :: (SimpleLens a b) -> (b -> b) -> a -> a
which allow you to get, set, and modify a value of type b within the
 context of type a. The 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 :: SimpleLens App (Snaplet Foo) bar :: SimpleLens App (Snaplet Bar) someNonSnapletData :: SimpleLens App String
The coolest thing about lens lenses is that they compose using the
 (.) operator. If the Foo type had a field of type Quux within it with
 a lens quux :: SimpleLens Foo Quux, then you could create a lens of type
 SimpleLens App Quux by composition:
import Control.Lens
data Foo = Foo { _quux :: Quux }
makeLenses ''Foo
-- snapletValue is defined in the framework:
snapletValue :: SimpleLens (Snaplet a) a
appQuuxLens :: SimpleLens App Quux
appQuuxLens = foo . snapletValue . quuxLens composition is very similar to function composition except it works in the opposite direction (think Java-style System.out.println ordering) and it gives you a composed getter and setter at the same time.
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 export several helper lenses for working with Snaplet types.
snapletConfig :: forall s. Lens' (Snaplet s) SnapletConfig Source #
snapletValue :: forall s. Lens' (Snaplet s) s Source #
subSnaplet :: SnapletLens a b -> SnapletLens (Snaplet a) b Source #
Transforms a lens of the type you get from makeLenses to an similar lens that is more suitable for internal use.
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 SimpleLens 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 where Source #
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, and- getOpaqueConfig.
Minimal complete definition
Methods
Arguments
| :: SnapletLens v 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.
Arguments
| :: SnapletLens b 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' :: SnapletLens (Snaplet v) v' -> m b v' a -> m b v a Source #
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' :: SnapletLens (Snaplet b) v' -> m b v' a -> m b v a Source #
The absolute version of with'
getLens :: m b v (SnapletLens (Snaplet b) v) Source #
Gets the lens for the current snaplet.
getOpaqueConfig :: m b v SnapletConfig Source #
Gets the current snaplet's opaque config data type. You'll only use this function when writing MonadSnaplet instances.
Instances
| MonadSnaplet Initializer Source # | |
| Defined in Snap.Snaplet.Internal.Types Methods with :: SnapletLens v v' -> Initializer b v' a -> Initializer b v a Source # withTop :: SnapletLens b v' -> Initializer b v' a -> Initializer b v a Source # with' :: SnapletLens (Snaplet v) v' -> Initializer b v' a -> Initializer b v a Source # withTop' :: SnapletLens (Snaplet b) v' -> Initializer b v' a -> Initializer b v a Source # getLens :: Initializer b v (SnapletLens (Snaplet b) v) Source # | |
| MonadSnaplet Handler Source # | |
| Defined in Snap.Snaplet.Internal.Types Methods with :: SnapletLens v v' -> Handler b v' a -> Handler b v a Source # withTop :: SnapletLens b v' -> Handler b v' a -> Handler b v a Source # with' :: SnapletLens (Snaplet v) v' -> Handler b v' a -> Handler b v a Source # withTop' :: SnapletLens (Snaplet b) v' -> Handler b v' a -> Handler b v a Source # getLens :: Handler b v (SnapletLens (Snaplet b) v) Source # getOpaqueConfig :: Handler b v SnapletConfig Source # | |
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 FilePath Source #
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 Text Source #
Gets a human readable description of the snaplet.
getSnapletUserConfig :: (Monad (m b v), MonadSnaplet m) => m b v Config Source #
Gets the config data structure for the current snaplet.
getSnapletRootURL :: (Monad (m b v), MonadSnaplet m) => m b v ByteString Source #
Gets the base URL for the current snaplet.  Directories get added to
 the current snaplet path by calls to nestSnaplet.
snapletURL :: (Monad (m b v), MonadSnaplet m) => ByteString -> m b v ByteString Source #
Constructs a url relative to the current snaplet.
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 b Source #
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.
Instances
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.
Arguments
| :: 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.
Arguments
| :: 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. | 
| -> SnapletLens v 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.
Arguments
| :: 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. | 
| -> SnapletLens v 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 the top-level state, 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.
Note that this function does not change where this snaplet is located in the filesystem. The snaplet directory structure convention stays the same. Also, embedSnaplet limits the ways that snaplets can interact, so we usually recommend using nestSnaplet instead. However, we provide this function because sometimes reduced flexibility is useful. In short, if you don't understand what this function does for you from looking at its type, you probably don't want to use it.
Arguments
| :: 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 (Either Text 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 (Either Text (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.
getRoutes :: Initializer b v [ByteString] Source #
Lets you retrieve the list of routes currently set up by an Initializer. This can be useful in debugging.
getEnvironment :: Initializer b v String Source #
Return the current environment string.  This will be the
 environment given to runSnaplet or from the command line when
 using serveSnaplet.  Useful for changing behavior during
 development and testing.
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
 wrapSite.
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.
Arguments
| :: (Handler b v () -> Handler b v ()) | Handler modifier function | 
| -> Initializer b v () | 
Wraps the base snaplet's routing in another handler, allowing you to run code before and after all routes in an application.
Here are some examples of things you might do:
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.
Instances
failIfNotLocal :: MonadSnap m => m b -> m b Source #
Pass if the request is not coming from localhost.
reloadSite :: Handler b v () Source #
Handler that reloads the site.
modifyMaster :: v -> Handler b v () Source #
Lets you change a snaplet's initial state. It's almost like a reload, except that it doesn't run the initializer. It just modifies the result of the initializer. This can be used to let you define actions for reloading individual snaplets.
bracketHandler :: IO a -> (a -> IO x) -> (a -> Handler b v c) -> Handler b v c Source #
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 failorfinishWith
- An exception being thrown.
Serving Applications
runSnaplet :: Maybe String -> SnapletInit b b -> IO (Text, Snap (), IO ()) Source #
Given an environment and a Snaplet initializer, produce a concatenated log of all 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 configuration files used by 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.
Arguments
| :: Config Snap AppConfig | The configuration of the server - you can usually pass a
 default  | 
| -> SnapletInit b b | The snaplet initializer function. | 
| -> IO () | 
Initialize and run a Snaplet. This function parses command-line arguments,
 runs the given Snaplet initializer, and starts an HTTP server running the
 Snaplet's toplevel Handler.
serveSnapletNoArgParsing Source #
Arguments
| :: Config Snap AppConfig | The configuration of the server - you can usually pass a
 default  | 
| -> SnapletInit b b | The snaplet initializer function. | 
| -> IO () | 
Like serveSnaplet, but don't try to parse command-line arguments.
Arguments
| :: FileName | The name of the config file to look for.  In snap
 applications, this is something based on the
 environment...i.e.  | 
| -> FilePath | Path to the root directory of your project. | 
| -> IO Config | 
Allows you to get all of your app's config data in the IO monad without the web server infrastructure.
Snaplet Lenses
type SnapletLens s a = ALens' s (Snaplet a) Source #