Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
8 changes: 4 additions & 4 deletions bin/src/Main.purs
Original file line number Diff line number Diff line change
Expand Up @@ -641,7 +641,7 @@ main = do
let options = { depsOnly: false, pursArgs: List.toUnfoldable args.pursArgs, jsonErrors: false }
built <- runSpago buildEnv (Build.run options)
when built do
bundleEnv <- runSpago env (mkBundleEnv args)
bundleEnv <- runSpago env (mkBundleEnv args buildEnv)
runSpago bundleEnv Bundle.run
Run args@{ selectedPackage, ensureRanges, pure } -> do
{ env, fetchOpts } <- mkFetchEnv { packages: mempty, selectedPackage, ensureRanges, pure, testDeps: false, isRepl: false, migrateConfig, offline }
Expand Down Expand Up @@ -719,8 +719,8 @@ main = do
Left err -> die [ "Could not parse provided set version. Error:", show err ]
Right v -> pure v

mkBundleEnv :: forall a. BundleArgs -> Spago (Fetch.FetchEnv a) (Bundle.BundleEnv ())
mkBundleEnv bundleArgs = do
mkBundleEnv :: forall a b. BundleArgs -> Build.BuildEnv b -> Spago (Fetch.FetchEnv a) (Bundle.BundleEnv ())
mkBundleEnv bundleArgs { dependencies, purs } = do
{ workspace, logOptions, rootPath } <- ask
logDebug $ "Bundle args: " <> show bundleArgs

Expand Down Expand Up @@ -777,7 +777,7 @@ mkBundleEnv bundleArgs = do
}
}
esbuild <- Esbuild.getEsbuild
let bundleEnv = { esbuild, logOptions, rootPath, workspace: newWorkspace, selected, bundleOptions }
let bundleEnv = { esbuild, logOptions, rootPath, workspace: newWorkspace, selected, bundleOptions, purs, dependencies }
pure bundleEnv

mkRunEnv :: forall a b. RunArgs -> Build.BuildEnv b -> Spago (Fetch.FetchEnv a) (Run.RunEnv ())
Expand Down
1 change: 1 addition & 0 deletions spago.lock
Original file line number Diff line number Diff line change
Expand Up @@ -567,6 +567,7 @@
"http-methods",
"integers",
"json",
"language-cst-parser",
"lists",
"maybe",
"newtype",
Expand Down
1 change: 1 addition & 0 deletions spago.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,7 @@ package:
- http-methods
- integers
- json
- language-cst-parser
- lists
- maybe
- newtype
Expand Down
56 changes: 56 additions & 0 deletions src/Spago/Command/Bundle.purs
Original file line number Diff line number Diff line change
Expand Up @@ -3,14 +3,21 @@ module Spago.Command.Bundle where
import Spago.Prelude

import Data.Array (all, fold, take)
import Data.Array.NonEmpty as NEA
import Data.Map as Map
import Data.String as Str
import Data.String.Utils (startsWith)
import Spago.Cmd as Cmd
import Spago.Command.Build as Build
import Spago.Command.Fetch as Fetch
import Spago.Config (BundlePlatform(..), BundleType(..), Workspace, WorkspacePackage)
import Spago.Esbuild (Esbuild)
import Spago.FS as FS
import Spago.Generated.BuildInfo as BuildInfo
import Spago.Path as Path
import Spago.Purs (Purs, ModuleGraph(..))
import Spago.Purs as Purs
import Spago.Purs.EntryPoint as EntryPoint

type BundleEnv a =
{ esbuild :: Esbuild
Expand All @@ -19,6 +26,8 @@ type BundleEnv a =
, bundleOptions :: BundleOptions
, workspace :: Workspace
, selected :: WorkspacePackage
, purs :: Purs
, dependencies :: Fetch.PackageTransitiveDeps
| a
}

Expand Down Expand Up @@ -86,6 +95,10 @@ run = do
, entrypoint
]

-- Check that the entry module exports a `main` function when bundling an app
when (opts.type == BundleApp) do
validateMainExport opts.module

