{-# LANGUAGE OverloadedStrings, GeneralizedNewtypeDeriving, ScopedTypeVariables #-} module Main where import Control.Applicative import Control.Monad.Error import Data.Monoid import Data.String (fromString) import Network.HTTP.Types import Network.Wai.Middleware.RequestLogger import Network.Wai import System.Random import Web.Scotty.Trans -- Define a custom exception type. data Except = Forbidden | NotFound Int | StringEx String deriving (Show, Eq) -- The type must be an instance of 'ScottyError'. -- 'ScottyError' is essentially a combination of 'Error' and 'Show'. instance ScottyError Except where stringError = StringEx showError = fromString . show -- Handler for uncaught exceptions. handleEx :: Monad m => Except -> ActionT Except m () handleEx Forbidden = do status status403 html "

Scotty Says No

" handleEx (NotFound i) = do status status404 html $ fromString $ "

Can't find " ++ show i ++ ".

" main :: IO () main = scottyT 3000 id id $ do -- note, we aren't using any additional transformer layers -- so we can just use 'id' for the runners. middleware logStdoutDev defaultHandler handleEx -- define what to do with uncaught exceptions get "/" $ do html $ mconcat ["Option 1 (Not Found)" ,"
" ,"Option 2 (Forbidden)" ,"
" ,"Option 3 (Random)" ] get "/switch/:val" $ do v <- param "val" if even v then raise Forbidden else raise (NotFound v) text "this will never be reached" get "/random" $ do rBool <- liftIO randomIO i <- liftIO randomIO let catchOne Forbidden = html "

Forbidden was randomly thrown, but we caught it." catchOne other = raise other raise (if rBool then Forbidden else NotFound i) `rescue` catchOne