Skip to content
Draft
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
4 changes: 2 additions & 2 deletions waspc/cli/src/Wasp/Cli/Command/BuildStart/ArgumentsParser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ where

import qualified Options.Applicative as Opt
import Wasp.Cli.Util.EnvVarArgument (envVarReader)
import Wasp.Cli.Util.PathArgument (FilePathArgument, filePathReader)
import Wasp.Cli.Util.PathArgument (FilePathArgument)
import Wasp.Env (EnvVar)

data BuildStartArgs = BuildStartArgs
Expand Down Expand Up @@ -44,7 +44,7 @@ buildStartArgsParser =

makeEnvironmentFileParser :: String -> String -> Opt.Parser FilePathArgument
makeEnvironmentFileParser targetName longOptionName =
Opt.option filePathReader $
Opt.strOption $
Opt.long longOptionName
<> Opt.metavar "FILE_PATH"
<> Opt.help ("Load environment variables for the " <> targetName <> " from a file (can be used multiple times)")
Expand Down
3 changes: 3 additions & 0 deletions waspc/cli/src/Wasp/Cli/Command/CreateNewProject.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ import Wasp.Cli.Command.CreateNewProject.StarterTemplates
)
import Wasp.Cli.Command.CreateNewProject.StarterTemplates.Bundled (createProjectOnDiskFromBundledTemplate)
import Wasp.Cli.Command.CreateNewProject.StarterTemplates.GhReleaseArchive (createProjectOnDiskFromGhReleaseArchiveTemplate)
import Wasp.Cli.Command.CreateNewProject.StarterTemplates.Local (createProjectOnDiskFromLocalTemplate)
import Wasp.Cli.Command.Message (cliSendMessageC)
import Wasp.Cli.Util.Parser (parseArguments)
import qualified Wasp.Message as Msg
Expand Down Expand Up @@ -53,6 +54,8 @@ createProjectOnDisk
createProjectOnDiskFromGhReleaseArchiveTemplate absWaspProjectDir projectName appName ghRepoRef archiveName' archivePath'
BundledStarterTemplate {bundledPath = bundledPath'} ->
liftIO $ createProjectOnDiskFromBundledTemplate absWaspProjectDir projectName appName bundledPath'
LocalStarterTemplate {localPath = localPath'} ->
liftIO $ createProjectOnDiskFromLocalTemplate absWaspProjectDir projectName appName localPath'
AiGeneratedStarterTemplate ->
AI.createNewProjectInteractiveOnDisk absWaspProjectDir appName

Expand Down
30 changes: 26 additions & 4 deletions waspc/cli/src/Wasp/Cli/Command/CreateNewProject/ArgumentsParser.hs
Original file line number Diff line number Diff line change
@@ -1,24 +1,38 @@
module Wasp.Cli.Command.CreateNewProject.ArgumentsParser
( NewProjectArgs (..),
TemplateArg (..),
newProjectArgsParser,
)
where

import Control.Applicative (optional, (<|>))
import qualified Options.Applicative as Opt
import Wasp.Cli.Util.PathArgument (DirPathArgument)

data NewProjectArgs = NewProjectArgs
{ _projectName :: Maybe String,
_templateName :: Maybe String
_templateArg :: Maybe TemplateArg
}

data TemplateArg
= NamedTemplate String
| CustomTemplate DirPathArgument

newProjectArgsParser :: Opt.Parser NewProjectArgs
newProjectArgsParser =
NewProjectArgs
<$> Opt.optional projectNameParser
<*> Opt.optional templateNameParser
<$> optional projectNameParser
<*> optional templateArgParser
where
projectNameParser :: Opt.Parser String
projectNameParser = Opt.strArgument $ Opt.metavar "PROJECT_NAME"
projectNameParser =
Opt.strArgument $
Opt.metavar "PROJECT_NAME"

templateArgParser :: Opt.Parser TemplateArg
templateArgParser =
(NamedTemplate <$> templateNameParser)
<|> (CustomTemplate <$> customTemplatePathParser)

templateNameParser :: Opt.Parser String
templateNameParser =
Expand All @@ -27,3 +41,11 @@ newProjectArgsParser =
<> Opt.short 't'
<> Opt.metavar "TEMPLATE_NAME"
<> Opt.help "Template to use for the new project"

customTemplatePathParser :: Opt.Parser DirPathArgument
customTemplatePathParser =
Opt.strOption $
Opt.long "custom-template"
-- This is an internal option only intended for internal testing usage,
-- so we don't want to show help for it.
<> Opt.internal
Original file line number Diff line number Diff line change
Expand Up @@ -13,21 +13,25 @@ import Data.List (intercalate)
import Data.List.NonEmpty (fromList)
import Data.Maybe (isNothing)
import Path.IO (doesDirExist)
import StrongPath (Abs, Dir, Path')
import StrongPath (Abs, Dir, Path', fromAbsDir)
import StrongPath.Path (toPathAbsDir)
import System.Directory (doesDirectoryExist)
import Wasp.Analyzer.Parser (isValidWaspIdentifier)
import Wasp.Cli.Command (Command)
import Wasp.Cli.Command.CreateNewProject.ArgumentsParser
( NewProjectArgs (..),
TemplateArg (..),
)
import Wasp.Cli.Command.CreateNewProject.AvailableTemplates (defaultStarterTemplate)
import Wasp.Cli.Command.CreateNewProject.Common (throwProjectCreationError)
import Wasp.Cli.Command.CreateNewProject.StarterTemplates
( StarterTemplate,
( StarterTemplate (LocalStarterTemplate, localPath),
findTemplateByString,
)
import Wasp.Cli.FileSystem (getAbsPathToDirInCwd)
import qualified Wasp.Cli.Interactive as Interactive
import Wasp.Cli.Util.PathArgument (DirPathArgument)
import qualified Wasp.Cli.Util.PathArgument as PathArgument
import Wasp.Project.Common (WaspProjectDir)
import Wasp.Util (indent, kebabToCamelCase, whenM)

Expand All @@ -50,12 +54,14 @@ instance Show NewProjectAppName where

{-
There are two ways of getting the project description:

1. From CLI arguments

wasp new <project-name> [-t <template-name>]
wasp new <project-name> [-t <template-name> | -c <template-dir>]

- Project name is required.
- Template name is optional, if not provided, we use the default template.
- Template name/dir is optional, if not provided, we use the default template.

2. Interactively

wasp new
Expand All @@ -64,19 +70,21 @@ instance Show NewProjectAppName where
- Template name is required, we ask the user to choose from available templates.
-}
obtainNewProjectDescription :: NewProjectArgs -> [StarterTemplate] -> Command NewProjectDescription
obtainNewProjectDescription NewProjectArgs {_projectName = projectNameArg, _templateName = templateNameArg} starterTemplates = do
obtainNewProjectDescription NewProjectArgs {_projectName = projectNameArg, _templateArg = templateArg} starterTemplates = do
projectName <- maybe askForName return projectNameArg
appName <-
either throwProjectCreationError pure $
parseWaspProjectNameIntoAppName projectName

let prefersInteractive = isNothing projectNameArg
getFallbackTemplate =
if prefersInteractive
then askForTemplate starterTemplates
else return defaultStarterTemplate

template <- maybe getFallbackTemplate (findTemplateOrThrow starterTemplates) templateNameArg
template <- case templateArg of
Just (NamedTemplate templateName) -> findNamedTemplate starterTemplates templateName
Just (CustomTemplate templatePath) -> findCustomTemplate templatePath
Nothing ->
if prefersInteractive
then askForTemplate starterTemplates
else return defaultStarterTemplate

absWaspProjectDir <- obtainAvailableProjectDirPath projectName
return $ mkNewProjectDescription projectName appName absWaspProjectDir template
Expand All @@ -102,17 +110,32 @@ parseWaspProjectNameIntoAppName projectName
where
appName = kebabToCamelCase projectName

findTemplateOrThrow :: [StarterTemplate] -> String -> Command StarterTemplate
findTemplateOrThrow availableTemplates templateName = case findTemplateByString availableTemplates templateName of
Just template -> return template
Nothing -> throwProjectCreationError invalidTemplateNameError
findNamedTemplate :: [StarterTemplate] -> String -> Command StarterTemplate
findNamedTemplate availableTemplates templateName =
maybe throwInvalidTemplateNameError return $
findTemplateByString availableTemplates templateName
where
throwInvalidTemplateNameError =
throwProjectCreationError $
"The template "
<> show templateName
<> " doesn't exist. Available starter templates are: "
<> intercalate ", " (map show availableTemplates)
<> "."

findCustomTemplate :: DirPathArgument -> Command StarterTemplate
findCustomTemplate templatePath = do
absTemplatePath <- liftIO $ PathArgument.getDirPath templatePath
templateExists <- liftIO $ doesDirectoryExist $ fromAbsDir absTemplatePath
if templateExists
then return $ LocalStarterTemplate {localPath = absTemplatePath}
else throwInvalidCustomTemplatePathError absTemplatePath
where
invalidTemplateNameError =
"The template '"
<> templateName
<> "' doesn't exist. Available starter templates are: "
<> intercalate ", " (map show availableTemplates)
<> "."
throwInvalidCustomTemplatePathError absTemplatePath =
throwProjectCreationError $
"The directory "
<> show (fromAbsDir absTemplatePath)
<> " doesn't exist or can't be found."

obtainAvailableProjectDirPath :: String -> Command (Path' Abs (Dir WaspProjectDir))
obtainAvailableProjectDirPath projectName = do
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ where

import Data.Foldable (find)
import Data.Text (Text)
import StrongPath (Dir', File', Path, Path', Rel, Rel', System, reldir, (</>))
import StrongPath (Abs, Dir', File', Path, Path', Rel, Rel', System, reldir, (</>))
import qualified StrongPath as SP
import qualified Wasp.Cli.GithubRepo as GhRepo
import qualified Wasp.Cli.Interactive as Interactive
Expand All @@ -36,6 +36,8 @@ data StarterTemplate
{ bundledPath :: Path' Rel' Dir',
metadata :: !TemplateMetadata
}
| -- | Template from disk, that the user has locally extracted.
LocalStarterTemplate {localPath :: !(Path' Abs Dir')}
| -- | Template that will be dynamically generated by Wasp AI based on user's input.
AiGeneratedStarterTemplate

Expand All @@ -49,13 +51,15 @@ data TemplateMetadata = TemplateMetadata
instance Show StarterTemplate where
show (GhRepoReleaseArchiveTemplate {metadata = metadata'}) = _name metadata'
show (BundledStarterTemplate {metadata = metadata'}) = _name metadata'
show (LocalStarterTemplate _) = "custom"
show AiGeneratedStarterTemplate = "ai-generated"

instance Interactive.IsOption StarterTemplate where
showOption = show

showOptionDescription (GhRepoReleaseArchiveTemplate {metadata = metadata'}) = Just $ _description metadata'
showOptionDescription (BundledStarterTemplate {metadata = metadata'}) = Just $ _description metadata'
showOptionDescription (LocalStarterTemplate _) = Just "A custom starter template from a local path."
showOptionDescription AiGeneratedStarterTemplate =
Just "🤖 Describe an app in a couple of sentences and have Wasp AI generate initial code for you. (experimental)"

Expand All @@ -68,6 +72,7 @@ getTemplateStartingInstructions :: String -> StarterTemplate -> String
getTemplateStartingInstructions projectDirName = \case
GhRepoReleaseArchiveTemplate {metadata = metadata'} -> _buildStartingInstructions metadata' projectDirName
BundledStarterTemplate {metadata = metadata'} -> _buildStartingInstructions metadata' projectDirName
LocalStarterTemplate _ -> "Check the starter's documentation for guidance on how to start your app."
AiGeneratedStarterTemplate ->
unlines
[ styleText $ "To run your new app, do:",
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
module Wasp.Cli.Command.CreateNewProject.StarterTemplates.Local
( createProjectOnDiskFromLocalTemplate,
)
where

import Path.IO (copyDirRecur)
import StrongPath (Abs, Dir, Dir', Path')
import StrongPath.Path (toPathAbsDir)
import Wasp.Cli.Command.CreateNewProject.ProjectDescription (NewProjectAppName, NewProjectName)
import Wasp.Cli.Command.CreateNewProject.StarterTemplates.Templating (replaceTemplatePlaceholdersInTemplateFiles)
import Wasp.Project (WaspProjectDir)

createProjectOnDiskFromLocalTemplate ::
Path' Abs (Dir WaspProjectDir) -> NewProjectName -> NewProjectAppName -> Path' Abs Dir' -> IO ()
createProjectOnDiskFromLocalTemplate absWaspProjectDir projectName appName templatePath = do
copyDirRecur (toPathAbsDir templatePath) (toPathAbsDir absWaspProjectDir)
replaceTemplatePlaceholdersInTemplateFiles appName projectName absWaspProjectDir
22 changes: 15 additions & 7 deletions waspc/cli/src/Wasp/Cli/Util/PathArgument.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,13 @@
module Wasp.Cli.Util.PathArgument
( FilePathArgument,
DirPathArgument,
getFilePath,
filePathReader,
getDirPath,
)
where

import Options.Applicative (ReadM, str)
import StrongPath (Abs, File', Path')
import Data.String (IsString (..))
import StrongPath (Abs, Dir', File', Path', parseAbsDir)
import StrongPath.FilePath (parseAbsFile)
import System.Directory (makeAbsolute)

Expand All @@ -16,11 +17,18 @@ import System.Directory (makeAbsolute)
-- in the meantime; so we make these types opaque until we have access to the IO
-- monad.

newtype FilePathArgument = FilePathArgument FilePath
deriving (Show, Eq)
newtype FilePathArgument = FilePathArgument FilePath deriving (Show, Eq)

filePathReader :: ReadM FilePathArgument
filePathReader = FilePathArgument <$> str
newtype DirPathArgument = DirPathArgument FilePath deriving (Show, Eq)

instance IsString FilePathArgument where
fromString = FilePathArgument . fromString

instance IsString DirPathArgument where
fromString = DirPathArgument . fromString

getFilePath :: FilePathArgument -> IO (Path' Abs File')
getFilePath (FilePathArgument filePath) = makeAbsolute filePath >>= parseAbsFile

getDirPath :: DirPathArgument -> IO (Path' Abs Dir')
getDirPath (DirPathArgument dirPath) = makeAbsolute dirPath >>= parseAbsDir
1 change: 1 addition & 0 deletions waspc/waspc.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -591,6 +591,7 @@ library cli-lib
Wasp.Cli.Command.CreateNewProject.StarterTemplates
Wasp.Cli.Command.CreateNewProject.StarterTemplates.Bundled
Wasp.Cli.Command.CreateNewProject.StarterTemplates.GhReleaseArchive
Wasp.Cli.Command.CreateNewProject.StarterTemplates.Local
Wasp.Cli.Command.CreateNewProject.StarterTemplates.Templating
Wasp.Cli.Command.Db
Wasp.Cli.Command.Db.Migrate
Expand Down
Loading