Added lang parameter.

This commit is contained in:
Maksymilian Owsianny 2015-11-29 04:53:50 +00:00
parent 0b37222733
commit 69f09f2622
3 changed files with 94 additions and 85 deletions

View file

@ -122,144 +122,148 @@ type family Elem (a :: *) (ls::[*]) :: Constraint where
Elem a (a ': list) = () Elem a (a ': list) = ()
Elem a (b ': list) = Elem a list Elem a (b ': list) = Elem a list
class HasForeignType a where class HasForeignType lang a where
typeFor :: Proxy a -> ForeignType typeFor :: Proxy lang -> Proxy a -> ForeignType
class HasForeign (layout :: *) where class HasForeign lang (layout :: *) where
type Foreign layout :: * type Foreign layout :: *
foreignFor :: Proxy layout -> Req -> Foreign layout foreignFor :: Proxy lang -> Proxy layout -> Req -> Foreign layout
instance (HasForeign a, HasForeign b) instance (HasForeign lang a, HasForeign lang b)
=> HasForeign (a :<|> b) where => HasForeign lang (a :<|> b) where
type Foreign (a :<|> b) = Foreign a :<|> Foreign b type Foreign (a :<|> b) = Foreign a :<|> Foreign b
foreignFor Proxy req = foreignFor lang Proxy req =
foreignFor (Proxy :: Proxy a) req foreignFor lang (Proxy :: Proxy a) req
:<|> foreignFor (Proxy :: Proxy b) req :<|> foreignFor lang (Proxy :: Proxy b) req
instance (KnownSymbol sym, HasForeignType a, HasForeign sublayout) instance (KnownSymbol sym, HasForeignType lang a, HasForeign lang sublayout)
=> HasForeign (Capture sym a :> sublayout) where => HasForeign lang (Capture sym a :> sublayout) where
type Foreign (Capture sym a :> sublayout) = Foreign sublayout type Foreign (Capture sym a :> sublayout) = Foreign sublayout
foreignFor Proxy req = foreignFor lang Proxy req =
foreignFor (Proxy :: Proxy sublayout) $ foreignFor lang (Proxy :: Proxy sublayout) $
req & reqUrl.path <>~ [Segment (Cap arg)] req & reqUrl.path <>~ [Segment (Cap arg)]
& funcName %~ (++ ["by", str]) & funcName %~ (++ ["by", str])
where where
str = pack . symbolVal $ (Proxy :: Proxy sym) str = pack . symbolVal $ (Proxy :: Proxy sym)
arg = (str, typeFor (Proxy :: Proxy a)) arg = (str, typeFor lang (Proxy :: Proxy a))
instance (Elem JSON list, HasForeignType a) => HasForeign (Delete list a) where instance (Elem JSON list, HasForeignType lang a)
=> HasForeign lang (Delete list a) where
type Foreign (Delete list a) = Req type Foreign (Delete list a) = Req
foreignFor Proxy req = foreignFor lang Proxy req =
req & funcName %~ ("delete" :) req & funcName %~ ("delete" :)
& reqMethod .~ "DELETE" & reqMethod .~ "DELETE"
& reqReturnType .~ retType & reqReturnType .~ retType
where where
retType = typeFor (Proxy :: Proxy a) retType = typeFor lang (Proxy :: Proxy a)
instance (Elem JSON list, HasForeignType a) => HasForeign (Get list a) where instance (Elem JSON list, HasForeignType lang a)
=> HasForeign lang (Get list a) where
type Foreign (Get list a) = Req type Foreign (Get list a) = Req
foreignFor Proxy req = foreignFor lang Proxy req =
req & funcName %~ ("get" :) req & funcName %~ ("get" :)
& reqMethod .~ "GET" & reqMethod .~ "GET"
& reqReturnType .~ retType & reqReturnType .~ retType
where where
retType = typeFor (Proxy :: Proxy a) retType = typeFor lang (Proxy :: Proxy a)
instance (KnownSymbol sym, HasForeignType a, HasForeign sublayout) instance (KnownSymbol sym, HasForeignType lang a, HasForeign lang sublayout)
=> HasForeign (Header sym a :> sublayout) where => HasForeign lang (Header sym a :> sublayout) where
type Foreign (Header sym a :> sublayout) = Foreign sublayout type Foreign (Header sym a :> sublayout) = Foreign sublayout
foreignFor Proxy req = foreignFor lang Proxy req =
foreignFor subP $ req foreignFor lang subP $ req
& reqHeaders <>~ [HeaderArg arg] & reqHeaders <>~ [HeaderArg arg]
where where
hname = pack . symbolVal $ (Proxy :: Proxy sym) hname = pack . symbolVal $ (Proxy :: Proxy sym)
arg = (hname, typeFor (Proxy :: Proxy a)) arg = (hname, typeFor lang (Proxy :: Proxy a))
subP = Proxy :: Proxy sublayout subP = Proxy :: Proxy sublayout
instance (Elem JSON list, HasForeignType a) => HasForeign (Post list a) where instance (Elem JSON list, HasForeignType lang a)
=> HasForeign lang (Post list a) where
type Foreign (Post list a) = Req type Foreign (Post list a) = Req
foreignFor Proxy req = foreignFor lang Proxy req =
req & funcName %~ ("post" :) req & funcName %~ ("post" :)
& reqMethod .~ "POST" & reqMethod .~ "POST"
& reqReturnType .~ retType & reqReturnType .~ retType
where where
retType = typeFor (Proxy :: Proxy a) retType = typeFor lang (Proxy :: Proxy a)
instance (Elem JSON list, HasForeignType a) => HasForeign (Put list a) where instance (Elem JSON list, HasForeignType lang a)
=> HasForeign lang (Put list a) where
type Foreign (Put list a) = Req type Foreign (Put list a) = Req
foreignFor Proxy req = foreignFor lang Proxy req =
req & funcName %~ ("put" :) req & funcName %~ ("put" :)
& reqMethod .~ "PUT" & reqMethod .~ "PUT"
& reqReturnType .~ retType & reqReturnType .~ retType
where where
retType = typeFor (Proxy :: Proxy a) retType = typeFor lang (Proxy :: Proxy a)
instance (KnownSymbol sym, HasForeignType a, HasForeign sublayout) instance (KnownSymbol sym, HasForeignType lang a, HasForeign lang sublayout)
=> HasForeign (QueryParam sym a :> sublayout) where => HasForeign lang (QueryParam sym a :> sublayout) where
type Foreign (QueryParam sym a :> sublayout) = Foreign sublayout type Foreign (QueryParam sym a :> sublayout) = Foreign sublayout
foreignFor Proxy req = foreignFor lang Proxy req =
foreignFor (Proxy :: Proxy sublayout) $ foreignFor lang (Proxy :: Proxy sublayout) $
req & reqUrl.queryStr <>~ [QueryArg arg Normal] req & reqUrl.queryStr <>~ [QueryArg arg Normal]
where where
str = pack . symbolVal $ (Proxy :: Proxy sym) str = pack . symbolVal $ (Proxy :: Proxy sym)
arg = (str, typeFor (Proxy :: Proxy a)) arg = (str, typeFor lang (Proxy :: Proxy a))
instance (KnownSymbol sym, HasForeignType a, HasForeign sublayout) instance (KnownSymbol sym, HasForeignType lang a, HasForeign lang sublayout)
=> HasForeign (QueryParams sym a :> sublayout) where => HasForeign lang (QueryParams sym a :> sublayout) where
type Foreign (QueryParams sym a :> sublayout) = Foreign sublayout type Foreign (QueryParams sym a :> sublayout) = Foreign sublayout
foreignFor Proxy req = foreignFor lang Proxy req =
foreignFor (Proxy :: Proxy sublayout) $ foreignFor lang (Proxy :: Proxy sublayout) $
req & reqUrl.queryStr <>~ [QueryArg arg List] req & reqUrl.queryStr <>~ [QueryArg arg List]
where where
str = pack . symbolVal $ (Proxy :: Proxy sym) str = pack . symbolVal $ (Proxy :: Proxy sym)
arg = (str, typeFor (Proxy :: Proxy a)) arg = (str, typeFor lang (Proxy :: Proxy a))
instance (KnownSymbol sym, HasForeignType a, a ~ Bool, HasForeign sublayout) instance (KnownSymbol sym, HasForeignType lang a, a ~ Bool, HasForeign lang sublayout)
=> HasForeign (QueryFlag sym :> sublayout) where => HasForeign lang (QueryFlag sym :> sublayout) where
type Foreign (QueryFlag sym :> sublayout) = Foreign sublayout type Foreign (QueryFlag sym :> sublayout) = Foreign sublayout
foreignFor Proxy req = foreignFor lang Proxy req =
foreignFor (Proxy :: Proxy sublayout) $ foreignFor lang (Proxy :: Proxy sublayout) $
req & reqUrl.queryStr <>~ [QueryArg arg Flag] req & reqUrl.queryStr <>~ [QueryArg arg Flag]
where where
str = pack . symbolVal $ (Proxy :: Proxy sym) str = pack . symbolVal $ (Proxy :: Proxy sym)
arg = (str, typeFor (Proxy :: Proxy a)) arg = (str, typeFor lang (Proxy :: Proxy a))
instance HasForeign Raw where instance HasForeign lang Raw where
type Foreign Raw = Method -> Req type Foreign Raw = Method -> Req
foreignFor Proxy req method = foreignFor _ Proxy req method =
req & funcName %~ ((toLower method) :) req & funcName %~ ((toLower method) :)
& reqMethod .~ method & reqMethod .~ method
instance (Elem JSON list, HasForeignType a, HasForeign sublayout) instance (Elem JSON list, HasForeignType lang a, HasForeign lang sublayout)
=> HasForeign (ReqBody list a :> sublayout) where => HasForeign lang (ReqBody list a :> sublayout) where
type Foreign (ReqBody list a :> sublayout) = Foreign sublayout type Foreign (ReqBody list a :> sublayout) = Foreign sublayout
foreignFor Proxy req = foreignFor lang Proxy req =
foreignFor (Proxy :: Proxy sublayout) $ foreignFor lang (Proxy :: Proxy sublayout) $
req & reqBody .~ (Just $ typeFor (Proxy :: Proxy a)) req & reqBody .~ (Just $ typeFor lang (Proxy :: Proxy a))
instance (KnownSymbol path, HasForeign sublayout) instance (KnownSymbol path, HasForeign lang sublayout)
=> HasForeign (path :> sublayout) where => HasForeign lang (path :> sublayout) where
type Foreign (path :> sublayout) = Foreign sublayout type Foreign (path :> sublayout) = Foreign sublayout
foreignFor Proxy req = foreignFor lang Proxy req =
foreignFor (Proxy :: Proxy sublayout) $ foreignFor lang (Proxy :: Proxy sublayout) $
req & reqUrl.path <>~ [Segment (Static str)] req & reqUrl.path <>~ [Segment (Static str)]
& funcName %~ (++ [str]) & funcName %~ (++ [str])
@ -267,26 +271,26 @@ instance (KnownSymbol path, HasForeign sublayout)
str = Data.Text.map (\c -> if c == '.' then '_' else c) str = Data.Text.map (\c -> if c == '.' then '_' else c)
. pack . symbolVal $ (Proxy :: Proxy path) . pack . symbolVal $ (Proxy :: Proxy path)
instance HasForeign sublayout => HasForeign (RemoteHost :> sublayout) where instance HasForeign lang sublayout => HasForeign lang (RemoteHost :> sublayout) where
type Foreign (RemoteHost :> sublayout) = Foreign sublayout type Foreign (RemoteHost :> sublayout) = Foreign sublayout
foreignFor Proxy req = foreignFor lang Proxy req =
foreignFor (Proxy :: Proxy sublayout) req foreignFor lang (Proxy :: Proxy sublayout) req
instance HasForeign sublayout => HasForeign (IsSecure :> sublayout) where instance HasForeign lang sublayout => HasForeign lang (IsSecure :> sublayout) where
type Foreign (IsSecure :> sublayout) = Foreign sublayout type Foreign (IsSecure :> sublayout) = Foreign sublayout
foreignFor Proxy req = foreignFor lang Proxy req =
foreignFor (Proxy :: Proxy sublayout) req foreignFor lang (Proxy :: Proxy sublayout) req
instance HasForeign sublayout => HasForeign (Vault :> sublayout) where instance HasForeign lang sublayout => HasForeign lang (Vault :> sublayout) where
type Foreign (Vault :> sublayout) = Foreign sublayout type Foreign (Vault :> sublayout) = Foreign sublayout
foreignFor Proxy req = foreignFor lang Proxy req =
foreignFor (Proxy :: Proxy sublayout) req foreignFor lang (Proxy :: Proxy sublayout) req
instance HasForeign sublayout => HasForeign (HttpVersion :> sublayout) where instance HasForeign lang sublayout => HasForeign lang (HttpVersion :> sublayout) where
type Foreign (HttpVersion :> sublayout) = Foreign sublayout type Foreign (HttpVersion :> sublayout) = Foreign sublayout
foreignFor Proxy req = foreignFor lang Proxy req =
foreignFor (Proxy :: Proxy sublayout) req foreignFor lang (Proxy :: Proxy sublayout) req

