Add tests for ToValidFunctionName

This commit is contained in:
Dario Bertini 2016-10-08 16:10:59 +01:00
parent 3daa2adea5
commit 8091654ab2
No known key found for this signature in database
GPG key ID: 7B498306B3BF75A0
3 changed files with 25 additions and 6 deletions

View file

@ -93,4 +93,5 @@ test-suite spec
, servant , servant
, servant-js , servant-js
, text , text
, QuickCheck
default-language: Haskell2010 default-language: Haskell2010

View file

@ -1,5 +1,4 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
module Servant.JS.Internal module Servant.JS.Internal
( JavaScriptGenerator ( JavaScriptGenerator
@ -116,12 +115,11 @@ toValidFunctionName t =
setFirstChar x `T.cons` T.filter remainder xs setFirstChar x `T.cons` T.filter remainder xs
Nothing -> "_" Nothing -> "_"
where where
setFirstChar c = if firstChar c then c else '_' setFirstChar c = if Set.member c firstLetterOK then c else '_'
firstChar c = prefixOK c || Set.member c firstLetterOK remainder c = Set.member c remainderOK
remainder c = prefixOK c || Set.member c remainderOK
prefixOK c = c `elem` ['$','_']
firstLetterOK = (filterBmpChars $ mconcat firstLetterOK = (filterBmpChars $ mconcat
[ Set.lowercaseLetter [ Set.fromDistinctAscList "$_"
, Set.lowercaseLetter
, Set.uppercaseLetter , Set.uppercaseLetter
, Set.titlecaseLetter , Set.titlecaseLetter
, Set.modifierLetter , Set.modifierLetter

View file

@ -15,10 +15,14 @@ import Data.Monoid.Compat ((<>))
import Data.Proxy import Data.Proxy
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as T import qualified Data.Text as T
import Language.ECMAScript3.Lexer (identifier)
import Language.ECMAScript3.Parser (program, parse) import Language.ECMAScript3.Parser (program, parse)
import Prelude () import Prelude ()
import Prelude.Compat import Prelude.Compat
import Test.Hspec hiding (shouldContain, shouldNotContain) import Test.Hspec hiding (shouldContain, shouldNotContain)
import Test.QuickCheck (Arbitrary (..),
choose, listOf,
property)
import Servant.API.Internal.Test.ComprehensiveAPI import Servant.API.Internal.Test.ComprehensiveAPI
import Servant.API.ContentTypes import Servant.API.ContentTypes
@ -97,6 +101,7 @@ spec = describe "Servant.JQuery" $ do
angularSpec Angular angularSpec Angular
axiosSpec axiosSpec
--angularSpec AngularCustom --angularSpec AngularCustom
internalSpec
shouldContain :: Text -> Text -> Expectation shouldContain :: Text -> Text -> Expectation
a `shouldContain` b = shouldSatisfy a (T.isInfixOf b) a `shouldContain` b = shouldSatisfy a (T.isInfixOf b)
@ -152,6 +157,21 @@ angularSpec test = describe specLabel $ do
ngOpts = NG.defAngularOptions { NG.serviceName = testName } ngOpts = NG.defAngularOptions { NG.serviceName = testName }
genJS req = NG.angularService ngOpts req genJS req = NG.angularService ngOpts req
instance Arbitrary T.Text where
-- Our arbitrary instance is generating only ASCII, since language-ecmascript lexer
-- is currently (October 2016) still a bit naïve
arbitrary = fmap T.pack $ listOf $ choose (minBound, '\127')
shrink xs = T.pack <$> shrink (T.unpack xs)
internalSpec :: Spec
internalSpec = describe "Internal" $ do
it "should generate only valid javascript identifiers for any ASCII route" $ do
let parseIdentifier = fmap (T.pack . filter (< '\65536')) . parse identifier ""
property $ \x -> let valid = toValidFunctionName x in
Right valid == parseIdentifier valid
it "should generate a valid javascript identifier when supplied with hyphens, unicode whitespace, non-bmp unicode" $ do
toValidFunctionName "a_--a\66352b\6158c\65075" `shouldBe` "a_abc\65075"
generateJSSpec :: TestNames -> (AjaxReq -> Text) -> Spec generateJSSpec :: TestNames -> (AjaxReq -> Text) -> Spec
generateJSSpec n gen = describe specLabel $ do generateJSSpec n gen = describe specLabel $ do
let parseFromText = parse program "" let parseFromText = parse program ""