Convert servant-js to use text.
This commit is contained in:
parent
e17987e5ff
commit
a62441077e
6 changed files with 151 additions and 114 deletions
|
@ -39,7 +39,7 @@
|
||||||
-- Let's keep it simple and produce vanilla Javascript code with the default options.
|
-- Let's keep it simple and produce vanilla Javascript code with the default options.
|
||||||
--
|
--
|
||||||
-- @
|
-- @
|
||||||
-- jsCode :: String
|
-- jsCode :: Text
|
||||||
-- jsCode = 'jsForAPI' api 'vanillaJS'
|
-- jsCode = 'jsForAPI' api 'vanillaJS'
|
||||||
-- @
|
-- @
|
||||||
--
|
--
|
||||||
|
@ -60,7 +60,7 @@
|
||||||
-- All you need to do to use it is to use 'vanillaJSWith' and pass it @myOptions@.
|
-- All you need to do to use it is to use 'vanillaJSWith' and pass it @myOptions@.
|
||||||
--
|
--
|
||||||
-- @
|
-- @
|
||||||
-- jsCodeWithMyOptions :: String
|
-- jsCodeWithMyOptions :: Text
|
||||||
-- jsCodeWithMyOptions = 'jsForAPI' api ('vanillaJSWith' myOptions)
|
-- jsCodeWithMyOptions = 'jsForAPI' api ('vanillaJSWith' myOptions)
|
||||||
-- @
|
-- @
|
||||||
--
|
--
|
||||||
|
@ -112,7 +112,10 @@ module Servant.JS
|
||||||
, GenerateList(..)
|
, GenerateList(..)
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
import Prelude hiding (writeFile)
|
||||||
import Data.Proxy
|
import Data.Proxy
|
||||||
|
import Data.Text
|
||||||
|
import Data.Text.IO (writeFile)
|
||||||
import Servant.JS.Angular
|
import Servant.JS.Angular
|
||||||
import Servant.JS.Axios
|
import Servant.JS.Axios
|
||||||
import Servant.JS.Internal
|
import Servant.JS.Internal
|
||||||
|
@ -131,7 +134,7 @@ javascript p = foreignFor p defReq
|
||||||
jsForAPI :: (HasForeign api, GenerateList (Foreign api))
|
jsForAPI :: (HasForeign 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)
|
||||||
-> String -- ^ a string 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
|
||||||
jsForAPI p gen = gen (listFromAPI p)
|
jsForAPI p gen = gen (listFromAPI p)
|
||||||
|
|
||||||
-- | Directly generate all the javascript functions for your API
|
-- | Directly generate all the javascript functions for your API
|
||||||
|
@ -142,6 +145,8 @@ writeJSForAPI :: (HasForeign api, GenerateList (Foreign api))
|
||||||
-> 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
|
||||||
-> IO ()
|
-> IO ()
|
||||||
|
|
||||||
|
-- TODO Data.Text
|
||||||
writeJSForAPI p gen fp = writeFile fp (jsForAPI p gen)
|
writeJSForAPI p gen fp = writeFile fp (jsForAPI p gen)
|
||||||
|
|
||||||
-- | Utility class used by 'jsForAPI' which computes
|
-- | Utility class used by 'jsForAPI' which computes
|
||||||
|
|
|
@ -1,17 +1,19 @@
|
||||||
|
{-#LANGUAGE OverloadedStrings #-}
|
||||||
module Servant.JS.Angular where
|
module Servant.JS.Angular where
|
||||||
|
|
||||||
import Control.Lens
|
import Control.Lens
|
||||||
import Data.List
|
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
|
import qualified Data.Text as T
|
||||||
|
import Data.Text (Text)
|
||||||
import Servant.Foreign
|
import Servant.Foreign
|
||||||
import Servant.JS.Internal
|
import Servant.JS.Internal
|
||||||
|
|
||||||
-- | Options specific to the angular code generator
|
-- | Options specific to the angular code generator
|
||||||
data AngularOptions = AngularOptions
|
data AngularOptions = AngularOptions
|
||||||
{ serviceName :: String -- ^ When generating code with wrapInService,
|
{ serviceName :: Text -- ^ When generating code with wrapInService,
|
||||||
-- name of the service to generate
|
-- name of the service to generate
|
||||||
, prologue :: String -> String -> String -- ^ beginning of the service definition
|
, prologue :: Text -> Text -> Text -- ^ beginning of the service definition
|
||||||
, epilogue :: String -- ^ end of the service definition
|
, epilogue :: Text -- ^ end of the service definition
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | Default options for the Angular codegen. Used by 'wrapInService'.
|
-- | Default options for the Angular codegen. Used by 'wrapInService'.
|
||||||
|
@ -34,12 +36,12 @@ angularService ngOpts = angularServiceWith ngOpts defCommonGeneratorOptions
|
||||||
angularServiceWith :: AngularOptions -> CommonGeneratorOptions -> JavaScriptGenerator
|
angularServiceWith :: AngularOptions -> CommonGeneratorOptions -> JavaScriptGenerator
|
||||||
angularServiceWith ngOpts opts reqs =
|
angularServiceWith ngOpts opts reqs =
|
||||||
prologue ngOpts svc mName
|
prologue ngOpts svc mName
|
||||||
<> intercalate "," (map generator reqs) <>
|
<> T.intercalate "," (map generator reqs) <>
|
||||||
epilogue ngOpts
|
epilogue ngOpts
|
||||||
where
|
where
|
||||||
generator req = generateAngularJSWith ngOpts opts req
|
generator req = generateAngularJSWith ngOpts opts req
|
||||||
svc = serviceName ngOpts
|
svc = serviceName ngOpts
|
||||||
mName = if null (moduleName opts)
|
mName = if moduleName opts == ""
|
||||||
then "app."
|
then "app."
|
||||||
else moduleName opts <> "."
|
else moduleName opts <> "."
|
||||||
|
|
||||||
|
@ -50,14 +52,14 @@ angular ngopts = angularWith ngopts defCommonGeneratorOptions
|
||||||
|
|
||||||
-- | Generate regular javascript functions that use the $http service.
|
-- | Generate regular javascript functions that use the $http service.
|
||||||
angularWith :: AngularOptions -> CommonGeneratorOptions -> JavaScriptGenerator
|
angularWith :: AngularOptions -> CommonGeneratorOptions -> JavaScriptGenerator
|
||||||
angularWith ngopts opts = intercalate "\n\n" . map (generateAngularJSWith ngopts opts)
|
angularWith ngopts opts = T.intercalate "\n\n" . map (generateAngularJSWith ngopts opts)
|
||||||
|
|
||||||
-- | js codegen using $http service from Angular using default options
|
-- | js codegen using $http service from Angular using default options
|
||||||
generateAngularJS :: AngularOptions -> AjaxReq -> String
|
generateAngularJS :: AngularOptions -> AjaxReq -> Text
|
||||||
generateAngularJS ngOpts = generateAngularJSWith ngOpts defCommonGeneratorOptions
|
generateAngularJS ngOpts = generateAngularJSWith ngOpts defCommonGeneratorOptions
|
||||||
|
|
||||||
-- | js codegen using $http service from Angular
|
-- | js codegen using $http service from Angular
|
||||||
generateAngularJSWith :: AngularOptions -> CommonGeneratorOptions -> AjaxReq -> String
|
generateAngularJSWith :: AngularOptions -> CommonGeneratorOptions -> AjaxReq -> Text
|
||||||
generateAngularJSWith ngOptions opts req = "\n" <>
|
generateAngularJSWith ngOptions opts req = "\n" <>
|
||||||
fname <> fsep <> " function(" <> argsStr <> ")\n"
|
fname <> fsep <> " function(" <> argsStr <> ")\n"
|
||||||
<> "{\n"
|
<> "{\n"
|
||||||
|
@ -69,7 +71,7 @@ generateAngularJSWith ngOptions opts req = "\n" <>
|
||||||
<> " });\n"
|
<> " });\n"
|
||||||
<> "}\n"
|
<> "}\n"
|
||||||
|
|
||||||
where argsStr = intercalate ", " args
|
where argsStr = T.intercalate ", " args
|
||||||
args = http
|
args = http
|
||||||
++ captures
|
++ captures
|
||||||
++ map (view argName) queryparams
|
++ map (view argName) queryparams
|
||||||
|
@ -79,7 +81,7 @@ generateAngularJSWith ngOptions opts req = "\n" <>
|
||||||
-- If we want to generate Top Level Function, they must depend on
|
-- If we want to generate Top Level Function, they must depend on
|
||||||
-- the $http service, if we generate a service, the functions will
|
-- the $http service, if we generate a service, the functions will
|
||||||
-- inherit this dependency from the service
|
-- inherit this dependency from the service
|
||||||
http = case length (serviceName ngOptions) of
|
http = case T.length (serviceName ngOptions) of
|
||||||
0 -> ["$http"]
|
0 -> ["$http"]
|
||||||
_ -> []
|
_ -> []
|
||||||
|
|
||||||
|
@ -104,12 +106,12 @@ generateAngularJSWith ngOptions opts req = "\n" <>
|
||||||
reqheaders =
|
reqheaders =
|
||||||
if null hs
|
if null hs
|
||||||
then ""
|
then ""
|
||||||
else " , headers: { " ++ headersStr ++ " }\n"
|
else " , headers: { " <> headersStr <> " }\n"
|
||||||
|
|
||||||
where headersStr = intercalate ", " $ map headerStr hs
|
where headersStr = T.intercalate ", " $ map headerStr hs
|
||||||
headerStr header = "\"" ++
|
headerStr header = "\"" <>
|
||||||
headerArgName header ++
|
headerArgName header <>
|
||||||
"\": " ++ toJSHeader header
|
"\": " <> toJSHeader header
|
||||||
|
|
||||||
namespace =
|
namespace =
|
||||||
if hasService
|
if hasService
|
||||||
|
@ -118,9 +120,9 @@ generateAngularJSWith ngOptions opts req = "\n" <>
|
||||||
then "var "
|
then "var "
|
||||||
else (moduleName opts) <> "."
|
else (moduleName opts) <> "."
|
||||||
where
|
where
|
||||||
hasNoModule = null (moduleName opts)
|
hasNoModule = moduleName opts == ""
|
||||||
|
|
||||||
hasService = not $ null (serviceName ngOptions)
|
hasService = serviceName ngOptions /= ""
|
||||||
|
|
||||||
fsep = if hasService then ":" else " ="
|
fsep = if hasService then ":" else " ="
|
||||||
|
|
||||||
|
@ -129,13 +131,13 @@ generateAngularJSWith ngOptions opts req = "\n" <>
|
||||||
method = req ^. reqMethod
|
method = req ^. reqMethod
|
||||||
url = if url' == "'" then "'/'" else url'
|
url = if url' == "'" then "'/'" else url'
|
||||||
url' = "'"
|
url' = "'"
|
||||||
++ urlPrefix opts
|
<> urlPrefix opts
|
||||||
++ urlArgs
|
<> urlArgs
|
||||||
++ queryArgs
|
<> queryArgs
|
||||||
|
|
||||||
urlArgs = jsSegments
|
urlArgs = jsSegments
|
||||||
$ req ^.. reqUrl.path.traverse
|
$ req ^.. reqUrl.path.traverse
|
||||||
|
|
||||||
queryArgs = if null queryparams
|
queryArgs = if null queryparams
|
||||||
then ""
|
then ""
|
||||||
else " + '?" ++ jsParams queryparams
|
else " + '?" <> jsParams queryparams
|
||||||
|
|
|
@ -1,9 +1,10 @@
|
||||||
|
{-#LANGUAGE OverloadedStrings #-}
|
||||||
module Servant.JS.Axios where
|
module Servant.JS.Axios where
|
||||||
|
|
||||||
import Control.Lens
|
import Control.Lens
|
||||||
import Data.Char (toLower)
|
|
||||||
import Data.List
|
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
|
import Data.Text (Text)
|
||||||
|
import qualified Data.Text as T
|
||||||
import Servant.Foreign
|
import Servant.Foreign
|
||||||
import Servant.JS.Internal
|
import Servant.JS.Internal
|
||||||
|
|
||||||
|
@ -14,9 +15,9 @@ data AxiosOptions = AxiosOptions
|
||||||
-- should be made using credentials
|
-- should be made using credentials
|
||||||
withCredentials :: !Bool
|
withCredentials :: !Bool
|
||||||
-- | the name of the cookie to use as a value for xsrf token
|
-- | the name of the cookie to use as a value for xsrf token
|
||||||
, xsrfCookieName :: !(Maybe String)
|
, xsrfCookieName :: !(Maybe Text)
|
||||||
-- | the name of the header to use as a value for xsrf token
|
-- | the name of the header to use as a value for xsrf token
|
||||||
, xsrfHeaderName :: !(Maybe String)
|
, xsrfHeaderName :: !(Maybe Text)
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | Default instance of the AxiosOptions
|
-- | Default instance of the AxiosOptions
|
||||||
|
@ -36,14 +37,14 @@ axios aopts = axiosWith aopts defCommonGeneratorOptions
|
||||||
|
|
||||||
-- | Generate regular javascript functions that use the axios library.
|
-- | Generate regular javascript functions that use the axios library.
|
||||||
axiosWith :: AxiosOptions -> CommonGeneratorOptions -> JavaScriptGenerator
|
axiosWith :: AxiosOptions -> CommonGeneratorOptions -> JavaScriptGenerator
|
||||||
axiosWith aopts opts = intercalate "\n\n" . map (generateAxiosJSWith aopts opts)
|
axiosWith aopts opts = T.intercalate "\n\n" . map (generateAxiosJSWith aopts opts)
|
||||||
|
|
||||||
-- | js codegen using axios library using default options
|
-- | js codegen using axios library using default options
|
||||||
generateAxiosJS :: AxiosOptions -> AjaxReq -> String
|
generateAxiosJS :: AxiosOptions -> AjaxReq -> Text
|
||||||
generateAxiosJS aopts = generateAxiosJSWith aopts defCommonGeneratorOptions
|
generateAxiosJS aopts = generateAxiosJSWith aopts defCommonGeneratorOptions
|
||||||
|
|
||||||
-- | js codegen using axios library
|
-- | js codegen using axios library
|
||||||
generateAxiosJSWith :: AxiosOptions -> CommonGeneratorOptions -> AjaxReq -> String
|
generateAxiosJSWith :: AxiosOptions -> CommonGeneratorOptions -> AjaxReq -> Text
|
||||||
generateAxiosJSWith aopts opts req = "\n" <>
|
generateAxiosJSWith aopts opts req = "\n" <>
|
||||||
fname <> " = function(" <> argsStr <> ")\n"
|
fname <> " = function(" <> argsStr <> ")\n"
|
||||||
<> "{\n"
|
<> "{\n"
|
||||||
|
@ -57,7 +58,7 @@ generateAxiosJSWith aopts opts req = "\n" <>
|
||||||
<> " });\n"
|
<> " });\n"
|
||||||
<> "}\n"
|
<> "}\n"
|
||||||
|
|
||||||
where argsStr = intercalate ", " args
|
where argsStr = T.intercalate ", " args
|
||||||
args = captures
|
args = captures
|
||||||
++ map (view argName) queryparams
|
++ map (view argName) queryparams
|
||||||
++ body
|
++ body
|
||||||
|
@ -101,30 +102,30 @@ generateAxiosJSWith aopts opts req = "\n" <>
|
||||||
then ""
|
then ""
|
||||||
else " , headers: { " <> headersStr <> " }\n"
|
else " , headers: { " <> headersStr <> " }\n"
|
||||||
|
|
||||||
where headersStr = intercalate ", " $ map headerStr hs
|
where headersStr = T.intercalate ", " $ map headerStr hs
|
||||||
headerStr header = "\"" ++
|
headerStr header = "\"" <>
|
||||||
headerArgName header ++
|
headerArgName header <>
|
||||||
"\": " ++ toJSHeader header
|
"\": " <> toJSHeader header
|
||||||
|
|
||||||
namespace =
|
namespace =
|
||||||
if hasNoModule
|
if hasNoModule
|
||||||
then "var "
|
then "var "
|
||||||
else (moduleName opts) <> "."
|
else (moduleName opts) <> "."
|
||||||
where
|
where
|
||||||
hasNoModule = null (moduleName opts)
|
hasNoModule = moduleName opts == ""
|
||||||
|
|
||||||
fname = namespace <> (functionNameBuilder opts $ req ^. funcName)
|
fname = namespace <> (functionNameBuilder opts $ req ^. funcName)
|
||||||
|
|
||||||
method = map toLower $ req ^. reqMethod
|
method = T.toLower $ req ^. reqMethod
|
||||||
url = if url' == "'" then "'/'" else url'
|
url = if url' == "'" then "'/'" else url'
|
||||||
url' = "'"
|
url' = "'"
|
||||||
++ urlPrefix opts
|
<> urlPrefix opts
|
||||||
++ urlArgs
|
<> urlArgs
|
||||||
++ queryArgs
|
<> queryArgs
|
||||||
|
|
||||||
urlArgs = jsSegments
|
urlArgs = jsSegments
|
||||||
$ req ^.. reqUrl.path.traverse
|
$ req ^.. reqUrl.path.traverse
|
||||||
|
|
||||||
queryArgs = if null queryparams
|
queryArgs = if null queryparams
|
||||||
then ""
|
then ""
|
||||||
else " + '?" ++ jsParams queryparams
|
else " + '?" <> jsParams queryparams
|
||||||
|
|
|
@ -1,3 +1,4 @@
|
||||||
|
{-#LANGUAGE OverloadedStrings #-}
|
||||||
module Servant.JS.Internal
|
module Servant.JS.Internal
|
||||||
( JavaScriptGenerator
|
( JavaScriptGenerator
|
||||||
, CommonGeneratorOptions(..)
|
, CommonGeneratorOptions(..)
|
||||||
|
@ -34,28 +35,28 @@ module Servant.JS.Internal
|
||||||
import Control.Lens ((^.))
|
import Control.Lens ((^.))
|
||||||
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.Monoid
|
import Data.Monoid
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
|
import Data.Text (Text)
|
||||||
import Servant.Foreign
|
import Servant.Foreign
|
||||||
|
|
||||||
type AjaxReq = Req
|
type AjaxReq = Req
|
||||||
|
|
||||||
-- A 'JavascriptGenerator' just takes the data found in the API type
|
-- A 'JavascriptGenerator' just takes the data found in the API type
|
||||||
-- for each endpoint and generates Javascript code in a String. Several
|
-- for each endpoint and generates Javascript code in a Text. Several
|
||||||
-- generators are available in this package.
|
-- generators are available in this package.
|
||||||
type JavaScriptGenerator = [Req] -> String
|
type JavaScriptGenerator = [Req] -> Text
|
||||||
|
|
||||||
-- | This structure is used by specific implementations to let you
|
-- | This structure is used by specific implementations to let you
|
||||||
-- customize the output
|
-- customize the output
|
||||||
data CommonGeneratorOptions = CommonGeneratorOptions
|
data CommonGeneratorOptions = CommonGeneratorOptions
|
||||||
{
|
{
|
||||||
functionNameBuilder :: FunctionName -> String -- ^ function generating function names
|
functionNameBuilder :: FunctionName -> Text -- ^ function generating function names
|
||||||
, requestBody :: String -- ^ name used when a user want to send the request body (to let you redefine it)
|
, requestBody :: Text -- ^ 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 :: Text -- ^ name of the callback parameter when the request was successful
|
||||||
, errorCallback :: String -- ^ name of the callback parameter when the request reported an error
|
, errorCallback :: Text -- ^ name of the callback parameter when the request reported an error
|
||||||
, moduleName :: String -- ^ namespace on which we define the foreign function (empty mean local var)
|
, moduleName :: Text -- ^ namespace on which we define the foreign function (empty mean local var)
|
||||||
, urlPrefix :: String -- ^ a prefix we should add to the Url in the codegen
|
, urlPrefix :: Text -- ^ a prefix we should add to the Url in the codegen
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | Default options.
|
-- | Default options.
|
||||||
|
@ -87,7 +88,34 @@ defCommonGeneratorOptions = CommonGeneratorOptions
|
||||||
-- Couldn't work out how to handle zero-width characters.
|
-- Couldn't work out how to handle zero-width characters.
|
||||||
--
|
--
|
||||||
-- @TODO: specify better default function name, or throw error?
|
-- @TODO: specify better default function name, or throw error?
|
||||||
toValidFunctionName :: String -> String
|
toValidFunctionName :: Text -> Text
|
||||||
|
-- @TODO: Cons text
|
||||||
|
--
|
||||||
|
|
||||||
|
toValidFunctionName t =
|
||||||
|
case T.uncons t of
|
||||||
|
Just (x,xs) ->
|
||||||
|
setFirstChar x `T.cons` T.filter remainder xs
|
||||||
|
Nothing -> "_"
|
||||||
|
where
|
||||||
|
setFirstChar c = if firstChar c then c else '_'
|
||||||
|
firstChar c = prefixOK c || any (Set.member c) firstLetterOK
|
||||||
|
remainder c = prefixOK c || any (Set.member c) remainderOK
|
||||||
|
-- Valid prefixes
|
||||||
|
prefixOK c = c `elem` ['$','_']
|
||||||
|
-- Unicode character sets
|
||||||
|
firstLetterOK = [ Set.lowercaseLetter
|
||||||
|
, Set.uppercaseLetter
|
||||||
|
, Set.titlecaseLetter
|
||||||
|
, Set.modifierLetter
|
||||||
|
, Set.otherLetter
|
||||||
|
, Set.letterNumber ]
|
||||||
|
remainderOK = firstLetterOK
|
||||||
|
<> [ Set.nonSpacingMark
|
||||||
|
, Set.spacingCombiningMark
|
||||||
|
, Set.decimalNumber
|
||||||
|
, Set.connectorPunctuation ]
|
||||||
|
{-
|
||||||
toValidFunctionName (x:xs) = [setFirstChar x] <> filter remainder xs
|
toValidFunctionName (x:xs) = [setFirstChar x] <> filter remainder xs
|
||||||
where
|
where
|
||||||
setFirstChar c = if firstChar c then c else '_'
|
setFirstChar c = if firstChar c then c else '_'
|
||||||
|
@ -108,59 +136,56 @@ toValidFunctionName (x:xs) = [setFirstChar x] <> filter remainder xs
|
||||||
, Set.decimalNumber
|
, Set.decimalNumber
|
||||||
, Set.connectorPunctuation ]
|
, Set.connectorPunctuation ]
|
||||||
toValidFunctionName [] = "_"
|
toValidFunctionName [] = "_"
|
||||||
|
-}
|
||||||
|
|
||||||
toJSHeader :: HeaderArg -> String
|
toJSHeader :: HeaderArg -> Text
|
||||||
toJSHeader (HeaderArg n) = toValidFunctionName ("header" <> n)
|
toJSHeader (HeaderArg n) = toValidFunctionName ("header" <> n)
|
||||||
toJSHeader (ReplaceHeaderArg n p)
|
toJSHeader (ReplaceHeaderArg n p)
|
||||||
| pn `isPrefixOf` p = pv <> " + \"" <> rp <> "\""
|
| pn `T.isPrefixOf` p = pv <> " + \"" <> rp <> "\""
|
||||||
| pn `isSuffixOf` p = "\"" <> rp <> "\" + " <> pv
|
| pn `T.isSuffixOf` p = "\"" <> rp <> "\" + " <> pv
|
||||||
| pn `isInfixOf` p = "\"" <> (replace pn ("\" + " <> pv <> " + \"") p)
|
| pn `T.isInfixOf` p = "\"" <> (T.replace pn ("\" + " <> pv <> " + \"") p)
|
||||||
<> "\""
|
<> "\""
|
||||||
| otherwise = p
|
| otherwise = p
|
||||||
where
|
where
|
||||||
pv = toValidFunctionName ("header" <> n)
|
pv = toValidFunctionName ("header" <> n)
|
||||||
pn = "{" <> n <> "}"
|
pn = "{" <> n <> "}"
|
||||||
rp = replace pn "" p
|
rp = T.replace pn "" p
|
||||||
-- Use replace method from Data.Text
|
|
||||||
replace old new = T.unpack
|
|
||||||
. T.replace (T.pack old) (T.pack new)
|
|
||||||
. T.pack
|
|
||||||
|
|
||||||
jsSegments :: [Segment] -> String
|
jsSegments :: [Segment] -> Text
|
||||||
jsSegments [] = ""
|
jsSegments [] = ""
|
||||||
jsSegments [x] = "/" ++ segmentToStr x False
|
jsSegments [x] = "/" <> segmentToStr x False
|
||||||
jsSegments (x:xs) = "/" ++ segmentToStr x True ++ jsSegments xs
|
jsSegments (x:xs) = "/" <> segmentToStr x True <> jsSegments xs
|
||||||
|
|
||||||
segmentToStr :: Segment -> Bool -> String
|
segmentToStr :: Segment -> Bool -> Text
|
||||||
segmentToStr (Segment st ms) notTheEnd =
|
segmentToStr (Segment st ms) notTheEnd =
|
||||||
segmentTypeToStr st ++ jsMParams ms ++ if notTheEnd then "" else "'"
|
segmentTypeToStr st <> jsMParams ms <> if notTheEnd then "" else "'"
|
||||||
|
|
||||||
segmentTypeToStr :: SegmentType -> String
|
segmentTypeToStr :: SegmentType -> Text
|
||||||
segmentTypeToStr (Static s) = s
|
segmentTypeToStr (Static s) = s
|
||||||
segmentTypeToStr (Cap s) = "' + encodeURIComponent(" ++ s ++ ") + '"
|
segmentTypeToStr (Cap s) = "' + encodeURIComponent(" <> s <> ") + '"
|
||||||
|
|
||||||
jsGParams :: String -> [QueryArg] -> String
|
jsGParams :: Text -> [QueryArg] -> Text
|
||||||
jsGParams _ [] = ""
|
jsGParams _ [] = ""
|
||||||
jsGParams _ [x] = paramToStr x False
|
jsGParams _ [x] = paramToStr x False
|
||||||
jsGParams s (x:xs) = paramToStr x True ++ s ++ jsGParams s xs
|
jsGParams s (x:xs) = paramToStr x True <> s <> jsGParams s xs
|
||||||
|
|
||||||
jsParams :: [QueryArg] -> String
|
jsParams :: [QueryArg] -> Text
|
||||||
jsParams = jsGParams "&"
|
jsParams = jsGParams "&"
|
||||||
|
|
||||||
jsMParams :: [MatrixArg] -> String
|
jsMParams :: [MatrixArg] -> Text
|
||||||
jsMParams [] = ""
|
jsMParams [] = ""
|
||||||
jsMParams xs = ";" ++ jsGParams ";" xs
|
jsMParams xs = ";" <> jsGParams ";" xs
|
||||||
|
|
||||||
paramToStr :: QueryArg -> Bool -> String
|
paramToStr :: QueryArg -> Bool -> Text
|
||||||
paramToStr qarg notTheEnd =
|
paramToStr qarg notTheEnd =
|
||||||
case qarg ^. argType of
|
case qarg ^. argType of
|
||||||
Normal -> name
|
Normal -> name
|
||||||
++ "=' + encodeURIComponent("
|
<> "=' + encodeURIComponent("
|
||||||
++ name
|
<> name
|
||||||
++ if notTheEnd then ") + '" else ")"
|
<> if notTheEnd then ") + '" else ")"
|
||||||
Flag -> name ++ "="
|
Flag -> name <> "="
|
||||||
List -> name
|
List -> name
|
||||||
++ "[]=' + encodeURIComponent("
|
<> "[]=' + encodeURIComponent("
|
||||||
++ name
|
<> name
|
||||||
++ if notTheEnd then ") + '" else ")"
|
<> if notTheEnd then ") + '" else ")"
|
||||||
where name = qarg ^. argName
|
where name = qarg ^. argName
|
||||||
|
|
|
@ -1,8 +1,10 @@
|
||||||
|
{-#LANGUAGE OverloadedStrings #-}
|
||||||
module Servant.JS.JQuery where
|
module Servant.JS.JQuery where
|
||||||
|
|
||||||
import Control.Lens
|
import Control.Lens
|
||||||
import Data.List
|
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
|
import qualified Data.Text as T
|
||||||
|
import Data.Text (Text)
|
||||||
import Servant.Foreign
|
import Servant.Foreign
|
||||||
import Servant.JS.Internal
|
import Servant.JS.Internal
|
||||||
|
|
||||||
|
@ -10,19 +12,19 @@ import Servant.JS.Internal
|
||||||
-- 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 = concatMap generateJQueryJS
|
jquery = mconcat . map 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 = concatMap (generateJQueryJSWith opts)
|
jqueryWith opts = mconcat . map (generateJQueryJSWith opts)
|
||||||
|
|
||||||
-- | js codegen using JQuery using default options
|
-- | js codegen using JQuery using default options
|
||||||
generateJQueryJS :: AjaxReq -> String
|
generateJQueryJS :: AjaxReq -> Text
|
||||||
generateJQueryJS = generateJQueryJSWith defCommonGeneratorOptions
|
generateJQueryJS = generateJQueryJSWith defCommonGeneratorOptions
|
||||||
|
|
||||||
-- | js codegen using JQuery
|
-- | js codegen using JQuery
|
||||||
generateJQueryJSWith :: CommonGeneratorOptions -> AjaxReq -> String
|
generateJQueryJSWith :: CommonGeneratorOptions -> AjaxReq -> Text
|
||||||
generateJQueryJSWith opts req = "\n" <>
|
generateJQueryJSWith opts req = "\n" <>
|
||||||
fname <> " = function(" <> argsStr <> ")\n"
|
fname <> " = function(" <> argsStr <> ")\n"
|
||||||
<> "{\n"
|
<> "{\n"
|
||||||
|
@ -36,7 +38,7 @@ generateJQueryJSWith opts req = "\n" <>
|
||||||
<> " });\n"
|
<> " });\n"
|
||||||
<> "}\n"
|
<> "}\n"
|
||||||
|
|
||||||
where argsStr = intercalate ", " args
|
where argsStr = T.intercalate ", " args
|
||||||
args = captures
|
args = captures
|
||||||
++ map (view argName) queryparams
|
++ map (view argName) queryparams
|
||||||
++ body
|
++ body
|
||||||
|
@ -67,14 +69,14 @@ generateJQueryJSWith opts req = "\n" <>
|
||||||
reqheaders =
|
reqheaders =
|
||||||
if null hs
|
if null hs
|
||||||
then ""
|
then ""
|
||||||
else " , headers: { " ++ headersStr ++ " }\n"
|
else " , headers: { " <> headersStr <> " }\n"
|
||||||
|
|
||||||
where headersStr = intercalate ", " $ map headerStr hs
|
where headersStr = T.intercalate ", " $ map headerStr hs
|
||||||
headerStr header = "\"" ++
|
headerStr header = "\"" <>
|
||||||
headerArgName header ++
|
headerArgName header <>
|
||||||
"\": " ++ toJSHeader header
|
"\": " <> toJSHeader header
|
||||||
|
|
||||||
namespace = if null (moduleName opts)
|
namespace = if (moduleName opts) == ""
|
||||||
then "var "
|
then "var "
|
||||||
else (moduleName opts) <> "."
|
else (moduleName opts) <> "."
|
||||||
fname = namespace <> (functionNameBuilder opts $ req ^. funcName)
|
fname = namespace <> (functionNameBuilder opts $ req ^. funcName)
|
||||||
|
@ -82,13 +84,13 @@ generateJQueryJSWith opts req = "\n" <>
|
||||||
method = req ^. reqMethod
|
method = req ^. reqMethod
|
||||||
url = if url' == "'" then "'/'" else url'
|
url = if url' == "'" then "'/'" else url'
|
||||||
url' = "'"
|
url' = "'"
|
||||||
++ urlPrefix opts
|
<> urlPrefix opts
|
||||||
++ urlArgs
|
<> urlArgs
|
||||||
++ queryArgs
|
<> queryArgs
|
||||||
|
|
||||||
urlArgs = jsSegments
|
urlArgs = jsSegments
|
||||||
$ req ^.. reqUrl.path.traverse
|
$ req ^.. reqUrl.path.traverse
|
||||||
|
|
||||||
queryArgs = if null queryparams
|
queryArgs = if null queryparams
|
||||||
then ""
|
then ""
|
||||||
else " + '?" ++ jsParams queryparams
|
else " + '?" <> jsParams queryparams
|
||||||
|
|
|
@ -1,7 +1,9 @@
|
||||||
|
{-#LANGUAGE OverloadedStrings #-}
|
||||||
module Servant.JS.Vanilla where
|
module Servant.JS.Vanilla where
|
||||||
|
|
||||||
import Control.Lens
|
import Control.Lens
|
||||||
import Data.List
|
import Data.Text (Text)
|
||||||
|
import qualified Data.Text as T
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
import Servant.Foreign
|
import Servant.Foreign
|
||||||
import Servant.JS.Internal
|
import Servant.JS.Internal
|
||||||
|
@ -10,20 +12,20 @@ import Servant.JS.Internal
|
||||||
-- 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 = concatMap generateVanillaJS
|
vanillaJS = mconcat . map 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 = concatMap (generateVanillaJSWith opts)
|
vanillaJSWith opts = mconcat . map (generateVanillaJSWith opts)
|
||||||
|
|
||||||
-- | js codegen using XmlHttpRequest using default generation options
|
-- | js codegen using XmlHttpRequest using default generation options
|
||||||
generateVanillaJS :: AjaxReq -> String
|
generateVanillaJS :: AjaxReq -> Text
|
||||||
generateVanillaJS = generateVanillaJSWith defCommonGeneratorOptions
|
generateVanillaJS = generateVanillaJSWith defCommonGeneratorOptions
|
||||||
|
|
||||||
-- | js codegen using XmlHttpRequest
|
-- | js codegen using XmlHttpRequest
|
||||||
generateVanillaJSWith :: CommonGeneratorOptions -> AjaxReq -> String
|
generateVanillaJSWith :: CommonGeneratorOptions -> AjaxReq -> Text
|
||||||
generateVanillaJSWith opts req = "\n" <>
|
generateVanillaJSWith opts req = "\n" <>
|
||||||
fname <> " = function(" <> argsStr <> ")\n"
|
fname <> " = function(" <> argsStr <> ")\n"
|
||||||
<> "{\n"
|
<> "{\n"
|
||||||
|
@ -43,7 +45,7 @@ generateVanillaJSWith opts req = "\n" <>
|
||||||
<> " xhr.send(" <> dataBody <> ");\n"
|
<> " xhr.send(" <> dataBody <> ");\n"
|
||||||
<> "}\n"
|
<> "}\n"
|
||||||
|
|
||||||
where argsStr = intercalate ", " args
|
where argsStr = T.intercalate ", " args
|
||||||
args = captures
|
args = captures
|
||||||
++ map (view argName) queryparams
|
++ map (view argName) queryparams
|
||||||
++ body
|
++ body
|
||||||
|
@ -74,14 +76,14 @@ generateVanillaJSWith opts req = "\n" <>
|
||||||
reqheaders =
|
reqheaders =
|
||||||
if null hs
|
if null hs
|
||||||
then ""
|
then ""
|
||||||
else headersStr ++ "\n"
|
else headersStr <> "\n"
|
||||||
|
|
||||||
where headersStr = intercalate "\n" $ map headerStr hs
|
where headersStr = T.intercalate "\n" $ map headerStr hs
|
||||||
headerStr header = " xhr.setRequestHeader(\"" ++
|
headerStr header = " xhr.setRequestHeader(\"" <>
|
||||||
headerArgName header ++
|
headerArgName header <>
|
||||||
"\", " ++ toJSHeader header ++ ");"
|
"\", " <> toJSHeader header <> ");"
|
||||||
|
|
||||||
namespace = if null (moduleName opts)
|
namespace = if moduleName opts == ""
|
||||||
then "var "
|
then "var "
|
||||||
else (moduleName opts) <> "."
|
else (moduleName opts) <> "."
|
||||||
fname = namespace <> (functionNameBuilder opts $ req ^. funcName)
|
fname = namespace <> (functionNameBuilder opts $ req ^. funcName)
|
||||||
|
@ -89,13 +91,13 @@ generateVanillaJSWith opts req = "\n" <>
|
||||||
method = req ^. reqMethod
|
method = req ^. reqMethod
|
||||||
url = if url' == "'" then "'/'" else url'
|
url = if url' == "'" then "'/'" else url'
|
||||||
url' = "'"
|
url' = "'"
|
||||||
++ urlPrefix opts
|
<> urlPrefix opts
|
||||||
++ urlArgs
|
<> urlArgs
|
||||||
++ queryArgs
|
<> queryArgs
|
||||||
|
|
||||||
urlArgs = jsSegments
|
urlArgs = jsSegments
|
||||||
$ req ^.. reqUrl.path.traverse
|
$ req ^.. reqUrl.path.traverse
|
||||||
|
|
||||||
queryArgs = if null queryparams
|
queryArgs = if null queryparams
|
||||||
then ""
|
then ""
|
||||||
else " + '?" ++ jsParams queryparams
|
else " + '?" <> jsParams queryparams
|
||||||
|
|
Loading…
Add table
Reference in a new issue