Merge pull request #9 from anchor/content-types
Code changes to support Jkarni/content types.
This commit is contained in:
commit
af8e395664
2 changed files with 26 additions and 19 deletions
|
@ -1,9 +1,12 @@
|
||||||
{-# LANGUAGE DataKinds #-}
|
{-# LANGUAGE DataKinds #-}
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
{-# LANGUAGE TypeOperators #-}
|
{-# LANGUAGE TypeOperators #-}
|
||||||
|
{-# LANGUAGE ConstraintKinds #-}
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
module Servant.JQuery.Internal where
|
module Servant.JQuery.Internal where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
|
@ -15,6 +18,7 @@ import Data.List
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
import Data.Proxy
|
import Data.Proxy
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
|
import GHC.Exts (Constraint)
|
||||||
import GHC.TypeLits
|
import GHC.TypeLits
|
||||||
import Servant.API
|
import Servant.API
|
||||||
|
|
||||||
|
@ -157,7 +161,12 @@ paramToStr qarg notTheEnd =
|
||||||
defReq :: AjaxReq
|
defReq :: AjaxReq
|
||||||
defReq = AjaxReq defUrl "GET" [] False ""
|
defReq = AjaxReq defUrl "GET" [] False ""
|
||||||
|
|
||||||
class HasJQ layout where
|
type family Elem (a :: *) (ls::[*]) :: Constraint where
|
||||||
|
Elem a '[] = 'False ~ 'True
|
||||||
|
Elem a (a ': list) = ()
|
||||||
|
Elem a (b ': list) = Elem a list
|
||||||
|
|
||||||
|
class HasJQ (layout :: *) where
|
||||||
type JQ layout :: *
|
type JQ layout :: *
|
||||||
jqueryFor :: Proxy layout -> AjaxReq -> JQ layout
|
jqueryFor :: Proxy layout -> AjaxReq -> JQ layout
|
||||||
|
|
||||||
|
@ -186,8 +195,8 @@ instance HasJQ Delete where
|
||||||
req & funcName %~ ("delete" <>)
|
req & funcName %~ ("delete" <>)
|
||||||
& reqMethod .~ "DELETE"
|
& reqMethod .~ "DELETE"
|
||||||
|
|
||||||
instance HasJQ (Get a) where
|
instance Elem JSON list => HasJQ (Get list a) where
|
||||||
type JQ (Get a) = AjaxReq
|
type JQ (Get list a) = AjaxReq
|
||||||
|
|
||||||
jqueryFor Proxy req =
|
jqueryFor Proxy req =
|
||||||
req & funcName %~ ("get" <>)
|
req & funcName %~ ("get" <>)
|
||||||
|
@ -203,15 +212,15 @@ instance (KnownSymbol sym, HasJQ sublayout)
|
||||||
where hname = symbolVal (Proxy :: Proxy sym)
|
where hname = symbolVal (Proxy :: Proxy sym)
|
||||||
subP = Proxy :: Proxy sublayout
|
subP = Proxy :: Proxy sublayout
|
||||||
|
|
||||||
instance HasJQ (Post a) where
|
instance Elem JSON list => HasJQ (Post list a) where
|
||||||
type JQ (Post a) = AjaxReq
|
type JQ (Post list a) = AjaxReq
|
||||||
|
|
||||||
jqueryFor Proxy req =
|
jqueryFor Proxy req =
|
||||||
req & funcName %~ ("post" <>)
|
req & funcName %~ ("post" <>)
|
||||||
& reqMethod .~ "POST"
|
& reqMethod .~ "POST"
|
||||||
|
|
||||||
instance HasJQ (Put a) where
|
instance Elem JSON list => HasJQ (Put list a) where
|
||||||
type JQ (Put a) = AjaxReq
|
type JQ (Put list a) = AjaxReq
|
||||||
|
|
||||||
jqueryFor Proxy req =
|
jqueryFor Proxy req =
|
||||||
req & funcName %~ ("put" <>)
|
req & funcName %~ ("put" <>)
|
||||||
|
@ -226,7 +235,6 @@ instance (KnownSymbol sym, HasJQ sublayout)
|
||||||
req & reqUrl.queryStr <>~ [QueryArg str Normal]
|
req & reqUrl.queryStr <>~ [QueryArg str Normal]
|
||||||
|
|
||||||
where str = symbolVal (Proxy :: Proxy sym)
|
where str = symbolVal (Proxy :: Proxy sym)
|
||||||
strArg = str ++ "Value"
|
|
||||||
|
|
||||||
instance (KnownSymbol sym, HasJQ sublayout)
|
instance (KnownSymbol sym, HasJQ sublayout)
|
||||||
=> HasJQ (QueryParams sym a :> sublayout) where
|
=> HasJQ (QueryParams sym a :> sublayout) where
|
||||||
|
@ -255,8 +263,8 @@ instance HasJQ Raw where
|
||||||
req & funcName %~ ((toLower <$> method) <>)
|
req & funcName %~ ((toLower <$> method) <>)
|
||||||
& reqMethod .~ method
|
& reqMethod .~ method
|
||||||
|
|
||||||
instance HasJQ sublayout => HasJQ (ReqBody a :> sublayout) where
|
instance (Elem JSON list, HasJQ sublayout) => HasJQ (ReqBody list a :> sublayout) where
|
||||||
type JQ (ReqBody a :> sublayout) = JQ sublayout
|
type JQ (ReqBody list a :> sublayout) = JQ sublayout
|
||||||
|
|
||||||
jqueryFor Proxy req =
|
jqueryFor Proxy req =
|
||||||
jqueryFor (Proxy :: Proxy sublayout) $
|
jqueryFor (Proxy :: Proxy sublayout) $
|
||||||
|
|
|
@ -13,28 +13,27 @@ import Language.ECMAScript3.Parser (parseFromString)
|
||||||
import Test.Hspec
|
import Test.Hspec
|
||||||
|
|
||||||
import Servant.API
|
import Servant.API
|
||||||
|
import Servant.API.ContentTypes
|
||||||
import Servant.JQuery
|
import Servant.JQuery
|
||||||
import Servant.JQuerySpec.CustomHeaders
|
import Servant.JQuerySpec.CustomHeaders
|
||||||
|
|
||||||
type TestAPI = [sitemap|
|
type TestAPI = "simple" :> ReqBody '[JSON,FormUrlEncoded] String :> Post '[JSON] Bool
|
||||||
POST /simple String -> Bool
|
:<|> "has.extension" :> Get '[FormUrlEncoded,JSON] Bool
|
||||||
GET /has.extension Bool
|
|
||||||
|]
|
|
||||||
|
|
||||||
type TopLevelRawAPI = "something" :> Get Int
|
type TopLevelRawAPI = "something" :> Get '[JSON] Int
|
||||||
:<|> Raw
|
:<|> Raw
|
||||||
|
|
||||||
type HeaderHandlingAPI = "something" :> Header "Foo" String
|
type HeaderHandlingAPI = "something" :> Header "Foo" String
|
||||||
:> Get Int
|
:> Get '[JSON] Int
|
||||||
|
|
||||||
type CustomAuthAPI = "something" :> Authorization "Basic" String
|
type CustomAuthAPI = "something" :> Authorization "Basic" String
|
||||||
:> Get Int
|
:> Get '[JSON] Int
|
||||||
|
|
||||||
type CustomHeaderAPI = "something" :> MyLovelyHorse String
|
type CustomHeaderAPI = "something" :> MyLovelyHorse String
|
||||||
:> Get Int
|
:> Get '[JSON] Int
|
||||||
|
|
||||||
type CustomHeaderAPI2 = "something" :> WhatsForDinner String
|
type CustomHeaderAPI2 = "something" :> WhatsForDinner String
|
||||||
:> Get Int
|
:> Get '[JSON] Int
|
||||||
|
|
||||||
headerHandlingProxy :: Proxy HeaderHandlingAPI
|
headerHandlingProxy :: Proxy HeaderHandlingAPI
|
||||||
headerHandlingProxy = Proxy
|
headerHandlingProxy = Proxy
|
||||||
|
|
Loading…
Reference in a new issue