welshy: Haskell web framework (because Scotty had trouble yodeling)
A Haskell web framework heavily influenced by the excellent Scotty, which was in turn influenced by Ruby's Sinatra.
Welshy strives to make it easier to do error handling without overly complicating the control flow. An example:
{-# LANGUAGE OverloadedStrings #-}
import Control.Applicative import Control.Monad import qualified Data.Text.Lazy as T import Network.HTTP.Types import Web.Welshy fibs :: [Int] fibs = 0 : 1 : zipWith (+) fibs (tail fibs) main :: IO () main = welshy 3000 $ do get "/fibs" $ do offset <- queryParam "offset" <|> return 0 length <- queryParam "length" when (offset < 0 || length < 0) (halt $ status badRequest400) when (offset + length > 1000) (halt $ status requestedRangeNotSatisfiable416) let result = take length $ drop offset fibs text $ T.pack $ show result
Some of the features demonstrated here:
You can
halt
the current action at any point and continue with a different one.Functions like
queryParam
andjsonParam
have built-in error handling.Welshy's
Action
monad is an instance ofAlternative
.
Downloads
- welshy-0.1.0.0.tar.gz [browse] (Cabal source package)
- Package description (revised from the package)
Note: This package has metadata revisions in the cabal description newer than included in the tarball. To unpack the package including the revisions, use 'cabal get'.
Maintainer's Corner
For package maintainers and hackage trustees
Candidates
- No Candidates
Versions [RSS] | 0.1.0.0 |
---|---|
Dependencies | aeson (>=0.6 && <0.7), base (>=4.6 && <4.8), blaze-builder (>=0.3 && <0.4), bytestring (>=0.10 && <0.11), conduit (>=1.0 && <1.1), http-types (>=0.8 && <0.9), lifted-base (>=0.2 && <0.3), resourcet (>=0.4 && <0.5), text (>=0.11 && <0.12), transformers (>=0.3 && <0.4), unordered-containers (>=0.2 && <0.3), wai (>=1.4 && <1.5), warp (>=1.3 && <1.4) [details] |
License | MIT |
Copyright | (c) 2013 Michael Schröder |
Author | Michael Schröder |
Maintainer | mcschroeder@gmail.com |
Revised | Revision 1 made by MichaelSchroeder at 2015-02-22T21:42:42Z |
Category | Web |
Home page | https://github.com/mcschroeder/welshy |
Bug tracker | https://github.com/mcschroeder/welshy/issues |
Source repo | head: git clone https://github.com/mcschroeder/welshy.git |
Uploaded | by MichaelSchroeder at 2013-09-30T18:12:12Z |
Distributions | |
Reverse Dependencies | 1 direct, 0 indirect [details] |
Downloads | 1157 total (5 in the last 30 days) |
Rating | (no votes yet) [estimated by Bayesian average] |
Your Rating | |
Status | Docs available [build log] Successful builds reported [all 1 reports] |