fn: A functional web framework.

[ library, web ] [ Propose Tags ]

A Haskell web framework where you write plain old functions.

Provided you have stack installed, you can run this example like a shell script (it'll listen on port 3000):

#!/usr/bin/env stack
-- stack --resolver lts-5.5 --install-ghc runghc --package fn --package warp
{-# LANGUAGE OverloadedStrings #-}
import Data.Monoid ((<>))
import Data.Text (Text)
import Network.Wai (Response)
import Network.Wai.Handler.Warp (run)
import Web.Fn

data Ctxt = Ctxt { _req :: FnRequest }
instance RequestContext Ctxt where
  getRequest = _req
  setRequest c r = c { _req = r }

initializer :: IO Ctxt
initializer = return (Ctxt defaultFnRequest)

main :: IO ()
main = do ctxt <- initializer
          run 3000 $ toWAI ctxt site

site :: Ctxt -> IO Response
site ctxt = route ctxt [ end                        ==> indexH
                       , path "echo" // param "msg" ==> echoH
                       , path "echo" // segment     ==> echoH
                       ]
                  `fallthrough` notFoundText "Page not found."

indexH :: Ctxt -> IO (Maybe Response)
indexH _ = okText "Try visiting /echo?msg=hello or /echo/hello"

echoH :: Ctxt -> Text -> IO (Maybe Response)
echoH _ msg = okText $ "Echoing '" <> msg <> "'."

Fn lets you write web code that just looks like normal Haskell code.

  • An application has some "context", which must contain a Request, but can contain other data as well, like database connection pools, etc. This context will be passed to each of your handlers, updated with the current HTTP Request.

  • Routes are declared to capture parameters and/or segments of the url, and then routed to handler functions that have the appropriate number and type of arguments. These functions return IO (Maybe Response), where Nothing indicates to Fn that you want it to keep looking for matching routes.

  • All handlers just use plain old IO, which means it is easy to call them from GHCi, forkIO, etc.

  • All of this is a small wrapper around the WAI interface, so you have the flexilibility to do anything you need to do with HTTP.

The name comes from the fact that Fn emphasizes functions (over monads), where all necessary data is passed via function arguments, and control flow is mediated by return values.


[Skip to Readme]

Modules

[Index]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.0.0.0, 0.1.0.0, 0.1.1.0, 0.1.2.0, 0.1.3.0, 0.1.3.1, 0.1.4.0, 0.2.0.0, 0.2.0.1, 0.2.0.2, 0.3.0.0, 0.3.0.1, 0.3.0.2 (info)
Change log CHANGELOG.md
Dependencies base (>=4.7 && <6), blaze-builder, bytestring, directory, filepath, http-types, resourcet, text, unordered-containers, wai (>=3), wai-extra (>=3) [details]
License ISC
Copyright 2016 Position Development, LLC.
Author Daniel Patterson <dbp@dbpmail.net>
Maintainer workers@positiondev.com
Category Web
Home page http://github.com/positiondev/fn#readme
Source repo head: git clone https://github.com/positiondev/fn
Uploaded by LibbyHoracek at 2017-09-13T00:23:41Z
Distributions LTSHaskell:0.3.0.2, NixOS:0.3.0.2, Stackage:0.3.0.2
Reverse Dependencies 1 direct, 1 indirect [details]
Downloads 8535 total (47 in the last 30 days)
Rating 2.25 (votes: 2) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2017-09-13 [all 1 reports]

Readme for fn-0.3.0.2

[back to package description]

Fn (eff-enn) - a functional web framework.

Or, how to do away with the monad transformers, and just use plain functions.

Example

See the example application in the repository for a full usage including database access, heist templates, sessions, etc.