-- FIXME: remove this after 2024-12-01
whenM (FS.exists $ rootPath </> checkWatermarkMarkerFileName)
$ unless opts.force
Expand Down Expand Up @@ -146,3 +159,46 @@ nodeTargetPolyfill = Str.joinWith ";"
, "const __dirname = __path.dirname(__url.fileURLToPath(import.meta.url))"
, "const __filename=new URL(import.meta.url).pathname"
]

-- | Validate that the entry module declares and exports a `main` function
validateMainExport :: forall a. String -> Spago (BundleEnv a) Unit
validateMainExport moduleName = do
{ rootPath, selected, dependencies } <- ask

let
globs = Build.getBuildGlobs
{ rootPath
, dependencies: Fetch.toAllDependencies dependencies
, depsOnly: false
, withTests: false
, selected: NEA.singleton selected
}

Purs.graph rootPath globs [] >>= case _ of
Left err -> logWarn $ "Could not verify main export: " <> show err
Right (ModuleGraph graph) ->
case Map.lookup moduleName graph of
Nothing ->
die
[ "Cannot bundle app: module " <> moduleName <> " was not found in the build."
, ""
, "Make sure the module exists and is included in your build."
]
Just { path } -> do
sourceCode <- FS.readTextFile (rootPath </> path)
case EntryPoint.hasMainExport sourceCode of
EntryPoint.MainExported -> pure unit
EntryPoint.MainWrongType ->
logWarn "The `main` function does not have the expected type `Effect Unit`. The bundle may not work correctly."
EntryPoint.MainNotDeclared ->
die
[ "Cannot bundle app: module " <> moduleName <> " does not declare a `main` function."
, "If you want to create a bundle without an entry point, use --bundle-type=module instead."
]
EntryPoint.MainNotExported ->
die
[ "Cannot bundle app: module " <> moduleName <> " does not export `main`."
, "Add `main` to the module's export list, remove the explicit export list, or use --bundle-type=module."
]
EntryPoint.ParseError err ->
logDebug $ "Could not verify main export: " <> err
91 changes: 91 additions & 0 deletions src/Spago/Purs/EntryPoint.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,91 @@
module Spago.Purs.EntryPoint
( hasMainExport
, EntryPointCheckResult(..)
) where

import Prelude

import Data.Array as Array
import Data.Array.NonEmpty as NonEmptyArray
import Data.Maybe (Maybe(..))
import Data.Newtype (unwrap)
import Data.Tuple (snd)
import PureScript.CST (RecoveredParserResult(..), parseModule)
import PureScript.CST.Types as CST

data EntryPointCheckResult
= MainExported
| MainWrongType
| MainNotDeclared
| MainNotExported
| ParseError String

-- | Check if the given PureScript source code declares and exports `main`
hasMainExport :: String -> EntryPointCheckResult
hasMainExport sourceCode = case parseModule sourceCode of
ParseSucceeded mod -> checkModule mod
ParseSucceededWithErrors mod _ -> checkModule mod
ParseFailed _ -> ParseError "Failed to parse module"

checkModule :: forall e. CST.Module e -> EntryPointCheckResult
checkModule (CST.Module { header: CST.ModuleHeader { exports }, body: CST.ModuleBody { decls } }) =
let
hasMainDecl = Array.any isMainDecl decls
hasMainSignature = Array.any isMainSignature decls
hasCorrectType = Array.any isMainEffectUnit decls
isExported = case exports of
Nothing -> true -- No explicit exports = everything exported
Just exportList -> Array.any isMainExport (separatedToArray (unwrap exportList).value)
in
if not hasMainDecl then MainNotDeclared
else if not isExported then MainNotExported
-- Only check type if there's a signature; if no signature, we can't verify the type
else if hasMainSignature && not hasCorrectType then MainWrongType
else MainExported

-- | Check for DeclValue or DeclSignature with name "main"
isMainDecl :: forall e. CST.Declaration e -> Boolean
isMainDecl = case _ of
CST.DeclValue { name } -> getIdentName name == "main"
CST.DeclSignature (CST.Labeled { label }) -> getIdentName label == "main"
_ -> false

-- | Check if there's any type signature for "main"
isMainSignature :: forall e. CST.Declaration e -> Boolean
isMainSignature = case _ of
CST.DeclSignature (CST.Labeled { label }) -> getIdentName label == "main"
_ -> false

