servant/servant-js/src/Servant/JS/Internal.hs

191 lines
5.4 KiB
Haskell
Raw Normal View History

2016-02-17 22:47:30 +01:00
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
module Servant.JS.Internal
( JavaScriptGenerator
, CommonGeneratorOptions(..)
, defCommonGeneratorOptions
, AjaxReq
, jsSegments
, segmentToStr
, segmentTypeToStr
, jsParams
, jsGParams
, paramToStr
, toValidFunctionName
, toJSHeader
-- re-exports
, (:<|>)(..)
, (:>)
, defReq
, reqHeaders
, HasForeign(..)
, HasForeignType(..)
2016-02-17 22:47:30 +01:00
, HasNoForeignType
, GenerateList(..)
, NoTypes
, HeaderArg
, ArgType(..)
, HeaderArg(..)
2016-02-17 22:47:30 +01:00
, QueryArg(..)
, Req(..)
, Segment(..)
, SegmentType(..)
, Url(..)
, Path
, ForeignType(..)
, Arg(..)
, FunctionName(..)
, PathSegment(..)
, concatCase
, snakeCase
, camelCase
, ReqBody
, JSON
, FormUrlEncoded
, Post
, Get
, Raw
, Header
2015-09-23 18:26:05 +02:00
) where
2016-02-17 22:47:30 +01:00
import Control.Lens
import qualified Data.CharSet as Set
import qualified Data.CharSet.Unicode.Category as Set
import Data.Monoid
import qualified Data.Text as T
2015-10-02 13:59:54 +02:00
import Data.Text (Text)
import Servant.Foreign
type AjaxReq = Req
-- A 'JavascriptGenerator' just takes the data found in the API type
2015-10-02 13:59:54 +02:00
-- for each endpoint and generates Javascript code in a Text. Several
-- generators are available in this package.
2015-10-02 13:59:54 +02:00
type JavaScriptGenerator = [Req] -> Text
2015-01-03 18:52:18 +01:00
-- | This structure is used by specific implementations to let you
-- customize the output
data CommonGeneratorOptions = CommonGeneratorOptions
{
functionNameBuilder :: FunctionName -> Text
-- ^ function generating function names
, requestBody :: Text
-- ^ name used when a user want to send the request body
-- (to let you redefine it)
, successCallback :: Text
-- ^ name of the callback parameter when the request was successful
, errorCallback :: Text
-- ^ name of the callback parameter when the request reported an error
, moduleName :: Text
-- ^ namespace on which we define the foreign function (empty mean local var)
, urlPrefix :: Text
-- ^ a prefix we should add to the Url in the codegen
}
-- | Default options.
--
-- @
-- > defCommonGeneratorOptions = CommonGeneratorOptions
-- > { functionNameBuilder = camelCase
-- > , requestBody = "body"
-- > , successCallback = "onSuccess"
-- > , errorCallback = "onError"
-- > , moduleName = ""
-- > , urlPrefix = ""
-- > }
-- @
defCommonGeneratorOptions :: CommonGeneratorOptions
defCommonGeneratorOptions = CommonGeneratorOptions
{
functionNameBuilder = camelCase
, requestBody = "body"
, successCallback = "onSuccess"
, errorCallback = "onError"
, moduleName = ""
, urlPrefix = ""
}
-- | Attempts to reduce the function name provided to that allowed by @'Foreign'@.
--
-- https://mathiasbynens.be/notes/javascript-identifiers
-- Couldn't work out how to handle zero-width characters.
--
-- @TODO: specify better default function name, or throw error?
2015-10-02 13:59:54 +02:00
toValidFunctionName :: Text -> Text
toValidFunctionName t =
case T.uncons t of
Just (x,xs) ->
setFirstChar x `T.cons` T.filter remainder xs
2015-10-02 13:59:54 +02:00
Nothing -> "_"
where
setFirstChar c = if firstChar c then c else '_'
2015-10-04 23:32:31 +02:00
firstChar c = prefixOK c || Set.member c firstLetterOK
remainder c = prefixOK c || Set.member c remainderOK
prefixOK c = c `elem` ['$','_']
2015-10-04 23:32:31 +02:00
firstLetterOK = mconcat
[ Set.lowercaseLetter
, Set.uppercaseLetter
, Set.titlecaseLetter
, Set.modifierLetter
, Set.otherLetter
, Set.letterNumber
2015-10-04 23:32:31 +02:00
]
remainderOK = firstLetterOK
2015-10-04 23:32:31 +02:00
<> mconcat
[ Set.nonSpacingMark
, Set.spacingCombiningMark
, Set.decimalNumber
, Set.connectorPunctuation
]
2015-10-02 13:59:54 +02:00
toJSHeader :: HeaderArg -> Text
2016-02-17 22:47:30 +01:00
toJSHeader (HeaderArg n)
= toValidFunctionName ("header" <> n ^. aName . _PathSegment)
toJSHeader (ReplaceHeaderArg n p)
2015-10-02 13:59:54 +02:00
| pn `T.isPrefixOf` p = pv <> " + \"" <> rp <> "\""
| pn `T.isSuffixOf` p = "\"" <> rp <> "\" + " <> pv
| pn `T.isInfixOf` p = "\"" <> (T.replace pn ("\" + " <> pv <> " + \"") p)
<> "\""
| otherwise = p
where
2016-02-17 22:47:30 +01:00
pv = toValidFunctionName ("header" <> n ^. aName . _PathSegment)
pn = "{" <> n ^. aName . _PathSegment <> "}"
2015-10-02 13:59:54 +02:00
rp = T.replace pn "" p
2015-10-02 13:59:54 +02:00
jsSegments :: [Segment] -> Text
2015-01-03 18:52:18 +01:00
jsSegments [] = ""
2015-10-02 13:59:54 +02:00
jsSegments [x] = "/" <> segmentToStr x False
jsSegments (x:xs) = "/" <> segmentToStr x True <> jsSegments xs
2015-01-03 18:52:18 +01:00
2015-10-02 13:59:54 +02:00
segmentToStr :: Segment -> Bool -> Text
segmentToStr (Segment st) notTheEnd =
segmentTypeToStr st <> if notTheEnd then "" else "'"
2015-01-03 18:52:18 +01:00
2015-10-02 13:59:54 +02:00
segmentTypeToStr :: SegmentType -> Text
2016-02-17 22:47:30 +01:00
segmentTypeToStr (Static s) = s ^. _PathSegment
segmentTypeToStr (Cap s) =
"' + encodeURIComponent(" <> s ^. aName . _PathSegment <> ") + '"
2015-01-03 18:52:18 +01:00
2015-10-02 13:59:54 +02:00
jsGParams :: Text -> [QueryArg] -> Text
jsGParams _ [] = ""
jsGParams _ [x] = paramToStr x False
2015-10-02 13:59:54 +02:00
jsGParams s (x:xs) = paramToStr x True <> s <> jsGParams s xs
2015-01-03 18:52:18 +01:00
2015-10-02 13:59:54 +02:00
jsParams :: [QueryArg] -> Text
2015-01-03 18:52:18 +01:00
jsParams = jsGParams "&"
2015-10-02 13:59:54 +02:00
paramToStr :: QueryArg -> Bool -> Text
paramToStr qarg notTheEnd =
case qarg ^. argType of
Normal -> name
2015-10-02 13:59:54 +02:00
<> "=' + encodeURIComponent("
<> name
<> if notTheEnd then ") + '" else ")"
Flag -> name <> "="
List -> name
2015-10-02 13:59:54 +02:00
<> "[]=' + encodeURIComponent("
<> name
<> if notTheEnd then ") + '" else ")"
2016-02-17 22:47:30 +01:00
where name = qarg ^. argName . aName . _PathSegment