{-#LANGUAGE OverloadedStrings #-}
module Servant.JS.Axios where
import           Prelude ()
import           Prelude.Compat
import           Control.Lens
import           Data.Maybe (isJust)
import           Data.Text (Text)
import           Data.Text.Encoding (decodeUtf8)
import qualified Data.Text as T
import           Servant.Foreign
import           Servant.JS.Internal
data AxiosOptions = AxiosOptions
  { 
    
    withCredentials :: !Bool
    
  , xsrfCookieName  :: !(Maybe Text)
    
  , xsrfHeaderName  :: !(Maybe Text)
  }
defAxiosOptions :: AxiosOptions
defAxiosOptions = AxiosOptions
  { withCredentials = False
  , xsrfCookieName = Nothing
  , xsrfHeaderName = Nothing
  }
axios :: AxiosOptions -> JavaScriptGenerator
axios aopts = axiosWith aopts defCommonGeneratorOptions
axiosWith :: AxiosOptions -> CommonGeneratorOptions -> JavaScriptGenerator
axiosWith aopts opts = T.intercalate "\n\n" . map (generateAxiosJSWith aopts opts)
generateAxiosJS :: AxiosOptions -> AjaxReq -> Text
generateAxiosJS aopts = generateAxiosJSWith aopts defCommonGeneratorOptions
generateAxiosJSWith :: AxiosOptions -> CommonGeneratorOptions -> AjaxReq -> Text
generateAxiosJSWith aopts opts req = "\n" <>
    fname <> " = function(" <> argsStr <> ")\n"
 <> "{\n"
 <> "  return axios({ url: " <> url <> "\n"
 <> "    , method: '" <> method <> "'\n"
 <> dataBody
 <> reqheaders
 <> withCreds
 <> xsrfCookie
 <> xsrfHeader
 <> "    });\n"
 <> "}\n"
  where argsStr = T.intercalate ", " args
        args = captures
            ++ map (view $ queryArgName . argPath) queryparams
            ++ body
            ++ map ( toValidFunctionName
                   . (<>) "header"
                   . view (headerArg . argPath)
                   ) hs
        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: body\n" <>
                 "    , responseType: 'json'\n"
            else ""
        withCreds =
          if withCredentials aopts
            then "    , withCredentials: true\n"
            else ""
        xsrfCookie =
          case xsrfCookieName aopts of
            Just name -> "    , xsrfCookieName: '" <> name <> "'\n"
            Nothing   -> ""
        xsrfHeader =
          case xsrfHeaderName aopts of
            Just name -> "    , xsrfHeaderName: '" <> name <> "'\n"
            Nothing   -> ""
        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 hasNoModule
                  then "var "
                  else (moduleName opts) <> "."
               where
                  hasNoModule = moduleName opts == ""
        fname = namespace <> (toValidFunctionName (functionNameBuilder opts $ req ^. reqFuncName))
        method = T.toLower . decodeUtf8 $ 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