Skip to content

Architecture: happstack

Alias Qli edited this page Jul 13, 2022 · 6 revisions

May be out of date

Happstack is a web framework for Haskell. happstack-server provides utilities for responding to HTTP requests. happstack-state provides persistent storage of native Haskell datatypes.

The information below is subject to change for major Happstack releases. It's a very rough guide; the documentation is of course a good place to start too.

happstack-server

ServerPart is the main monad from which requests are served. Unwrapped in 0.5.0.2, it looks something like:

Request -> (Maybe (Either Response a, SetAppend (Response -> Response)))

Essentially it's a Request -> Response which can fail or be modified in a bunch of ways.

Below I've outlined some of the things you can do with it.

Return a response

The top level server function looks something like:

simpleHTTP :: Conf -> ServerPart Response -> IO ()

If you do simpleHTTP (return res), then this serves res :: Response with an HTTP 200 (ok) response code. The easiest way to construct a response is with the ToMessage typeclass. In Hackage, these are defined in Happstack.Server.ResourceTypes.

newtype CabalFile = CabalFile BS.Lazy.ByteString
instance ToMessage CabalFile where
    toContentType _ = BS.pack "text/plain"
    toMessage (CabalFile bs) = bs

newtype SuggestJson = SuggestJson JSON.JSValue
instance ToMessage SuggestJson where
    toContentType _ = BS.pack "application/x-suggestions+json"
    toMessage (SuggestJson val) = BS.Lazy.pack $ JSON.encode val

The method toResponse constructs a Response object from this information. Some useful instances of ToMessage that are built in with Happstack include (), which returns a blank page, and String, which returns a text/plain page.

Tampering with responses

Happstack provides a way to tamper with responses even before you generate them by providing a stack of functions to filter the response through. It's called FilterMonad, and ServerPart is an instance of it. Some useful functions defined in Happstack.Server.SimpleHTTP, again with simplified typeclasses, are:

setResponseCode :: Int -> ServerPart ()

ok :: a -> ServerPart a
--- and likewise for forbidden, notFound, badRequest, internalServerError

seeOther :: ToSURI uri => uri -> res -> ServerPart res
-- Some instances of ToSURI: String, Network.URI

addHeaderM :: String -> String -> ServerPart ()

setHeaderM :: String -> String -> ServerPart ()

Examples:

randomFind :: ServerPart Response
randomFind = do
   num <- liftIO $ randomRIO (1, 3)
   case num of
      1 -> ok $ toResponse "Important information"
      2 -> notFound $ toResponse "The fates have decided your document is missing"
      3 -> do
         setHeaderM "X-Serve-Info" "Two cubes of sugar"
         setResponseCode 418
         return $ toResponse "I'm a teapot"
      _ -> internalServerError $ toResponse "Impossible"

Routing URIs with MonadPlus

Happstack utilizes a combinator approach to route URIs that are requested from it. First, it splits URIs into their component parts, so "/page/5/test.html" becomes ["page", "5", "test.html"]. Then it lets you traverse the list using these key functions:

dir :: String -> ServerPart a -> ServerPart a
path :: FromReqURI a => (a -> ServerPart b) -> ServerPart b
nullDir :: ServerPart ()

ServerPart is an instance of MonadPlus, so routes are combined together using mplus. if a certain URI routing returns mzero, it tries the next one, and this is a very cheap operation. dir makes sure a ServerPart is only entered if it can pop the directory in question, so dir "page" would make the above list become ["5", "test.html"]. path enters a ServerPart if there's still a path segment left, regardless of what it is, and passes its value along the way. Otherwise, both of these return mzero. nullDir makes a branch return mzero if there are still remaining path segments. For example:

simpleHTTP $ msum
  [ dir "help" $ return . toResponse $ "help"
  , dir "content" $ msum
      [ dir "index" $ do
            nullDir
            return . toResponse $ "index"
      , path $ \str -> case str of
            ('t':_) -> mzero
            _ ->  return . toResponse $ "other " ++ str
      ]
  , notFound . toResponse $ "404"
  ]

Here are some example results that cover all of the branches.

/help                 help
/help/me/             help
/content              404
/content/index/       index
/content/index/help   404
/content/telephone    404
/content/internet     other internet
/omg                  404

Routing URIs isn't enough, though: it's also important to select certain ways to response to certain HTTP methods, like GET or POST. These are defined in Happstack as constructors of the Method type, and they can be used with:

methodSP :: Method -> ServerPart a -> ServerPart a
-- Executes code only if the method is the Method and
-- there are no remaining path segments (nullDir). This is very
-- commonly used in Happstack code.
methodOnly :: Method -> ServerPart ()
-- Guards against the method, nothing else.

Note that the Hackage approach ignores these combinators in order to merge nearly-redundant routes with the Resource and ServerTree objects, but it's useful to know how it works.

Querying from requests

After routing your URIs; how do you obtain other information from requests? Happstack provides some functions to take advantage of the fact that it's a Reader for the Request object (defined in Happstack.Server.HTTP.Types).

getHeaderM :: String -> ServerPart (Maybe ByteString)
-- e.g. agent <- fmap (maybe "Unknown" BS.unpack) $ getHeaderM "User-Agent"

The preferred way to get form inputs is with

