Contributing
This commit is contained in:
parent
1a27e46f5c
commit
98b6e85128
12 changed files with 180 additions and 84 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)
|
![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`, 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-server`, which lets you *implement* an HTTP server with handlers for
|
||||||
- `servant-client`, which lets you derive automatically Haskell functions that let you query each endpoint of a `servant` webservice.
|
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-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-js`, which lets you derive Javascript functions (using vanilla JS
|
||||||
- `servant-blaze` and `servant-lucid` provide easy HTML rendering of your data as an `HTML` content-type "combinator".
|
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
|
## 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!
|
||||||
|
|
|
@ -99,7 +99,7 @@ setRQBody b t req = req { reqBody = Just (b, t) }
|
||||||
|
|
||||||
reqToRequest :: (Functor m, MonadThrow m) => Req -> BaseUrl -> m Request
|
reqToRequest :: (Functor m, MonadThrow m) => Req -> BaseUrl -> m Request
|
||||||
reqToRequest req (BaseUrl reqScheme reqHost reqPort) =
|
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
|
where url = show $ nullURI { uriScheme = case reqScheme of
|
||||||
Http -> "http:"
|
Http -> "http:"
|
||||||
|
|
|
@ -141,8 +141,8 @@ toValidFunctionName (x:xs) = [setFirstChar x] <> filter remainder xs
|
||||||
setFirstChar c = if firstChar c
|
setFirstChar c = if firstChar c
|
||||||
then c
|
then c
|
||||||
else '_'
|
else '_'
|
||||||
firstChar c = (prefixOK c) || (or . map (Set.member c) $ firstLetterOK)
|
firstChar c = prefixOK c || any (Set.member c) firstLetterOK
|
||||||
remainder c = (prefixOK c) || (or . map (Set.member c) $ remainderOK)
|
remainder c = prefixOK c || any (Set.member c) remainderOK
|
||||||
-- Valid prefixes
|
-- Valid prefixes
|
||||||
prefixOK c = c `elem` ['$','_']
|
prefixOK c = c `elem` ['$','_']
|
||||||
-- Unicode character sets
|
-- Unicode character sets
|
||||||
|
|
|
@ -9,12 +9,12 @@ import Data.Monoid
|
||||||
-- to make the AJAX calls. Uses 'defCommonGeneratorOptions'
|
-- to make the AJAX calls. Uses 'defCommonGeneratorOptions'
|
||||||
-- for the generator options.
|
-- for the generator options.
|
||||||
jquery :: JavaScriptGenerator
|
jquery :: JavaScriptGenerator
|
||||||
jquery = concat . map generateJQueryJS
|
jquery = concatMap generateJQueryJS
|
||||||
|
|
||||||
-- | Generate javascript functions that use the /jQuery/ library
|
-- | Generate javascript functions that use the /jQuery/ library
|
||||||
-- to make the AJAX calls. Lets you specify your own 'CommonGeneratorOptions'.
|
-- to make the AJAX calls. Lets you specify your own 'CommonGeneratorOptions'.
|
||||||
jqueryWith :: CommonGeneratorOptions -> JavaScriptGenerator
|
jqueryWith :: CommonGeneratorOptions -> JavaScriptGenerator
|
||||||
jqueryWith opts = concat . map (generateJQueryJSWith opts)
|
jqueryWith opts = concatMap (generateJQueryJSWith opts)
|
||||||
|
|
||||||
-- | js codegen using JQuery using default options
|
-- | js codegen using JQuery using default options
|
||||||
generateJQueryJS :: AjaxReq -> String
|
generateJQueryJS :: AjaxReq -> String
|
||||||
|
|
|
@ -9,13 +9,13 @@ import Data.Monoid
|
||||||
-- to your API, using /XMLHttpRequest/. Uses 'defCommonGeneratorOptions'
|
-- to your API, using /XMLHttpRequest/. Uses 'defCommonGeneratorOptions'
|
||||||
-- for the 'CommonGeneratorOptions'.
|
-- for the 'CommonGeneratorOptions'.
|
||||||
vanillaJS :: JavaScriptGenerator
|
vanillaJS :: JavaScriptGenerator
|
||||||
vanillaJS = concat . map generateVanillaJS
|
vanillaJS = concatMap generateVanillaJS
|
||||||
|
|
||||||
-- | Generate vanilla javascript functions to make AJAX requests
|
-- | Generate vanilla javascript functions to make AJAX requests
|
||||||
-- to your API, using /XMLHttpRequest/. Lets you specify your
|
-- to your API, using /XMLHttpRequest/. Lets you specify your
|
||||||
-- own options.
|
-- own options.
|
||||||
vanillaJSWith :: CommonGeneratorOptions -> JavaScriptGenerator
|
vanillaJSWith :: CommonGeneratorOptions -> JavaScriptGenerator
|
||||||
vanillaJSWith opts = concat . map (generateVanillaJSWith opts)
|
vanillaJSWith opts = concatMap (generateVanillaJSWith opts)
|
||||||
|
|
||||||
-- | js codegen using XmlHttpRequest using default generation options
|
-- | js codegen using XmlHttpRequest using default generation options
|
||||||
generateVanillaJS :: AjaxReq -> String
|
generateVanillaJS :: AjaxReq -> String
|
||||||
|
|
|
@ -102,7 +102,7 @@ axiosSpec = describe specLabel $ do
|
||||||
cookieOpts = AX.defAxiosOptions { AX.xsrfCookieName = Just "MyXSRFcookie" }
|
cookieOpts = AX.defAxiosOptions { AX.xsrfCookieName = Just "MyXSRFcookie" }
|
||||||
headerOpts = AX.defAxiosOptions { AX.xsrfHeaderName = Just "MyXSRFheader" }
|
headerOpts = AX.defAxiosOptions { AX.xsrfHeaderName = Just "MyXSRFheader" }
|
||||||
genJS :: AxiosOptions -> [AjaxReq] -> String
|
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 :: TestNames -> Spec
|
||||||
angularSpec test = describe specLabel $ do
|
angularSpec test = describe specLabel $ do
|
||||||
|
@ -130,7 +130,7 @@ angularSpec test = describe specLabel $ do
|
||||||
generateJSSpec :: TestNames -> (AjaxReq -> String) -> Spec
|
generateJSSpec :: TestNames -> (AjaxReq -> String) -> Spec
|
||||||
generateJSSpec n gen = describe specLabel $ do
|
generateJSSpec n gen = describe specLabel $ do
|
||||||
it "should generate valid javascript" $ 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
|
parseFromString s `shouldSatisfy` isRight
|
||||||
|
|
||||||
it "should use non-empty function names" $ do
|
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.\"")
|
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
|
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
|
parseFromString jsStr `shouldSatisfy` isRight
|
||||||
where
|
where
|
||||||
specLabel = "generateJS(" ++ (show n) ++ ")"
|
specLabel = "generateJS(" ++ (show n) ++ ")"
|
||||||
|
|
|
@ -1,10 +1,10 @@
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
{-# LANGUAGE DataKinds #-}
|
{-# LANGUAGE DataKinds #-}
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
{-# LANGUAGE TypeOperators #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
|
{-# LANGUAGE TypeOperators #-}
|
||||||
-- |
|
-- |
|
||||||
-- Module : Servant.Mock
|
-- Module : Servant.Mock
|
||||||
-- Copyright : 2015 Alp Mestanogullari
|
-- Copyright : 2015 Alp Mestanogullari
|
||||||
|
@ -51,18 +51,18 @@
|
||||||
module Servant.Mock ( HasMock(..) ) where
|
module Servant.Mock ( HasMock(..) ) where
|
||||||
|
|
||||||
#if !MIN_VERSION_base(4,8,0)
|
#if !MIN_VERSION_base(4,8,0)
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
#endif
|
#endif
|
||||||
import Control.Monad.IO.Class
|
import Control.Monad.IO.Class
|
||||||
import Data.ByteString.Lazy.Char8 (pack)
|
import Data.ByteString.Lazy.Char8 (pack)
|
||||||
import Data.Proxy
|
import Data.Proxy
|
||||||
import GHC.TypeLits
|
import GHC.TypeLits
|
||||||
import Network.HTTP.Types.Status
|
import Network.HTTP.Types.Status
|
||||||
import Network.Wai
|
import Network.Wai
|
||||||
import Servant
|
import Servant
|
||||||
import Servant.API.ContentTypes
|
import Servant.API.ContentTypes
|
||||||
import Test.QuickCheck.Arbitrary (Arbitrary(..), vector)
|
import Test.QuickCheck.Arbitrary (Arbitrary (..), vector)
|
||||||
import Test.QuickCheck.Gen (Gen, generate)
|
import Test.QuickCheck.Gen (Gen, generate)
|
||||||
|
|
||||||
-- | 'HasMock' defines an interpretation of API types
|
-- | 'HasMock' defines an interpretation of API types
|
||||||
-- than turns them into random-response-generating
|
-- than turns them into random-response-generating
|
||||||
|
@ -169,7 +169,7 @@ instance HasMock Raw where
|
||||||
bdy <- genBody
|
bdy <- genBody
|
||||||
respond $ responseLBS status200 [] bdy
|
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 :: (MonadIO m, Arbitrary a) => m a
|
||||||
mockArbitrary = liftIO (generate arbitrary)
|
mockArbitrary = liftIO (generate arbitrary)
|
||||||
|
|
|
@ -137,9 +137,7 @@ processMethodRouter handleA status method headers request = case handleA of
|
||||||
Nothing -> failWith UnsupportedMediaType
|
Nothing -> failWith UnsupportedMediaType
|
||||||
Just (contentT, body) -> succeedWith $ responseLBS status hdrs bdy
|
Just (contentT, body) -> succeedWith $ responseLBS status hdrs bdy
|
||||||
where
|
where
|
||||||
bdy = case allowedMethodHead method request of
|
bdy = if allowedMethodHead method request then "" else body
|
||||||
True -> ""
|
|
||||||
False -> body
|
|
||||||
hdrs = (hContentType, cs contentT) : (fromMaybe [] headers)
|
hdrs = (hContentType, cs contentT) : (fromMaybe [] headers)
|
||||||
|
|
||||||
methodRouter :: (AllCTRender ctypes a)
|
methodRouter :: (AllCTRender ctypes a)
|
||||||
|
@ -512,7 +510,7 @@ instance (KnownSymbol sym, FromText a, HasServer sublayout)
|
||||||
-- named "foo" or "foo[]" and call fromText on the
|
-- named "foo" or "foo[]" and call fromText on the
|
||||||
-- corresponding values
|
-- corresponding values
|
||||||
parameters = filter looksLikeParam querytext
|
parameters = filter looksLikeParam querytext
|
||||||
values = catMaybes $ map (convert . snd) parameters
|
values = mapMaybe (convert . snd) parameters
|
||||||
in route (Proxy :: Proxy sublayout) (feedTo subserver values)
|
in route (Proxy :: Proxy sublayout) (feedTo subserver values)
|
||||||
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
|
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
|
||||||
looksLikeParam (name, _) = name == paramname || name == (paramname <> "[]")
|
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
|
-- named "foo" or "foo[]" and call fromText on the
|
||||||
-- corresponding values
|
-- corresponding values
|
||||||
parameters = filter looksLikeParam matrixtext
|
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 values)
|
||||||
_ -> route (Proxy :: Proxy sublayout) (feedTo subserver [])
|
_ -> route (Proxy :: Proxy sublayout) (feedTo subserver [])
|
||||||
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
|
where paramname = cs $ symbolVal (Proxy :: Proxy sym)
|
||||||
|
|
|
@ -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;
|
|
||||||
}
|
|
|
@ -57,15 +57,15 @@ spec = describe "Servant.API.ContentTypes" $ do
|
||||||
let p = Proxy :: Proxy FormUrlEncoded
|
let p = Proxy :: Proxy FormUrlEncoded
|
||||||
|
|
||||||
it "has mimeUnrender reverse mimeRender" $ do
|
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)])
|
==> mimeUnrender p (mimeRender p x) == Right (x::[(TextS.Text,TextS.Text)])
|
||||||
|
|
||||||
it "has mimeUnrender reverse exportParams (Network.URL)" $ do
|
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)])
|
==> (mimeUnrender p . cs . exportParams . map (cs *** cs) $ x) == Right (x::[(TextS.Text,TextS.Text)])
|
||||||
|
|
||||||
it "has importParams (Network.URL) reverse mimeRender" $ do
|
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)])
|
==> (fmap (map (cs *** cs)) . importParams . cs . mimeRender p $ x) == Just (x::[(TextS.Text,TextS.Text)])
|
||||||
|
|
||||||
describe "The PlainText Content-Type type" $ do
|
describe "The PlainText Content-Type type" $ do
|
||||||
|
|
Loading…
Reference in a new issue