Skip to content

Commit

Permalink
Merge b1e9b07 into 4bc8ef0
Browse files Browse the repository at this point in the history
  • Loading branch information
Ryan Scott committed Jan 2, 2015
2 parents 4bc8ef0 + b1e9b07 commit 9444b64
Show file tree
Hide file tree
Showing 13 changed files with 58 additions and 26 deletions.
2 changes: 2 additions & 0 deletions Web/Scotty/Action.hs
Expand Up @@ -46,7 +46,9 @@ import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Lazy.Char8 as BL
import qualified Data.CaseInsensitive as CI
import Data.Default (def)
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid (mconcat)
#endif
import qualified Data.Text as ST
import qualified Data.Text.Lazy as T
import Data.Text.Lazy.Encoding (encodeUtf8)
Expand Down
4 changes: 4 additions & 0 deletions Web/Scotty/Internal/Types.hs
Expand Up @@ -3,7 +3,9 @@ module Web.Scotty.Internal.Types where

import Blaze.ByteString.Builder (Builder)

#if !(MIN_VERSION_base(4,8,0))
import Control.Applicative
#endif
import qualified Control.Exception as E
import Control.Monad.Base (MonadBase, liftBase, liftBaseDefault)
#if MIN_VERSION_mtl(2,2,1)
Expand All @@ -18,7 +20,9 @@ import Control.Monad.Trans.Control (MonadBaseControl, StM, liftBaseWit
import qualified Data.ByteString as BS
import Data.ByteString.Lazy.Char8 (ByteString)
import Data.Default (Default, def)
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid (mempty)
#endif
import Data.String (IsString(..))
import Data.Text.Lazy (Text, pack)
import Data.Typeable (Typeable)
Expand Down
2 changes: 2 additions & 0 deletions Web/Scotty/Route.hs
Expand Up @@ -18,7 +18,9 @@ import qualified Control.Monad.State as MS
import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Lazy.Char8 as BL
import Data.Maybe (fromMaybe, isJust)
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid (mconcat)
#endif
import Data.String (fromString)
import qualified Data.Text.Lazy as T
import qualified Data.Text as TS
Expand Down
14 changes: 8 additions & 6 deletions examples/basic.hs
@@ -1,16 +1,18 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP, OverloadedStrings #-}
module Main (main) where

import Web.Scotty

import Network.Wai.Middleware.RequestLogger -- install wai-extra if you don't have this

import Control.Monad
import Control.Monad.Trans
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid
#endif
import System.Random (newStdGen, randomRs)

import Network.HTTP.Types (status302)
import Network.Wai
import qualified Data.Text.Lazy as T

import Data.Text.Lazy.Encoding (decodeUtf8)
import Data.String (fromString)
Expand Down Expand Up @@ -45,12 +47,12 @@ main = scotty 3000 $ do

-- redirects preempt execution
get "/redirect" $ do
redirect "http://www.google.com"
void $ redirect "http://www.google.com"
raise "this error is never reached"

-- Of course you can catch your own errors.
get "/rescue" $ do
(do raise "a rescued error"; redirect "http://www.we-never-go-here.com")
(do void $ raise "a rescued error"; redirect "http://www.we-never-go-here.com")
`rescue` (\m -> text $ "we recovered from " `mappend` m)

-- Parts of the URL that start with a colon match
Expand All @@ -65,7 +67,7 @@ main = scotty 3000 $ do

-- You can stop execution of this action and keep pattern matching routes.
get "/random" $ do
next
void next
redirect "http://www.we-never-go-here.com"

-- You can do IO with liftIO, and you can return JSON content.
Expand Down
2 changes: 1 addition & 1 deletion examples/bodyecho.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
module Main where
module Main (main) where

import Web.Scotty

Expand Down
15 changes: 8 additions & 7 deletions examples/cookies.hs
@@ -1,9 +1,10 @@
{-# LANGUAGE OverloadedStrings #-}
-- This examples requires you to: cabal install cookie
-- and: cabal install blaze-html
module Main (main) where

import Control.Monad (forM_)
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as T
import qualified Data.Text.Lazy.Encoding as T
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL
Expand All @@ -27,7 +28,7 @@ setCookie n v = setHeader "Set-Cookie" (renderSetCookie' (makeCookie n v))
getCookies :: ActionM (Maybe CookiesText)
getCookies =
fmap (fmap (parseCookiesText . lazyToStrict . T.encodeUtf8)) $
reqHeader "Cookie"
header "Cookie"
where
lazyToStrict = BS.concat . BSL.toChunks

Expand All @@ -37,9 +38,9 @@ renderCookiesTable cs =
H.tr $ do
H.th "name"
H.th "value"
forM_ cs $ \(name, val) -> do
forM_ cs $ \(name', val) -> do
H.tr $ do
H.td (H.toMarkup name)
H.td (H.toMarkup name')
H.td (H.toMarkup val)

main :: IO ()
Expand All @@ -56,7 +57,7 @@ main = scotty 3000 $ do
H.input H.! type_ "submit" H.! value "set a cookie"

post "/set-a-cookie" $ do
name <- param "name"
value <- param "value"
setCookie name value
name' <- param "name"
value' <- param "value"
setCookie name' value'
redirect "/"
13 changes: 8 additions & 5 deletions examples/exceptions.hs
@@ -1,15 +1,18 @@
{-# LANGUAGE OverloadedStrings, GeneralizedNewtypeDeriving, ScopedTypeVariables #-}
module Main where
{-# LANGUAGE CPP, OverloadedStrings, GeneralizedNewtypeDeriving, ScopedTypeVariables #-}
module Main (main) where

#if !(MIN_VERSION_base(4,8,0))
import Control.Applicative
import Control.Monad.Error
#endif
import Control.Monad.IO.Class

#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid
#endif
import Data.String (fromString)

import Network.HTTP.Types
import Network.Wai.Middleware.RequestLogger
import Network.Wai

import System.Random

Expand Down Expand Up @@ -51,7 +54,7 @@ main = scottyT 3000 id id $ do -- note, we aren't using any additional transform

get "/switch/:val" $ do
v <- param "val"
if even v then raise Forbidden else raise (NotFound v)
_ <- if even v then raise Forbidden else raise (NotFound v)
text "this will never be reached"

get "/random" $ do
Expand Down
9 changes: 6 additions & 3 deletions examples/globalstate.hs
@@ -1,4 +1,4 @@
{-# LANGUAGE OverloadedStrings, GeneralizedNewtypeDeriving #-}
{-# LANGUAGE CPP, OverloadedStrings, GeneralizedNewtypeDeriving #-}
-- An example of embedding a custom monad into
-- Scotty's transformer stack, using ReaderT to provide access
-- to a TVar containing global state.
Expand All @@ -7,8 +7,11 @@
-- is IO itself. The types of 'scottyT' and 'scottyAppT' are
-- general enough to allow a Scotty application to be
-- embedded into any MonadIO monad.
module Main where
module Main (main) where

#if !(MIN_VERSION_base(4,8,0))
import Control.Applicative
#endif
import Control.Concurrent.STM
import Control.Monad.Reader

Expand Down Expand Up @@ -36,7 +39,7 @@ instance Default AppState where
-- Also note: your monad must be an instance of 'MonadIO' for
-- Scotty to use it.
newtype WebM a = WebM { runWebM :: ReaderT (TVar AppState) IO a }
deriving (Monad, MonadIO, MonadReader (TVar AppState))
deriving (Applicative, Functor, Monad, MonadIO, MonadReader (TVar AppState))

-- Scotty's monads are layered on top of our custom monad.
-- We define this synonym for lift in order to be explicit
Expand Down
2 changes: 2 additions & 0 deletions examples/gzip.hs
@@ -1,4 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
module Main (main) where

import Network.Wai.Middleware.RequestLogger
import Network.Wai.Middleware.Gzip

Expand Down
6 changes: 4 additions & 2 deletions examples/options.hs
@@ -1,15 +1,17 @@
{-# LANGUAGE OverloadedStrings #-}
module Main (main) where

import Web.Scotty

import Network.Wai.Middleware.RequestLogger -- install wai-extra if you don't have this

import Data.Default (def)
import Network.Wai.Handler.Warp (settingsPort)
import Network.Wai.Handler.Warp (setPort)

-- Set some Scotty settings
opts :: Options
opts = def { verbose = 0
, settings = (settings def) { settingsPort = 4000 }
, settings = setPort 4000 $ settings def
}

-- This won't display anything at startup, and will listen on localhost:4000
Expand Down
3 changes: 3 additions & 0 deletions examples/reader.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}

Expand All @@ -7,7 +8,9 @@
-}
module Main where

#if !(MIN_VERSION_base(4,8,0))
import Control.Applicative (Applicative)
#endif
import Control.Monad.Reader (MonadIO, MonadReader, ReaderT, asks, lift, runReaderT)
import Data.Default (def)
import Data.Text.Lazy (Text, pack)
Expand Down
6 changes: 5 additions & 1 deletion examples/upload.hs
@@ -1,8 +1,12 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP, OverloadedStrings #-}
module Main (main) where

import Web.Scotty

import Control.Monad.IO.Class
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid
#endif

import Network.Wai.Middleware.RequestLogger
import Network.Wai.Middleware.Static
Expand Down
6 changes: 5 additions & 1 deletion examples/urlshortener.hs
@@ -1,10 +1,14 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP, OverloadedStrings #-}
module Main (main) where

import Web.Scotty

import Control.Concurrent.MVar
import Control.Monad.IO.Class
import qualified Data.Map as M
#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid (mconcat)
#endif
import qualified Data.Text.Lazy as T

import Network.Wai.Middleware.RequestLogger
Expand Down

0 comments on commit 9444b64

Please sign in to comment.