JsImport now distinguishes between default and named imports.

This commit is contained in:
Martin Sosic 2020-08-25 12:06:46 +02:00
parent c825f8f811
commit 3483582fc6
5 changed files with 24 additions and 18 deletions

View File

@ -7,7 +7,7 @@ module Generator.WebAppGenerator.PageGenerator
, generatePageStyle
) where
import Data.Maybe (fromJust)
import Data.Maybe (fromJust, fromMaybe)
import Data.Aeson ((.=), object)
import qualified Data.Aeson as Aeson
import qualified System.FilePath as FP
@ -44,7 +44,7 @@ generatePage wasp page =
generatePageComponent :: Wasp -> WP.Page -> FileDraft
generatePageComponent wasp page = Common.makeTemplateFD tmplPath dstPath (Just templateData)
where
tmplPath = (SP.fromPathRelFile [P.relfile|src/_Page.js|]) :: Path (Rel Common.WebAppTemplatesDir) File
tmplPath = SP.fromPathRelFile [P.relfile|src/_Page.js|] :: Path (Rel Common.WebAppTemplatesDir) File
dstPath = Common.webAppSrcDirInWebAppRootDir </> pageDirPathInSrc
</> (fromJust $ SP.parseRelFile $ (WP.pageName page) ++ ".js")
templateData = object $
@ -93,11 +93,11 @@ generatePageComponent wasp page = Common.makeTemplateFD tmplPath dstPath (Just t
toJsImportData :: WJsImport.JsImport -> Aeson.Value
toJsImportData jsImport = object
[ "what" .= WJsImport.jsImportWhat jsImport
[ "what" .= fromMaybe (error "Expected default JS import.") (WJsImport.jsImportDefaultImport jsImport)
-- NOTE: Here we assume that "from" is relative to external code dir path.
-- If this part will be reused, consider externalizing this assumption, so we don't have it on multiple places.
, "from" .= (buildImportPathFromPathInSrc $ extCodeDirInWebAppSrcDir
</> (castRelPathFromSrcToGenExtCodeDir $ WJsImport.jsImportFrom jsImport))
, "from" .= buildImportPathFromPathInSrc
(extCodeDirInWebAppSrcDir </> castRelPathFromSrcToGenExtCodeDir (WJsImport.jsImportFrom jsImport))
]
data PageDir

View File

@ -17,9 +17,15 @@ jsImport :: Parser Wasp.JsImport.JsImport
jsImport = do
L.whiteSpace
_ <- L.reserved L.reservedNameImport
what <- L.identifier <|> L.braces L.identifier
-- For now we support only default import or one named import.
(defaultImport, namedImports) <- ((\i -> (Just i, [])) <$> L.identifier)
<|> ((\i -> (Nothing, [i])) <$> L.braces L.identifier)
_ <- L.reserved L.reservedNameFrom
-- TODO: For now we only support double quotes here, we should also support single quotes.
-- We would need to write this from scratch, with single quote escaping enabled.
from <- Parser.ExternalCode.extCodeFilePathString
return Wasp.JsImport.JsImport { Wasp.JsImport.jsImportWhat = what, Wasp.JsImport.jsImportFrom = from }
return Wasp.JsImport.JsImport
{ Wasp.JsImport.jsImportDefaultImport = defaultImport
, Wasp.JsImport.jsImportNamedImports = namedImports
, Wasp.JsImport.jsImportFrom = from
}

View File

@ -11,13 +11,14 @@ import ExternalCode (SourceExternalCodeDir)
-- | Represents javascript import -> "import <what> from <from>".
data JsImport = JsImport
{ -- ^ Currently this will always be an identifier, coming either from default or single named import.
jsImportWhat :: !String
{ jsImportDefaultImport :: !(Maybe String)
, jsImportNamedImports :: ![String]
, jsImportFrom :: !(Path (Rel SourceExternalCodeDir) File)
} deriving (Show, Eq)
instance ToJSON JsImport where
toJSON jsImport = object
[ "what" .= jsImportWhat jsImport
, "from" .= (SP.toFilePath $ jsImportFrom jsImport)
[ "defaultImport" .= jsImportDefaultImport jsImport
, "namedImports" .= jsImportNamedImports jsImport
, "from" .= SP.toFilePath (jsImportFrom jsImport)
]

View File

@ -15,19 +15,19 @@ spec_parseJsImport :: Spec
spec_parseJsImport = do
it "Parses external code js import with default import correctly" $ do
runWaspParser jsImport "import something from \"@ext/some/file.js\""
`shouldBe` Right (Wasp.JsImport "something" (SP.fromPathRelFile [P.relfile|some/file.js|]))
`shouldBe` Right (Wasp.JsImport (Just "something") [] (SP.fromPathRelFile [P.relfile|some/file.js|]))
it "Parses correctly when there is whitespace up front" $ do
runWaspParser jsImport " import something from \"@ext/some/file.js\""
`shouldBe` Right (Wasp.JsImport "something" (SP.fromPathRelFile [P.relfile|some/file.js|]))
`shouldBe` Right (Wasp.JsImport (Just "something") [] (SP.fromPathRelFile [P.relfile|some/file.js|]))
it "Parses correctly when 'from' is part of WHAT part" $ do
runWaspParser jsImport "import somethingfrom from \"@ext/some/file.js\""
`shouldBe` Right (Wasp.JsImport "somethingfrom" (SP.fromPathRelFile [P.relfile|some/file.js|]))
`shouldBe` Right (Wasp.JsImport (Just "somethingfrom") [] (SP.fromPathRelFile [P.relfile|some/file.js|]))
it "Parses correctly when 'what' is a single named export" $ do
runWaspParser jsImport "import { something } from \"@ext/some/file.js\""
`shouldBe` Right (Wasp.JsImport "something" (SP.fromPathRelFile [P.relfile|some/file.js|]))
`shouldBe` Right (Wasp.JsImport Nothing ["something"] (SP.fromPathRelFile [P.relfile|some/file.js|]))
it "For now we don't support multiple named exports in WHAT part" $ do
isLeft (runWaspParser jsImport "import { foo, bar } from \"@ext/some/file.js\"")

View File

@ -21,8 +21,7 @@ spec_parseWasp =
isLeft (parseWasp "hoho") `shouldBe` True
before (readFile "test/Parser/valid.wasp") $ do
it "When given a valid wasp source, should return correct\
\ Wasp" $ \wasp -> do
it "When given a valid wasp source, should return correct Wasp" $ \wasp -> do
parseWasp wasp
`shouldBe`
Right (fromWaspElems
@ -120,5 +119,5 @@ spec_parseWasp =
]
}
]
`setJsImports` [ JsImport "something" (SP.fromPathRelFile [P.relfile|some/file|]) ]
`setJsImports` [ JsImport (Just "something") [] (SP.fromPathRelFile [P.relfile|some/file|]) ]
)