-- | Check for main :: Effect Unit (unqualified)
isMainEffectUnit :: forall e. CST.Declaration e -> Boolean
isMainEffectUnit = case _ of
CST.DeclSignature
( CST.Labeled
{ label: CST.Name { name: CST.Ident "main" }
, value: CST.TypeApp fn args
}
) -> isEffectConstructor fn && isSingletonUnit args
_ -> false
where
isEffectConstructor = case _ of
CST.TypeConstructor (CST.QualifiedName { name: CST.Proper "Effect" }) -> true
_ -> false
isSingletonUnit args =
NonEmptyArray.length args == 1 && isUnitConstructor (NonEmptyArray.head args)
isUnitConstructor = case _ of
CST.TypeConstructor (CST.QualifiedName { name: CST.Proper "Unit" }) -> true
_ -> false

-- | Check if export is ExportValue with name "main"
isMainExport :: forall e. CST.Export e -> Boolean
isMainExport = case _ of
CST.ExportValue name -> getIdentName name == "main"
_ -> false

-- | Extract the string from a Name Ident
getIdentName :: CST.Name CST.Ident -> String
getIdentName (CST.Name { name: CST.Ident s }) = s

-- | Convert Separated to Array
separatedToArray :: forall a. CST.Separated a -> Array a
separatedToArray (CST.Separated { head, tail }) = Array.cons head (map snd tail)
15 changes: 15 additions & 0 deletions test-fixtures/bundle-main-not-exported-error.txt
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
Reading Spago workspace configuration...

✓ Selecting package to build: test-package

Downloading dependencies...
Building...
Src Lib All
Warnings 0 0 0
Errors 0 0 0

✓ Build succeeded.


✘ Cannot bundle app: module Main does not export `main`.
Add `main` to the module's export list, remove the explicit export list, or use --bundle-type=module.
15 changes: 15 additions & 0 deletions test-fixtures/bundle-no-main-error.txt
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
Reading Spago workspace configuration...

✓ Selecting package to build: test-package

Downloading dependencies...
Building...
Src Lib All
Warnings 0 0 0
Errors 0 0 0

✓ Build succeeded.


✘ Cannot bundle app: module Main does not declare a `main` function.
If you want to create a bundle without an entry point, use --bundle-type=module instead.
31 changes: 31 additions & 0 deletions test/Spago/Bundle.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@ module Test.Spago.Bundle where

import Test.Prelude

import Data.Array as Array
import Data.String as Str
import Spago.Command.Bundle (checkWatermarkMarkerFileName)
import Spago.FS as FS
Expand Down Expand Up @@ -78,6 +79,36 @@ spec = Spec.around withTempDir do
spago [ "bundle" ] >>= shouldBeSuccess
checkBundle (testCwd </> "index.js") (fixture "bundle-default.js")

Spec.it "checks that main is declared and exported when bundling app" \{ spago, fixture, testCwd } -> do
spago [ "init", "--name", "test-package" ] >>= shouldBeSuccess

-- Module without main: app bundle fails, module bundle succeeds
FS.writeTextFile (testCwd </> "src" </> "Main.purs") $ writeMain
[ "import Prelude"
, ""
, "foo :: Int"
, "foo = 42"
]
spago [ "build" ] >>= shouldBeSuccess
spago [ "bundle", "--bundle-type", "app" ] >>= shouldBeFailureErr (fixture "bundle-no-main-error.txt")
spago [ "bundle", "--bundle-type", "module", "--outfile", "bundle.js" ] >>= shouldBeSuccess

-- Module with main not exported: app bundle fails
FS.writeTextFile (testCwd </> "src" </> "Main.purs") $ Array.intercalate "\n"
[ "module Main (foo) where"
, ""
, "import Prelude"
, "import Effect (Effect)"
, ""
, "foo :: Int"
, "foo = 42"
, ""
, "main :: Effect Unit"
, "main = pure unit"
]
spago [ "build" ] >>= shouldBeSuccess
spago [ "bundle", "--bundle-type", "app" ] >>= shouldBeFailureErr (fixture "bundle-main-not-exported-error.txt")

where
-- This is a version of `checkFixture`, but it replaces the "v0" placeholder
-- in the bundle magic marker with the actual current build version. Fixture
Expand Down
Loading