Merge pull request #196 from haskell-servant/jkarni/contributing
'Contributing' section in the README + stylish haskell changes
This commit is contained in:
commit
90d837dda9
68 changed files with 557 additions and 457 deletions
77
.stylish-haskell.yaml
Normal file
77
.stylish-haskell.yaml
Normal file
|
@ -0,0 +1,77 @@
|
|||
# stylish-haskell configuration file
|
||||
# ==================================
|
||||
|
||||
# The stylish-haskell tool is mainly configured by specifying steps. These steps
|
||||
# are a list, so they have an order, and one specific step may appear more than
|
||||
# once (if needed). Each file is processed by these steps in the given order.
|
||||
steps:
|
||||
# Convert some ASCII sequences to their Unicode equivalents. This is disabled
|
||||
# by default.
|
||||
# - unicode_syntax:
|
||||
# # In order to make this work, we also need to insert the UnicodeSyntax
|
||||
# # language pragma. If this flag is set to true, we insert it when it's
|
||||
# # not already present. You may want to disable it if you configure
|
||||
# # language extensions using some other method than pragmas. Default:
|
||||
# # true.
|
||||
# add_language_pragma: true
|
||||
|
||||
# Import cleanup
|
||||
- imports:
|
||||
# There are different ways we can align names and lists.
|
||||
#
|
||||
# - global: Align the import names and import list throughout the entire
|
||||
# file.
|
||||
#
|
||||
# - file: Like global, but don't add padding when there are no qualified
|
||||
# imports in the file.
|
||||
#
|
||||
# - group: Only align the imports per group (a group is formed by adjacent
|
||||
# import lines).
|
||||
#
|
||||
# - none: Do not perform any alignment.
|
||||
#
|
||||
# Default: global.
|
||||
align: global
|
||||
|
||||
# Language pragmas
|
||||
- language_pragmas:
|
||||
# We can generate different styles of language pragma lists.
|
||||
#
|
||||
# - vertical: Vertical-spaced language pragmas, one per line.
|
||||
#
|
||||
# - compact: A more compact style.
|
||||
#
|
||||
# - compact_line: Similar to compact, but wrap each line with
|
||||
# `{-#LANGUAGE #-}'.
|
||||
#
|
||||
# Default: vertical.
|
||||
style: vertical
|
||||
|
||||
# stylish-haskell can detect redundancy of some language pragmas. If this
|
||||
# is set to true, it will remove those redundant pragmas. Default: true.
|
||||
remove_redundant: true
|
||||
|
||||
# Align the types in record declarations
|
||||
- records: {}
|
||||
|
||||
# Replace tabs by spaces. This is disabled by default.
|
||||
# - tabs:
|
||||
# # Number of spaces to use for each tab. Default: 8, as specified by the
|
||||
# # Haskell report.
|
||||
# spaces: 8
|
||||
|
||||
# Remove trailing whitespace
|
||||
- trailing_whitespace: {}
|
||||
|
||||
# A common setting is the number of columns (parts of) code will be wrapped
|
||||
# to. Different steps take this into account. Default: 80.
|
||||
columns: 80
|
||||
|
||||
# Sometimes, language extensions are specified in a cabal file or from the
|
||||
# command line instead of using language pragmas in the file. stylish-haskell
|
||||
# needs to be aware of these, so it can parse the file correctly.
|
||||
#
|
||||
# No language extensions are enabled by default.
|
||||
language_extensions:
|
||||
- TemplateHaskell
|
||||
- QuasiQuotes
|
6
HLint.hs
Normal file
6
HLint.hs
Normal file
|
@ -0,0 +1,6 @@
|
|||
import "hint" HLint.Default
|
||||
|
||||
ignore "Redundant do"
|
||||
ignore "Parse error"
|
||||
ignore "Use list comprehension"
|
||||
ignore "Use liftM"
|
53
README.md
53
README.md
|
@ -5,17 +5,56 @@
|
|||
|
||||
![servant](https://raw.githubusercontent.com/haskell-servant/servant/master/servant.png)
|
||||
|
||||
These libraries provides a family of combinators to define webservices and automatically generate the documentation and client-side querying functions for each endpoint.
|
||||
These libraries provides a family of combinators to define webservices and
|
||||
automatically generate the documentation and client-side querying functions for
|
||||
each endpoint.
|
||||
|
||||
In order to minimize the dependencies depending on your needs, we provide these features under different packages.
|
||||
In order to minimize the dependencies depending on your needs, we provide these
|
||||
features under different packages.
|
||||
|
||||
- `servant`, which contains everything you need to *declare* a webservice API.
|
||||
- `servant-server`, which lets you *implement* an HTTP server with handlers for each endpoint of an API.
|
||||
- `servant-client`, which lets you derive automatically Haskell functions that let you query each endpoint of a `servant` webservice.
|
||||
- `servant-server`, which lets you *implement* an HTTP server with handlers for
|
||||
each endpoint of an API.
|
||||
- `servant-client`, which lets you derive automatically Haskell functions that
|
||||
let you query each endpoint of a `servant` webservice.
|
||||
- `servant-docs`, which lets you generate API docs for your webservice.
|
||||
- `servant-js`, which lets you derive Javascript functions (using vanilla JS ajax requests, angular or jquery) to query your API's endpoints, in the same spirit as `servant-client`.
|
||||
- `servant-blaze` and `servant-lucid` provide easy HTML rendering of your data as an `HTML` content-type "combinator".
|
||||
- `servant-js`, which lets you derive Javascript functions (using vanilla JS
|
||||
ajax requests, angular or jquery) to query your API's endpoints, in the same
|
||||
spirit as `servant-client`.
|
||||
- `servant-blaze` and `servant-lucid` provide easy HTML rendering of your data
|
||||
as an `HTML` content-type "combinator".
|
||||
|
||||
## Tutorial
|
||||
|
||||
We have a [tutorial](http://haskell-servant.github.io/tutorial) guide that introduces the core types and features of servant. After this article, you should be able to write your first servant webservices, learning the rest from the haddocks' examples.
|
||||
We have a [tutorial](http://haskell-servant.github.io/tutorial) guide that
|
||||
introduces the core types and features of servant. After this article, you
|
||||
should be able to write your first servant webservices, learning the rest from
|
||||
the haddocks' examples.
|
||||
|
||||
## Contributing
|
||||
|
||||
Contributions are very welcome! To hack on the github version, clone the
|
||||
repository. You can use `cabal`:
|
||||
|
||||
```shell
|
||||
./scripts/start-sandbox.sh # Initialize the sandbox and add-source the packages
|
||||
./scripts/test-all.sh # Run all the tests
|
||||
```
|
||||
|
||||
`stack`:
|
||||
|
||||
```shell
|
||||
stack build # Install and build packages
|
||||
stack test # Run all the tests
|
||||
```
|
||||
|
||||
Or `nix`:
|
||||
```shell
|
||||
./scripts/update-nix-files.sh # Get up-to-date shell.nix files
|
||||
```
|
||||
|
||||
Though we aren't sticklers for style, the `.stylish-haskel.yaml` and `HLint.hs`
|
||||
files in the repository provide a good baseline for consistency.
|
||||
|
||||
Please include a description of the changes in your PR in the `CHANGELOG.md` of
|
||||
the packages you've changed. And of course, write tests!
|
||||
|
|
|
@ -11,7 +11,7 @@ module Servant.Common.BaseUrl (
|
|||
, showBaseUrl
|
||||
) where
|
||||
|
||||
import Control.Monad.Catch (MonadThrow, throwM, Exception)
|
||||
import Control.Monad.Catch (Exception, MonadThrow, throwM)
|
||||
import Data.List
|
||||
import Data.Typeable
|
||||
import GHC.Generics
|
||||
|
|
|
@ -99,7 +99,7 @@ setRQBody b t req = req { reqBody = Just (b, t) }
|
|||
|
||||
reqToRequest :: (Functor m, MonadThrow m) => Req -> BaseUrl -> m Request
|
||||
reqToRequest req (BaseUrl reqScheme reqHost reqPort) =
|
||||
fmap (setheaders . setAccept . setrqb . setQS ) $ parseUrl url
|
||||
setheaders . setAccept . setrqb . setQS <$> parseUrl url
|
||||
|
||||
where url = show $ nullURI { uriScheme = case reqScheme of
|
||||
Http -> "http:"
|
||||
|
|
|
@ -1,4 +1,4 @@
|
|||
import Servant.ClientSpec (spec, failSpec)
|
||||
import Servant.ClientSpec (failSpec, spec)
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
|
|
|
@ -1,5 +1,5 @@
|
|||
{-# LANGUAGE ConstraintKinds #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE ConstraintKinds #-}
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
|
@ -23,6 +23,7 @@ module Servant.Docs.Internal where
|
|||
import Control.Applicative
|
||||
#endif
|
||||
import Control.Lens
|
||||
import Data.ByteString.Conversion (ToByteString, toByteString)
|
||||
import Data.ByteString.Lazy.Char8 (ByteString)
|
||||
import qualified Data.CaseInsensitive as CI
|
||||
import Data.Hashable
|
||||
|
@ -32,7 +33,6 @@ import Data.Maybe
|
|||
import Data.Monoid
|
||||
import Data.Ord (comparing)
|
||||
import Data.Proxy
|
||||
import Data.ByteString.Conversion (ToByteString, toByteString)
|
||||
import Data.String.Conversions
|
||||
import Data.Text (Text, pack, unpack)
|
||||
import GHC.Exts (Constraint)
|
||||
|
|
|
@ -1,10 +1,10 @@
|
|||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
import Data.Aeson
|
||||
import Data.ByteString (ByteString)
|
||||
import Data.Text (Text)
|
||||
|
|
|
@ -1,7 +1,7 @@
|
|||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
import Control.Applicative
|
||||
import Control.Monad
|
||||
import Control.Monad.IO.Class
|
||||
|
|
|
@ -1,6 +1,6 @@
|
|||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
|
||||
|
||||
|
@ -8,17 +8,17 @@ import Data.Monoid ((<>))
|
|||
#if !MIN_VERSION_base(4,8,0)
|
||||
import Control.Applicative ((<$>))
|
||||
#endif
|
||||
import Network.Wai
|
||||
import Servant
|
||||
import Network.EngineIO.Wai
|
||||
import Network.Wai
|
||||
import Network.Wai.Handler.Warp (run)
|
||||
import Servant
|
||||
|
||||
|
||||
import qualified Control.Concurrent.STM as STM
|
||||
import qualified Network.SocketIO as SocketIO
|
||||
|
||||
|
||||
import Chat (eioServer, ServerState (..))
|
||||
import Chat (ServerState (..), eioServer)
|
||||
|
||||
|
||||
type API = "socket.io" :> Raw
|
||||
|
|
|
@ -1,6 +1,6 @@
|
|||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
module T1 where
|
||||
|
||||
|
|
|
@ -1,9 +1,9 @@
|
|||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||
module T10 where
|
||||
|
||||
import Data.ByteString.Lazy (ByteString)
|
||||
|
|
|
@ -1,6 +1,6 @@
|
|||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
module T2 where
|
||||
|
||||
|
|
|
@ -1,6 +1,6 @@
|
|||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
module T3 where
|
||||
|
||||
|
|
|
@ -1,9 +1,9 @@
|
|||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
module T4 where
|
||||
|
||||
import Data.Aeson
|
||||
|
|
|
@ -1,8 +1,8 @@
|
|||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
module T5 where
|
||||
|
||||
import Control.Monad.IO.Class
|
||||
|
|
|
@ -1,8 +1,8 @@
|
|||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
module T9 where
|
||||
|
||||
import Control.Applicative
|
||||
|
|
|
@ -3,6 +3,7 @@ import Network.Wai.Handler.Warp
|
|||
import System.Environment
|
||||
|
||||
import qualified T1
|
||||
import qualified T10
|
||||
import qualified T2
|
||||
import qualified T3
|
||||
import qualified T4
|
||||
|
@ -10,7 +11,6 @@ import qualified T5
|
|||
import qualified T6
|
||||
import qualified T7
|
||||
import qualified T9
|
||||
import qualified T10
|
||||
|
||||
app :: String -> (Application -> IO ()) -> IO ()
|
||||
app n f = case n of
|
||||
|
|
|
@ -1,7 +1,7 @@
|
|||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
|
||||
import Control.Concurrent.STM
|
||||
import Control.Monad.IO.Class
|
||||
|
|
|
@ -1,7 +1,7 @@
|
|||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
-----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : Servant.JS
|
||||
|
|
|
@ -1,9 +1,9 @@
|
|||
module Servant.JS.Angular where
|
||||
|
||||
import Servant.JS.Internal
|
||||
import Control.Lens
|
||||
import Data.List
|
||||
import Data.Monoid
|
||||
import Servant.JS.Internal
|
||||
|
||||
-- | Options specific to the angular code generator
|
||||
data AngularOptions = AngularOptions
|
||||
|
|
|
@ -1,10 +1,10 @@
|
|||
module Servant.JS.Axios where
|
||||
|
||||
import Servant.JS.Internal
|
||||
import Control.Lens
|
||||
import Data.Char (toLower)
|
||||
import Data.List
|
||||
import Data.Monoid
|
||||
import Servant.JS.Internal
|
||||
|
||||
-- | Axios 'configuration' type
|
||||
-- Let you customize the generation using Axios capabilities
|
||||
|
|
|
@ -141,8 +141,8 @@ toValidFunctionName (x:xs) = [setFirstChar x] <> filter remainder xs
|
|||
setFirstChar c = if firstChar c
|
||||
then c
|
||||
else '_'
|
||||
firstChar c = (prefixOK c) || (or . map (Set.member c) $ firstLetterOK)
|
||||
remainder c = (prefixOK c) || (or . map (Set.member c) $ remainderOK)
|
||||
firstChar c = prefixOK c || any (Set.member c) firstLetterOK
|
||||
remainder c = prefixOK c || any (Set.member c) remainderOK
|
||||
-- Valid prefixes
|
||||
prefixOK c = c `elem` ['$','_']
|
||||
-- Unicode character sets
|
||||
|
|
|
@ -1,20 +1,20 @@
|
|||
module Servant.JS.JQuery where
|
||||
|
||||
import Servant.JS.Internal
|
||||
import Control.Lens
|
||||
import Data.List
|
||||
import Data.Monoid
|
||||
import Servant.JS.Internal
|
||||
|
||||
-- | Generate javascript functions that use the /jQuery/ library
|
||||
-- to make the AJAX calls. Uses 'defCommonGeneratorOptions'
|
||||
-- for the generator options.
|
||||
jquery :: JavaScriptGenerator
|
||||
jquery = concat . map generateJQueryJS
|
||||
jquery = concatMap generateJQueryJS
|
||||
|
||||
-- | Generate javascript functions that use the /jQuery/ library
|
||||
-- to make the AJAX calls. Lets you specify your own 'CommonGeneratorOptions'.
|
||||
jqueryWith :: CommonGeneratorOptions -> JavaScriptGenerator
|
||||
jqueryWith opts = concat . map (generateJQueryJSWith opts)
|
||||
jqueryWith opts = concatMap (generateJQueryJSWith opts)
|
||||
|
||||
-- | js codegen using JQuery using default options
|
||||
generateJQueryJS :: AjaxReq -> String
|
||||
|
|
|
@ -1,21 +1,21 @@
|
|||
module Servant.JS.Vanilla where
|
||||
|
||||
import Servant.JS.Internal
|
||||
import Control.Lens
|
||||
import Data.List
|
||||
import Data.Monoid
|
||||
import Servant.JS.Internal
|
||||
|
||||
-- | Generate vanilla javascript functions to make AJAX requests
|
||||
-- to your API, using /XMLHttpRequest/. Uses 'defCommonGeneratorOptions'
|
||||
-- for the 'CommonGeneratorOptions'.
|
||||
vanillaJS :: JavaScriptGenerator
|
||||
vanillaJS = concat . map generateVanillaJS
|
||||
vanillaJS = concatMap generateVanillaJS
|
||||
|
||||
-- | Generate vanilla javascript functions to make AJAX requests
|
||||
-- to your API, using /XMLHttpRequest/. Lets you specify your
|
||||
-- own options.
|
||||
vanillaJSWith :: CommonGeneratorOptions -> JavaScriptGenerator
|
||||
vanillaJSWith opts = concat . map (generateVanillaJSWith opts)
|
||||
vanillaJSWith opts = concatMap (generateVanillaJSWith opts)
|
||||
|
||||
-- | js codegen using XmlHttpRequest using default generation options
|
||||
generateVanillaJS :: AjaxReq -> String
|
||||
|
|
|
@ -14,10 +14,10 @@ import Test.Hspec
|
|||
|
||||
import Servant.API
|
||||
import Servant.JS
|
||||
import qualified Servant.JS.Vanilla as JS
|
||||
import qualified Servant.JS.JQuery as JQ
|
||||
import qualified Servant.JS.Angular as NG
|
||||
import qualified Servant.JS.Axios as AX
|
||||
import qualified Servant.JS.JQuery as JQ
|
||||
import qualified Servant.JS.Vanilla as JS
|
||||
import Servant.JSSpec.CustomHeaders
|
||||
|
||||
type TestAPI = "simple" :> ReqBody '[JSON,FormUrlEncoded] String :> Post '[JSON] Bool
|
||||
|
@ -102,7 +102,7 @@ axiosSpec = describe specLabel $ do
|
|||
cookieOpts = AX.defAxiosOptions { AX.xsrfCookieName = Just "MyXSRFcookie" }
|
||||
headerOpts = AX.defAxiosOptions { AX.xsrfHeaderName = Just "MyXSRFheader" }
|
||||
genJS :: AxiosOptions -> [AjaxReq] -> String
|
||||
genJS opts req = concat $ map (AX.generateAxiosJS opts) req
|
||||
genJS opts req = concatMap (AX.generateAxiosJS opts) req
|
||||
|
||||
angularSpec :: TestNames -> Spec
|
||||
angularSpec test = describe specLabel $ do
|
||||
|
@ -130,7 +130,7 @@ angularSpec test = describe specLabel $ do
|
|||
generateJSSpec :: TestNames -> (AjaxReq -> String) -> Spec
|
||||
generateJSSpec n gen = describe specLabel $ do
|
||||
it "should generate valid javascript" $ do
|
||||
let s = jsForAPI (Proxy :: Proxy TestAPI) (concat . map gen)
|
||||
let s = jsForAPI (Proxy :: Proxy TestAPI) (concatMap gen)
|
||||
parseFromString s `shouldSatisfy` isRight
|
||||
|
||||
it "should use non-empty function names" $ do
|
||||
|
@ -167,7 +167,7 @@ generateJSSpec n gen = describe specLabel $ do
|
|||
jsText `shouldContain` (header n "X-WhatsForDinner" $ "\"I would like \" + headerXWhatsForDinner + \" with a cherry on top.\"")
|
||||
|
||||
it "can generate the whole javascript code string at once with jsForAPI" $ do
|
||||
let jsStr = jsForAPI (Proxy :: Proxy TestAPI) (concat . map gen)
|
||||
let jsStr = jsForAPI (Proxy :: Proxy TestAPI) (concatMap gen)
|
||||
parseFromString jsStr `shouldSatisfy` isRight
|
||||
where
|
||||
specLabel = "generateJS(" ++ (show n) ++ ")"
|
||||
|
|
|
@ -1,7 +1,7 @@
|
|||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
import Data.Aeson
|
||||
import GHC.Generics
|
||||
import Network.Wai.Handler.Warp
|
||||
|
|
|
@ -1,10 +1,10 @@
|
|||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
-- |
|
||||
-- Module : Servant.Mock
|
||||
-- Copyright : 2015 Alp Mestanogullari
|
||||
|
@ -169,7 +169,7 @@ instance HasMock Raw where
|
|||
bdy <- genBody
|
||||
respond $ responseLBS status200 [] bdy
|
||||
|
||||
where genBody = fmap pack $ generate (vector 100 :: Gen [Char])
|
||||
where genBody = pack <$> generate (vector 100 :: Gen [Char])
|
||||
|
||||
mockArbitrary :: (MonadIO m, Arbitrary a) => m a
|
||||
mockArbitrary = liftIO (generate arbitrary)
|
||||
|
|
|
@ -1,9 +1,9 @@
|
|||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE PolyKinds #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
import Data.Aeson
|
||||
import Data.Monoid
|
||||
|
|
|
@ -27,7 +27,7 @@ import Control.Monad.Trans.Either (EitherT)
|
|||
import qualified Data.ByteString as B
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
import qualified Data.Map as M
|
||||
import Data.Maybe (catMaybes, fromMaybe)
|
||||
import Data.Maybe (mapMaybe, fromMaybe)
|
||||
import Data.String (fromString)
|
||||
import Data.String.Conversions (cs, (<>), ConvertibleStrings)
|
||||
import Data.Text (Text)
|
||||
|
@ -137,9 +137,7 @@ processMethodRouter handleA status method headers request = case handleA of
|
|||
Nothing -> failWith UnsupportedMediaType
|
||||
Just (contentT, body) -> succeedWith $ responseLBS status hdrs bdy
|
||||
where
|
||||
bdy = case allowedMethodHead method request of
|
||||
True -> ""
|
||||
False -> body
|
||||
bdy = if allowedMethodHead method request then "" else body
|
||||
hdrs = (hContentType, cs contentT) : (fromMaybe [] headers)
|
||||
|
||||
methodRouter :: (AllCTRender ctypes a)
|
||||
|
@ -512,7 +510,7 @@ instance (KnownSymbol sym, FromText a, HasServer sublayout)
|
|||
-- named "foo" or "foo[]" and call fromText on the
|
||||
-- corresponding values
|
||||
parameters = filter looksLikeParam querytext
|
||||
values = catMaybes $ map (convert . snd) parameters
|
||||
values = mapMaybe (convert . snd) parameters
|
||||
in route (Proxy :: Proxy sublayout) (feedTo subserver values)
|
||||
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
|
||||
looksLikeParam (name, _) = name == paramname || name == (paramname <> "[]")
|
||||
|
@ -625,7 +623,7 @@ instance (KnownSymbol sym, FromText a, HasServer sublayout)
|
|||
-- named "foo" or "foo[]" and call fromText on the
|
||||
-- corresponding values
|
||||
parameters = filter looksLikeParam matrixtext
|
||||
values = catMaybes $ map (convert . snd) parameters
|
||||
values = mapMaybe (convert . snd) parameters
|
||||
route (Proxy :: Proxy sublayout) (feedTo subserver values)
|
||||
_ -> route (Proxy :: Proxy sublayout) (feedTo subserver [])
|
||||
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
|
||||
|
|
|
@ -11,15 +11,16 @@ import Data.Monoid (Monoid, mappend, mempty)
|
|||
import Control.Monad.Trans.Either (EitherT, runEitherT)
|
||||
import qualified Data.ByteString as B
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
import Data.IORef (newIORef, readIORef, writeIORef)
|
||||
import Data.IORef (newIORef, readIORef,
|
||||
writeIORef)
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Data.Monoid ((<>))
|
||||
import Data.String (fromString)
|
||||
import Network.HTTP.Types hiding (Header, ResponseHeaders)
|
||||
import Network.Wai (Application, Request, Response,
|
||||
ResponseReceived,
|
||||
requestBody,
|
||||
responseLBS,
|
||||
import Network.HTTP.Types hiding (Header,
|
||||
ResponseHeaders)
|
||||
import Network.Wai (Application, Request,
|
||||
Response, ResponseReceived,
|
||||
requestBody, responseLBS,
|
||||
strictRequestBody)
|
||||
import Servant.API ((:<|>) (..))
|
||||
import Servant.Server.Internal.ServantErr
|
||||
|
|
|
@ -5,7 +5,7 @@ module Servant.Server.Internal.ServantErr where
|
|||
import qualified Data.ByteString.Char8 as BS
|
||||
import qualified Data.ByteString.Lazy as LBS
|
||||
import qualified Network.HTTP.Types as HTTP
|
||||
import Network.Wai (responseLBS, Response)
|
||||
import Network.Wai (Response, responseLBS)
|
||||
|
||||
data ServantErr = ServantErr { errHTTPCode :: Int
|
||||
, errReasonPhrase :: String
|
||||
|
|
|
@ -7,10 +7,11 @@ module Servant.Utils.StaticFiles (
|
|||
serveDirectory,
|
||||
) where
|
||||
|
||||
import System.FilePath (addTrailingPathSeparator)
|
||||
import Network.Wai.Application.Static (staticApp, defaultFileServerSettings)
|
||||
import Network.Wai.Application.Static (defaultFileServerSettings,
|
||||
staticApp)
|
||||
import Servant.API.Raw (Raw)
|
||||
import Servant.Server (Server)
|
||||
import System.FilePath (addTrailingPathSeparator)
|
||||
#if !MIN_VERSION_wai_app_static(3,1,0)
|
||||
import Filesystem.Path.CurrentOS (decodeString)
|
||||
#endif
|
||||
|
|
|
@ -8,10 +8,12 @@ module Servant.Utils.StaticFilesSpec where
|
|||
import Control.Exception (bracket)
|
||||
import Data.Proxy (Proxy (Proxy))
|
||||
import Network.Wai (Application)
|
||||
import System.Directory (getCurrentDirectory, setCurrentDirectory, createDirectory)
|
||||
import System.Directory (createDirectory,
|
||||
getCurrentDirectory,
|
||||
setCurrentDirectory)
|
||||
import System.IO.Temp (withSystemTempDirectory)
|
||||
import Test.Hspec (Spec, describe, it, around_)
|
||||
import Test.Hspec.Wai (with, get, shouldRespondWith)
|
||||
import Test.Hspec (Spec, around_, describe, it)
|
||||
import Test.Hspec.Wai (get, shouldRespondWith, with)
|
||||
|
||||
import Servant.API (JSON)
|
||||
import Servant.API.Alternative ((:<|>) ((:<|>)))
|
||||
|
|
|
@ -1,24 +0,0 @@
|
|||
{ mkDerivation, aeson, attoparsec, base, bytestring
|
||||
, bytestring-conversion, case-insensitive, directory, doctest
|
||||
, filemanip, filepath, hspec, http-media, http-types, network-uri
|
||||
, parsec, QuickCheck, quickcheck-instances, stdenv
|
||||
, string-conversions, text, url, vault
|
||||
}:
|
||||
mkDerivation {
|
||||
pname = "servant";
|
||||
version = "0.5";
|
||||
src = ./.;
|
||||
buildDepends = [
|
||||
aeson attoparsec base bytestring bytestring-conversion
|
||||
case-insensitive http-media http-types network-uri
|
||||
string-conversions text vault
|
||||
];
|
||||
testDepends = [
|
||||
aeson attoparsec base bytestring directory doctest filemanip
|
||||
filepath hspec parsec QuickCheck quickcheck-instances
|
||||
string-conversions text url
|
||||
];
|
||||
homepage = "http://haskell-servant.github.io/";
|
||||
description = "A family of combinators for defining webservices APIs";
|
||||
license = stdenv.lib.licenses.bsd3;
|
||||
}
|
|
@ -12,13 +12,13 @@ import Data.Monoid
|
|||
#endif
|
||||
import Control.Arrow
|
||||
import Data.Aeson
|
||||
import Data.Either
|
||||
import Data.Function (on)
|
||||
import Data.Proxy
|
||||
import Data.ByteString.Char8 (ByteString, append, pack)
|
||||
import qualified Data.ByteString.Lazy as BSL
|
||||
import Data.Either
|
||||
import Data.Function (on)
|
||||
import Data.List (maximumBy)
|
||||
import Data.Maybe (fromJust, isJust, isNothing)
|
||||
import Data.Proxy
|
||||
import Data.String (IsString (..))
|
||||
import Data.String.Conversions (cs)
|
||||
import qualified Data.Text as TextS
|
||||
|
@ -57,15 +57,15 @@ spec = describe "Servant.API.ContentTypes" $ do
|
|||
let p = Proxy :: Proxy FormUrlEncoded
|
||||
|
||||
it "has mimeUnrender reverse mimeRender" $ do
|
||||
property $ \x -> all (/= mempty) x
|
||||
property $ \x -> mempty `notElem` x
|
||||
==> mimeUnrender p (mimeRender p x) == Right (x::[(TextS.Text,TextS.Text)])
|
||||
|
||||
it "has mimeUnrender reverse exportParams (Network.URL)" $ do
|
||||
property $ \x -> all (/= mempty) x
|
||||
property $ \x -> mempty `notElem` x
|
||||
==> (mimeUnrender p . cs . exportParams . map (cs *** cs) $ x) == Right (x::[(TextS.Text,TextS.Text)])
|
||||
|
||||
it "has importParams (Network.URL) reverse mimeRender" $ do
|
||||
property $ \x -> all (/= mempty) x
|
||||
property $ \x -> mempty `notElem` x
|
||||
==> (fmap (map (cs *** cs)) . importParams . cs . mimeRender p $ x) == Just (x::[(TextS.Text,TextS.Text)])
|
||||
|
||||
describe "The PlainText Content-Type type" $ do
|
||||
|
|
Loading…
Reference in a new issue