ReqBody content types.

And general cleanup.
This commit is contained in:
Julian K. Arni 2015-01-13 20:38:34 +01:00
parent 98e02ea7cf
commit a1e1de91a9
8 changed files with 34 additions and 15 deletions

View File

@ -47,13 +47,26 @@ library
base >=4.7 && <5
, bytestring == 0.10.*
, http-types == 0.8.*
, text >= 1
, template-haskell
, text >= 1 && < 2
, template-haskell >= 2.7 && < 2.10
, parsec >= 3.1
, string-conversions >= 0.3
, string-conversions >= 0.3 && < 0.4
, network-uri >= 2.6
hs-source-dirs: src
default-language: Haskell2010
extensions: DataKinds
, DeriveDataTypeable
, FunctionalDependencies
, KindSignatures
, MultiParamTypeClasses
, PolyKinds
, QuasiQuotes
, ScopedTypeVariables
, TemplateHaskell
, TypeFamilies
, TypeOperators
, UndecidableInstances
, FlexibleInstances
ghc-options: -Wall
test-suite spec

View File

@ -46,7 +46,8 @@ module Servant.API (
import Servant.API.Alternative ( (:<|>)(..) )
import Servant.API.Capture ( Capture )
import Servant.API.ContentTypes ( HTML, XML, JSON, JavaScript, CSS, PlainText )
import Servant.API.ContentTypes ( HTML, XML, JSON, JavaScript, CSS
, PlainText, OctetStream )
import Servant.API.Delete ( Delete )
import Servant.API.Get ( Get )
import Servant.API.Header ( Header )

View File

@ -10,3 +10,4 @@ data JSON deriving Typeable
data JavaScript deriving Typeable
data CSS deriving Typeable
data PlainText deriving Typeable
data OctetStream deriving Typeable

View File

@ -1,5 +1,7 @@
{-# LANGUAGE DeriveDataTypeable #-}
module Servant.API.Raw where
import Data.Typeable (Typeable)
-- | Endpoint for plugging in your own Wai 'Application's.
--
-- The given 'Application' will get the request as received by the server, potentially with
@ -9,4 +11,4 @@ module Servant.API.Raw where
-- this can also be used with 'Servant.Utils.StaticFiles.serveDirectory' to serve
-- static files stored in a particular directory on your filesystem, or to serve
-- your API's documentation with 'Servant.Utils.StaticFiles.serveDocumentation'.
data Raw
data Raw deriving Typeable

View File

@ -1,3 +1,4 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
module Servant.API.ReqBody where
@ -6,5 +7,5 @@ module Servant.API.ReqBody where
-- Example:
--
-- > -- POST /books
-- > type MyApi = "books" :> ReqBody Book :> Post Book
data ReqBody a
-- > type MyApi = "books" :> ReqBody '[JSON] Book :> Post Book
data ReqBody (ls::[*]) a

View File

@ -1,7 +1,7 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fno-warn-unused-do-bind #-}

View File

@ -2,10 +2,11 @@
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UndecidableInstances #-}
-- | Type safe generation of internal links.
@ -155,7 +156,8 @@ type family IsElem endpoint api :: Constraint where
IsElem e (sa :<|> sb) = Or (IsElem e sa) (IsElem e sb)
IsElem (e :> sa) (e :> sb) = IsElem sa sb
IsElem sa (Header x :> sb) = IsElem sa sb
IsElem sa (ReqBody x :> sb) = IsElem sa sb
IsElem sa (ReqBody y x :> sb) = IsElem sa sb
IsElem (e :> sa) (Capture x y :> sb) = IsElem sa sb
IsElem sa (QueryParam x y :> sb) = IsElem sa sb
IsElem sa (QueryParams x y :> sb) = IsElem sa sb
IsElem sa (QueryFlag x :> sb) = IsElem sa sb

View File

@ -12,7 +12,6 @@ import Servant.API ( type (:<|>), ReqBody, QueryParam, MatrixParam, MatrixParams
, MatrixFlag, Get, Post, Capture, type (:>) , HTML , JSON, XML )
import Servant.QQSpec ( (~>) )
import Servant.Utils.Links ( IsElem, IsLink )
<<<<<<< HEAD
type TestApi =
-- Capture and query/matrix params
@ -28,7 +27,7 @@ type TestApi =
-- All of the verbs
:<|> "get" :> Get '[JSON] ()
:<|> "put" :> Put '[JSON] ()
:<|> "post" :> ReqBody 'True :> Post '[JSON] ()
:<|> "post" :> ReqBody '[JSON] 'True :> Post '[JSON] ()
:<|> "delete" :> Header "ponies" :> Delete
:<|> "raw" :> Raw
@ -44,7 +43,7 @@ type BadTestLink' = "hello" :> "hi" :> Get '[HTML] Bool
type BadTestLink'2 = "greet" :> Get '[HTML] Bool
type NotALink = "hello" :> Capture "x" Bool :> Get '[JSON] Bool
type NotALink2 = "hello" :> ReqBody 'True :> Get '[JSON] Bool
type NotALink2 = "hello" :> ReqBody '[JSON] 'True :> Get '[JSON] Bool
apiLink :: (IsElem endpoint TestApi, HasLink endpoint)
=> Proxy endpoint -> MkLink endpoint