View file

@ -2,6 +2,7 @@
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE MultiParamTypeClasses #-}
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
-- | -- |
-- Module : Servant.JS -- Module : Servant.JS
@ -122,16 +123,19 @@ import Servant.JS.Internal
import Servant.JS.JQuery import Servant.JS.JQuery
import Servant.JS.Vanilla import Servant.JS.Vanilla
-- Dummy type specifying target language
data LangJS
-- | Generate the data necessary to generate javascript code -- | Generate the data necessary to generate javascript code
-- for all the endpoints of an API, as ':<|>'-separated values -- for all the endpoints of an API, as ':<|>'-separated values
-- of type 'AjaxReq'. -- of type 'AjaxReq'.
javascript :: HasForeign layout => Proxy layout -> Foreign layout javascript :: HasForeign LangJS layout => Proxy layout -> Foreign layout
javascript p = foreignFor p defReq javascript p = foreignFor (Proxy :: Proxy LangJS) p defReq
-- | Directly generate all the javascript functions for your API -- | Directly generate all the javascript functions for your API
-- from a 'Proxy' for your API type. You can then write it to -- from a 'Proxy' for your API type. You can then write it to
-- a file or integrate it in a page, for example. -- a file or integrate it in a page, for example.
jsForAPI :: (HasForeign api, GenerateList (Foreign api)) jsForAPI :: (HasForeign LangJS api, GenerateList (Foreign api))
=> Proxy api -- ^ proxy for your API type => Proxy api -- ^ proxy for your API type
-> JavaScriptGenerator -- ^ js code generator to use (angular, vanilla js, jquery, others) -> JavaScriptGenerator -- ^ js code generator to use (angular, vanilla js, jquery, others)
-> Text -- ^ a text that you can embed in your pages or write to a file -> Text -- ^ a text that you can embed in your pages or write to a file
@ -140,7 +144,7 @@ jsForAPI p gen = gen (listFromAPI p)
-- | Directly generate all the javascript functions for your API -- | Directly generate all the javascript functions for your API
-- from a 'Proxy' for your API type using the given generator -- from a 'Proxy' for your API type using the given generator
-- and write the resulting code to a file at the given path. -- and write the resulting code to a file at the given path.
writeJSForAPI :: (HasForeign api, GenerateList (Foreign api)) writeJSForAPI :: (HasForeign LangJS api, GenerateList (Foreign api))
=> Proxy api -- ^ proxy for your API type => Proxy api -- ^ proxy for your API type
-> JavaScriptGenerator -- ^ js code generator to use (angular, vanilla js, jquery, others) -> JavaScriptGenerator -- ^ js code generator to use (angular, vanilla js, jquery, others)
-> FilePath -- ^ path to the file you want to write the resulting javascript code into -> FilePath -- ^ path to the file you want to write the resulting javascript code into
@ -148,8 +152,8 @@ writeJSForAPI :: (HasForeign api, GenerateList (Foreign api))
writeJSForAPI p gen fp = writeFile fp (jsForAPI p gen) writeJSForAPI p gen fp = writeFile fp (jsForAPI p gen)
-- A catch all instance since JavaScript has no types. -- A catch all instance since JavaScript has no types.
instance HasForeignType a where instance HasForeignType LangJS a where
typeFor _ = empty typeFor _ _ = empty
-- | Utility class used by 'jsForAPI' which computes -- | Utility class used by 'jsForAPI' which computes
-- the data needed to generate a function for each endpoint -- the data needed to generate a function for each endpoint
@ -165,6 +169,6 @@ instance (GenerateList start, GenerateList rest) => GenerateList (start :<|> res
-- | Generate the necessary data for JS codegen as a list, each 'AjaxReq' -- | Generate the necessary data for JS codegen as a list, each 'AjaxReq'
-- describing one endpoint from your API type. -- describing one endpoint from your API type.
listFromAPI :: (HasForeign api, GenerateList (Foreign api)) => Proxy api -> [AjaxReq] listFromAPI :: (HasForeign LangJS api, GenerateList (Foreign api)) => Proxy api -> [AjaxReq]
listFromAPI p = generateList (javascript p) listFromAPI p = generateList (javascript p)

View file

@ -6,6 +6,7 @@
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Servant.JSSpec.CustomHeaders where module Servant.JSSpec.CustomHeaders where
@ -21,11 +22,11 @@ import Servant.JS.Internal
-- using -- Basic, Digest, whatever. -- using -- Basic, Digest, whatever.
data Authorization (sym :: Symbol) a data Authorization (sym :: Symbol) a
instance (KnownSymbol sym, HasForeign sublayout) instance (KnownSymbol sym, HasForeign lang sublayout)
=> HasForeign (Authorization sym a :> sublayout) where => HasForeign lang (Authorization sym a :> sublayout) where
type Foreign (Authorization sym a :> sublayout) = Foreign sublayout type Foreign (Authorization sym a :> sublayout) = Foreign sublayout
foreignFor Proxy req = foreignFor (Proxy :: Proxy sublayout) $ foreignFor lang Proxy req = foreignFor lang (Proxy :: Proxy sublayout) $
req & reqHeaders <>~ [ ReplaceHeaderArg ("Authorization", "") $ req & reqHeaders <>~ [ ReplaceHeaderArg ("Authorization", "") $
tokenType (pack . symbolVal $ (Proxy :: Proxy sym)) ] tokenType (pack . symbolVal $ (Proxy :: Proxy sym)) ]
where where
@ -34,11 +35,11 @@ instance (KnownSymbol sym, HasForeign sublayout)
-- | This is a combinator that fetches an X-MyLovelyHorse header. -- | This is a combinator that fetches an X-MyLovelyHorse header.
data MyLovelyHorse a data MyLovelyHorse a
instance (HasForeign sublayout) instance (HasForeign lang sublayout)
=> HasForeign (MyLovelyHorse a :> sublayout) where => HasForeign lang (MyLovelyHorse a :> sublayout) where
type Foreign (MyLovelyHorse a :> sublayout) = Foreign sublayout type Foreign (MyLovelyHorse a :> sublayout) = Foreign sublayout
foreignFor Proxy req = foreignFor (Proxy :: Proxy sublayout) $ foreignFor lang Proxy req = foreignFor lang (Proxy :: Proxy sublayout) $
req & reqHeaders <>~ [ ReplaceHeaderArg ("X-MyLovelyHorse", "") tpl ] req & reqHeaders <>~ [ ReplaceHeaderArg ("X-MyLovelyHorse", "") tpl ]
where where
tpl = "I am good friends with {X-MyLovelyHorse}" tpl = "I am good friends with {X-MyLovelyHorse}"
@ -46,11 +47,11 @@ instance (HasForeign sublayout)
-- | This is a combinator that fetches an X-WhatsForDinner header. -- | This is a combinator that fetches an X-WhatsForDinner header.
data WhatsForDinner a data WhatsForDinner a
instance (HasForeign sublayout) instance (HasForeign lang sublayout)
=> HasForeign (WhatsForDinner a :> sublayout) where => HasForeign lang (WhatsForDinner a :> sublayout) where
type Foreign (WhatsForDinner a :> sublayout) = Foreign sublayout type Foreign (WhatsForDinner a :> sublayout) = Foreign sublayout
foreignFor Proxy req = foreignFor (Proxy :: Proxy sublayout) $ foreignFor lang Proxy req = foreignFor lang (Proxy :: Proxy sublayout) $
req & reqHeaders <>~ [ ReplaceHeaderArg ("X-WhatsForDinner", "") tpl ] req & reqHeaders <>~ [ ReplaceHeaderArg ("X-WhatsForDinner", "") tpl ]
where where
tpl = "I would like {X-WhatsForDinner} with a cherry on top." tpl = "I would like {X-WhatsForDinner} with a cherry on top."