getDataFn :: RqData a -> ServerPart (Maybe a)

RqData is a reader monad over the inputs of a request (there is presently no distinction between inputs in a URI and those in a request body, whether multipart or URI-encoded). An example:

mres <- getDataFn $ liftM2 (,) (lookInput "file") (look "summary")
case mres of
    Nothing -> badRequest $ toResponse "file and summary inputs have to both be present"
    Just (body, _) | maybe True (any (not . isAlpha)) (inputFilename body) ->
        badRequest $ toResponse "File name is invalid"
    Just (body, summary) -> do
        isMinor <- fmap (maybe True $ \_ -> False) $ getDataFn $ look "minor"
        return . toResponse $ printf
            "You submitted a %d-byte document with the summary %s. This is%s a minor revision.\n"
            (BS.length $ inputValue body) (show summary) (if isMinor then "" else " not")

The askRq method gives you the request object directly, although there's little need for this (except perhaps to get the raw request body).

Serving a file

You can serve a file by creating a lazy bytestring for it and making a ToMessage type for it. Alternatively, you can use functions in Happstack.Server.HTTP.FileServe with simplified typeclasses:

serveFile :: (FilePath -> ServerPart String) -> FilePath -> ServerPart Response
asContentType :: Monad m => String -> FilePath -> m String
guessContentTypeM :: Monad m => MimeMap -> FilePath -> m String

You can write serveFile (asContentType "/text/plain") "/path/to/file" or use the guessing function with mimeTypes :: MimeMap. Make sure you're generating the path to the file yourself (use System.FilePath.Posix), rather than letting the user provide it.

safecopy

Hackage server uses acid-state for persistent data and safecopy for managing migrations. You can find many examples of acid-state usage in that project's github repository.

Making a data structure work with safecopy

To store a Hackage data structure you will need to make a SafeCopy instance for it.

class SafeCopy a where
    getCopy :: Contained (Get a)
    putCopy :: a -> Contained Put

A basic SafeCopy instance is:

instance SafeCopy DataStructure where
  getCopy = contained $ ...
  putCopy = contained $ ...
  kind = base
  version = 0

This instance allows the structure to be migrated to a newer one by, among other things, incrementing the version number. A simple example could be seen at Data.SafeCopy.

You can make a SafeCopy instance for a data structure with Template Haskell magic:

deriveSafeCopy 0 'base ''DataStructure

If you have numbers or strings with special meanings (like id numbers) it's a good practice to use a newtype wrapper and make a basic SafeCopy instance for it.

If you find you need to declare SafeCopy instances for data structures not defined by hackage-server, put them in Distribution.Server.Instances.

Making a happstack-state component

Components are data structures which you can query and update with happstack-state. Declaring an instance for a single structure is pretty simple:

instance Component DataStructure where
   type Dependencies DataStructure = End
   initialValue = emptyDataStruture

The highest level component in hackage-server is in Distribution.Server.State, and if you want a feature to use querying functions for a component, you should add it there. The main difference between using many combined components and one big data structure is that although updates are atomic within a component, they can't be all combined into one update function if an action affects more than one of them. The upside is that it's so much more flexible for adding new data.

Making functions for happstack-state structures and calling them

Functions for a component should all be declared in same module. They use the Update monad, which is a MonadState, and the Query monad, which is a MonadReader. For instance:

incrementByFloat :: String -> Float -> Update DataStructure Bool
incrementByFloat name arg = do
    updateStructure (+arg)
    data <- get
    res <- ... data ...
    case res of
        Nothing -> return False  --failure
        Just data' -> put data' >> return True

updateStructure :: (Float -> Float) -> Update DataStructure ()
updateStructure func = modify $ \st -> st { floatThing = func $ floatThing st }

getFloatThing :: Query DataStructure Float
getFloatThing = asks floatThing

-- have to be grouped together
$(mkMethods ''DataStructure ['incrementByFloat
                            ,'getFloatThing
                            ])

keepItUnder :: IO Float
keepItUnder = do
    res <- query $ GetFloatThing
    when (res > 10) $ update $ IncrementByFloat "thing" (10-res)
    return res

Some tips:

  • Do not let update arguments be too large (e.g., replacing an entire data structure). In order to replay data transactions, if necessary, happstack-state records the arguments into its database, and you can get a gigabyte-sized database very easily.
  • As a consequence of the above, Update/Query functions that are listed in mkMethods have to have serializeable arguments. It doesn't prevent making helper functions like updateStructure, only using them in mkMethods.
  • Make sure update operations maintain the consistency of any internal indices and minimize server race conditions by integrating checking into the Update operation itself, possibly with additional invariant-checking afterwards. keepItUnder fails to do this (imagine how calls could interleave).
  • Try not to do any Template Haskell in feature modules themselves, partly because of TH declaration ordering rules, and also to keep features focused on how to expose the data structures rather than their gritty internals.
  • It's a good idea to supply operations to query the entire component (defined as ask) and replace the entire component (defined as put). This is useful for backup.

When you migrates to a newer version of a happstack-state structure, you may want new functions as well. While creating new functions is totally OK, only Query functions can be safely modified and deleted. Update functions shouldn't be deleted, and their signatures shouldn't be changed either. Only their implementation may be changed.