Replace functionName with an array, and use functionRenamer to build the real function name
This commit is contained in:
parent
2cf2d08cd3
commit
c01ad63112
2 changed files with 36 additions and 12 deletions
|
@ -79,6 +79,11 @@ module Servant.JS
|
||||||
CommonGeneratorOptions(..)
|
CommonGeneratorOptions(..)
|
||||||
, defCommonGeneratorOptions
|
, defCommonGeneratorOptions
|
||||||
|
|
||||||
|
, -- * Function renamers
|
||||||
|
concatRenamer
|
||||||
|
, snakeCaseRenamer
|
||||||
|
, camelCaseRenamer
|
||||||
|
|
||||||
, -- * Vanilla Javascript code generation
|
, -- * Vanilla Javascript code generation
|
||||||
vanillaJS
|
vanillaJS
|
||||||
, vanillaJSWith
|
, vanillaJSWith
|
||||||
|
|
|
@ -14,7 +14,7 @@ module Servant.JS.Internal where
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
#endif
|
#endif
|
||||||
import Control.Lens
|
import Control.Lens
|
||||||
import Data.Char (toLower)
|
import Data.Char (toLower, toUpper)
|
||||||
import qualified Data.CharSet as Set
|
import qualified Data.CharSet as Set
|
||||||
import qualified Data.CharSet.Unicode.Category as Set
|
import qualified Data.CharSet.Unicode.Category as Set
|
||||||
import Data.List
|
import Data.List
|
||||||
|
@ -29,7 +29,7 @@ import Servant.API
|
||||||
-- customize the output
|
-- customize the output
|
||||||
data CommonGeneratorOptions = CommonGeneratorOptions
|
data CommonGeneratorOptions = CommonGeneratorOptions
|
||||||
{
|
{
|
||||||
functionRenamer :: String -> String -- ^ function transforming function names
|
functionRenamer :: FunctionName -> String -- ^ function transforming function names
|
||||||
, requestBody :: String -- ^ name used when a user want to send the request body (to let you redefine it)
|
, requestBody :: String -- ^ name used when a user want to send the request body (to let you redefine it)
|
||||||
, successCallback :: String -- ^ name of the callback parameter when the request was successful
|
, successCallback :: String -- ^ name of the callback parameter when the request was successful
|
||||||
, errorCallback :: String -- ^ name of the callback parameter when the request reported an error
|
, errorCallback :: String -- ^ name of the callback parameter when the request reported an error
|
||||||
|
@ -40,7 +40,7 @@ data CommonGeneratorOptions = CommonGeneratorOptions
|
||||||
--
|
--
|
||||||
-- @
|
-- @
|
||||||
-- > defCommonGeneratorOptions = CommonGeneratorOptions
|
-- > defCommonGeneratorOptions = CommonGeneratorOptions
|
||||||
-- > { functionRenamer = id
|
-- > { functionRenamer = concatRenamer
|
||||||
-- > , requestBody = "body"
|
-- > , requestBody = "body"
|
||||||
-- > , successCallback = "onSuccess"
|
-- > , successCallback = "onSuccess"
|
||||||
-- > , errorCallback = "onError"
|
-- > , errorCallback = "onError"
|
||||||
|
@ -50,13 +50,32 @@ data CommonGeneratorOptions = CommonGeneratorOptions
|
||||||
defCommonGeneratorOptions :: CommonGeneratorOptions
|
defCommonGeneratorOptions :: CommonGeneratorOptions
|
||||||
defCommonGeneratorOptions = CommonGeneratorOptions
|
defCommonGeneratorOptions = CommonGeneratorOptions
|
||||||
{
|
{
|
||||||
functionRenamer = id
|
functionRenamer = concatRenamer
|
||||||
, requestBody = "body"
|
, requestBody = "body"
|
||||||
, successCallback = "onSuccess"
|
, successCallback = "onSuccess"
|
||||||
, errorCallback = "onError"
|
, errorCallback = "onError"
|
||||||
, moduleName = ""
|
, moduleName = ""
|
||||||
}
|
}
|
||||||
|
|
||||||
|
-- | Function renamer that simply concat each part together
|
||||||
|
concatRenamer :: FunctionName -> String
|
||||||
|
concatRenamer = concat
|
||||||
|
|
||||||
|
-- | Function renamer using the snake_case convention.
|
||||||
|
-- each part is separated by a single underscore character.
|
||||||
|
snakeCaseRenamer :: FunctionName -> String
|
||||||
|
snakeCaseRenamer = intercalate "_"
|
||||||
|
|
||||||
|
-- | Function renamer using the CamelCase convention.
|
||||||
|
-- each part begins with an upper case character.
|
||||||
|
camelCaseRenamer :: FunctionName -> String
|
||||||
|
camelCaseRenamer [] = ""
|
||||||
|
camelCaseRenamer (p:ps) = concat $ p : camelCaseRenamer' ps
|
||||||
|
where camelCaseRenamer' [] = []
|
||||||
|
camelCaseRenamer' (r:rs) = capitalize r : camelCaseRenamer' rs
|
||||||
|
capitalize [] = []
|
||||||
|
capitalize (x:xs) = toUpper x : xs
|
||||||
|
|
||||||
type Arg = String
|
type Arg = String
|
||||||
|
|
||||||
-- A 'JavascriptGenerator' just takes the data found in the API type
|
-- A 'JavascriptGenerator' just takes the data found in the API type
|
||||||
|
@ -146,7 +165,7 @@ data Url = Url
|
||||||
defUrl :: Url
|
defUrl :: Url
|
||||||
defUrl = Url [] []
|
defUrl = Url [] []
|
||||||
|
|
||||||
type FunctionName = String
|
type FunctionName = [String]
|
||||||
type Method = String
|
type Method = String
|
||||||
|
|
||||||
data AjaxReq = AjaxReq
|
data AjaxReq = AjaxReq
|
||||||
|
@ -223,7 +242,7 @@ paramToStr qarg notTheEnd =
|
||||||
where name = qarg ^. argName
|
where name = qarg ^. argName
|
||||||
|
|
||||||
defReq :: AjaxReq
|
defReq :: AjaxReq
|
||||||
defReq = AjaxReq defUrl "GET" [] False ""
|
defReq = AjaxReq defUrl "GET" [] False []
|
||||||
|
|
||||||
type family Elem (a :: *) (ls::[*]) :: Constraint where
|
type family Elem (a :: *) (ls::[*]) :: Constraint where
|
||||||
Elem a '[] = 'False ~ 'True
|
Elem a '[] = 'False ~ 'True
|
||||||
|
@ -256,14 +275,14 @@ instance Elem JSON list => HasJS (Delete list a) where
|
||||||
type JS (Delete list a) = AjaxReq
|
type JS (Delete list a) = AjaxReq
|
||||||
|
|
||||||
javascriptFor Proxy req =
|
javascriptFor Proxy req =
|
||||||
req & funcName %~ ("delete" <>)
|
req & funcName %~ ("delete" :)
|
||||||
& reqMethod .~ "DELETE"
|
& reqMethod .~ "DELETE"
|
||||||
|
|
||||||
instance Elem JSON list => HasJS (Get list a) where
|
instance Elem JSON list => HasJS (Get list a) where
|
||||||
type JS (Get list a) = AjaxReq
|
type JS (Get list a) = AjaxReq
|
||||||
|
|
||||||
javascriptFor Proxy req =
|
javascriptFor Proxy req =
|
||||||
req & funcName %~ ("get" <>)
|
req & funcName %~ ("get" :)
|
||||||
& reqMethod .~ "GET"
|
& reqMethod .~ "GET"
|
||||||
|
|
||||||
instance (KnownSymbol sym, HasJS sublayout)
|
instance (KnownSymbol sym, HasJS sublayout)
|
||||||
|
@ -280,14 +299,14 @@ instance Elem JSON list => HasJS (Post list a) where
|
||||||
type JS (Post list a) = AjaxReq
|
type JS (Post list a) = AjaxReq
|
||||||
|
|
||||||
javascriptFor Proxy req =
|
javascriptFor Proxy req =
|
||||||
req & funcName %~ ("post" <>)
|
req & funcName %~ ("post" :)
|
||||||
& reqMethod .~ "POST"
|
& reqMethod .~ "POST"
|
||||||
|
|
||||||
instance Elem JSON list => HasJS (Put list a) where
|
instance Elem JSON list => HasJS (Put list a) where
|
||||||
type JS (Put list a) = AjaxReq
|
type JS (Put list a) = AjaxReq
|
||||||
|
|
||||||
javascriptFor Proxy req =
|
javascriptFor Proxy req =
|
||||||
req & funcName %~ ("put" <>)
|
req & funcName %~ ("put" :)
|
||||||
& reqMethod .~ "PUT"
|
& reqMethod .~ "PUT"
|
||||||
|
|
||||||
instance (KnownSymbol sym, HasJS sublayout)
|
instance (KnownSymbol sym, HasJS sublayout)
|
||||||
|
@ -355,7 +374,7 @@ instance HasJS Raw where
|
||||||
type JS Raw = Method -> AjaxReq
|
type JS Raw = Method -> AjaxReq
|
||||||
|
|
||||||
javascriptFor Proxy req method =
|
javascriptFor Proxy req method =
|
||||||
req & funcName %~ ((toLower <$> method) <>)
|
req & funcName %~ ((toLower <$> method) :)
|
||||||
& reqMethod .~ method
|
& reqMethod .~ method
|
||||||
|
|
||||||
instance (Elem JSON list, HasJS sublayout) => HasJS (ReqBody list a :> sublayout) where
|
instance (Elem JSON list, HasJS sublayout) => HasJS (ReqBody list a :> sublayout) where
|
||||||
|
@ -372,7 +391,7 @@ instance (KnownSymbol path, HasJS sublayout)
|
||||||
javascriptFor Proxy req =
|
javascriptFor Proxy req =
|
||||||
javascriptFor (Proxy :: Proxy sublayout) $
|
javascriptFor (Proxy :: Proxy sublayout) $
|
||||||
req & reqUrl.path <>~ [Segment (Static str) []]
|
req & reqUrl.path <>~ [Segment (Static str) []]
|
||||||
& funcName %~ (str <>)
|
& funcName %~ (++ [str])
|
||||||
|
|
||||||
where str = map (\c -> if c == '.' then '_' else c) $ symbolVal (Proxy :: Proxy path)
|
where str = map (\c -> if c == '.' then '_' else c) $ symbolVal (Proxy :: Proxy path)
|
||||||
|
|
||||||
|
|
Loading…
Reference in a new issue