{-#LANGUAGE OverloadedStrings #-}
module Servant.JS.Angular where
import Prelude ()
import Prelude.Compat
import Control.Lens
import Data.Maybe (isJust)
import qualified Data.Text as T
import Data.Text (Text)
import Data.Text.Encoding (decodeUtf8)
import Servant.Foreign
import Servant.JS.Internal
data AngularOptions = AngularOptions
{ serviceName :: Text
, prologue :: Text -> Text -> Text
, epilogue :: Text
}
defAngularOptions :: AngularOptions
defAngularOptions = AngularOptions
{ serviceName = ""
, prologue = \svc m -> m <> "service('" <> svc <> "', function($http) {\n"
<> " return ({"
, epilogue = "});\n});\n"
}
angularService :: AngularOptions -> JavaScriptGenerator
angularService ngOpts = angularServiceWith ngOpts defCommonGeneratorOptions
angularServiceWith :: AngularOptions -> CommonGeneratorOptions -> JavaScriptGenerator
angularServiceWith ngOpts opts reqs =
prologue ngOpts svc mName
<> T.intercalate "," (map generator reqs) <>
epilogue ngOpts
where
generator req = generateAngularJSWith ngOpts opts req
svc = serviceName ngOpts
mName = if moduleName opts == ""
then "app."
else moduleName opts <> "."
angular :: AngularOptions -> JavaScriptGenerator
angular ngopts = angularWith ngopts defCommonGeneratorOptions
angularWith :: AngularOptions -> CommonGeneratorOptions -> JavaScriptGenerator
angularWith ngopts opts = T.intercalate "\n\n" . map (generateAngularJSWith ngopts opts)
generateAngularJS :: AngularOptions -> AjaxReq -> Text
generateAngularJS ngOpts = generateAngularJSWith ngOpts defCommonGeneratorOptions
generateAngularJSWith :: AngularOptions -> CommonGeneratorOptions -> AjaxReq -> Text
generateAngularJSWith ngOptions opts req = "\n" <>
fname <> fsep <> " function(" <> argsStr <> ")\n"
<> "{\n"
<> " return $http(\n"
<> " { url: " <> url <> "\n"
<> dataBody
<> reqheaders
<> " , method: '" <> decodeUtf8 method <> "'\n"
<> " });\n"
<> "}\n"
where argsStr = T.intercalate ", " args
args = http
++ captures
++ map (view $ queryArgName . argPath) queryparams
++ body
++ map ( toValidFunctionName
. (<>) "header"
. view (headerArg . argPath)
) hs
http = case T.length (serviceName ngOptions) of
0 -> ["$http"]
_ -> []
captures = map (view argPath . captureArg)
. filter isCapture
$ req ^. reqUrl . path
hs = req ^. reqHeaders
queryparams = req ^.. reqUrl.queryStr.traverse
body = if isJust (req ^. reqBody)
then [requestBody opts]
else []
dataBody =
if isJust (req ^. reqBody)
then " , data: JSON.stringify(body)\n" <>
" , contentType: 'application/json'\n"
else ""
reqheaders =
if null hs
then ""
else " , headers: { " <> headersStr <> " }\n"
where
headersStr = T.intercalate ", " $ map headerStr hs
headerStr header = "\"" <>
header ^. headerArg . argPath <>
"\": " <> toJSHeader header
namespace =
if hasService
then ""
else if hasNoModule
then "var "
else (moduleName opts) <> "."
where
hasNoModule = moduleName opts == ""
hasService = serviceName ngOptions /= ""
fsep = if hasService then ":" else " ="
fname = namespace <> (toValidFunctionName (functionNameBuilder opts $ req ^. reqFuncName))
method = req ^. reqMethod
url = if url' == "'" then "'/'" else url'
url' = "'"
<> urlPrefix opts
<> urlArgs
<> queryArgs
urlArgs = jsSegments
$ req ^.. reqUrl.path.traverse
queryArgs = if null queryparams
then ""
else " + '?" <> jsParams queryparams