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
2 changes: 2 additions & 0 deletions waspc/.gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -12,3 +12,5 @@ waspc.cabal
.hie/
.bin/
stan.html

*.orig
62 changes: 8 additions & 54 deletions waspc/.hlint.yaml
Original file line number Diff line number Diff line change
@@ -1,14 +1,3 @@
# HLint configuration file
# https://github.com/ndmitchell/hlint
##########################

# This file contains a template configuration file, which is typically
# placed as .hlint.yaml in the root of your project


# Specify additional command line arguments
#
# - arguments: [--color, --cpp-simple, -XQuasiQuotes]
- arguments:
# NOTE: List of extensions below should reflect the list
# of default extensions from package.yaml.
Expand All @@ -17,46 +6,11 @@
- -XQuasiQuotes
- -XScopedTypeVariables

# Control which extensions/flags/modules/functions can be used
#
# - extensions:
# - default: false # all extension are banned by default
# - name: [PatternGuards, ViewPatterns] # only these listed extensions can be used
# - {name: CPP, within: CrossPlatform} # CPP can only be used in a given module
#
# - flags:
# - {name: -w, within: []} # -w is allowed nowhere
#
# - modules:
# - {name: [Data.Set, Data.HashSet], as: Set} # if you import Data.Set qualified, it must be as 'Set'
# - {name: Control.Arrow, within: []} # Certain modules are banned entirely
#
# - functions:
# - {name: unsafePerformIO, within: []} # unsafePerformIO can only appear in no modules


# Add custom hints for this project
#
# Will suggest replacing "wibbleMany [myvar]" with "wibbleOne myvar"
# - error: {lhs: "wibbleMany [x]", rhs: wibbleOne x}


# Turn on hints that are off by default
#
# Ban "module X(module X) where", to require a real export list
# - warn: {name: Use explicit module export list}
#
# Replace a $ b $ c with a . b $ c
# - group: {name: dollar, enabled: true}
#
# Generalise map to fmap, ++ to <>
# - group: {name: generalise, enabled: true}


# Ignore some builtin hints
# - ignore: {name: Use let}
# - ignore: {name: Use const, within: SpecialModule} # Only within certain modules


# Define some custom infix operators
# - fixity: infixr 3 ~^#^~
# TODO: Review the remaining ignored hlint rules.
- ignore: {name: Use camelCase}
- ignore: {name: Eta reduce}
- ignore: {name: Use first}
- ignore: {name: Use second}
- ignore: {name: Use newtype instead of data}
- ignore: {name: Use $>}
- ignore: {name: Use list comprehension}
6 changes: 3 additions & 3 deletions waspc/cli/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,9 +55,9 @@ main = do
Command.Call.Telemetry -> runCommand Telemetry.telemetry
Command.Call.Deps -> runCommand deps
Command.Call.Info -> runCommand info
Command.Call.PrintBashCompletionInstruction -> runCommand $ printBashCompletionInstruction
Command.Call.GenerateBashCompletionScript -> runCommand $ generateBashCompletionScript
Command.Call.BashCompletionListCommands -> runCommand $ bashCompletion
Command.Call.PrintBashCompletionInstruction -> runCommand printBashCompletionInstruction
Command.Call.GenerateBashCompletionScript -> runCommand generateBashCompletionScript
Command.Call.BashCompletionListCommands -> runCommand bashCompletion
Command.Call.Unknown _ -> printUsage

-- If sending of telemetry data is still not done 1 second since commmand finished, abort it.
Expand Down
5 changes: 2 additions & 3 deletions waspc/cli/Wasp/Cli/Command/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,6 +55,5 @@ waspSaysC = liftIO . waspSays

alphaWarningMessage :: String
alphaWarningMessage =
( "NOTE: Wasp is still in Alpha, therefore not yet production ready "
++ "and might change significantly in the future versions."
)
"NOTE: Wasp is still in Alpha, therefore not yet production ready "
++ "and might change significantly in the future versions."
7 changes: 1 addition & 6 deletions waspc/cli/Wasp/Cli/Command/Db/Migrate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -97,12 +97,7 @@ copyDbMigrationsDir copyDirection waspProjectDir genProjectRootDir = do
doesSrcDirExist <- PathIO.doesDirExist (SP.Path.toPathAbsDir src)
if doesSrcDirExist
then
( ( PathIO.copyDirRecur
(SP.Path.toPathAbsDir src)
(SP.Path.toPathAbsDir target)
)
>> return Nothing
)
PathIO.copyDirRecur (SP.Path.toPathAbsDir src) (SP.Path.toPathAbsDir target) >> return Nothing
`catch` (\e -> return $ Just $ show (e :: P.PathException))
`catch` (\e -> return $ Just $ show (e :: IOError))
else return Nothing
4 changes: 2 additions & 2 deletions waspc/cli/Wasp/Cli/Command/Watch.hs
Original file line number Diff line number Diff line change
Expand Up @@ -66,8 +66,8 @@ watch waspProjectDir outDir = FSN.withManager $ \mgr -> do
eventFilter event =
let filename = FP.takeFileName $ FSN.eventPath event
in not (null filename)
&& not (take 2 filename == ".#") -- Ignore emacs lock files.
&& take 2 filename /= ".#" -- Ignore emacs lock files.
&& not (head filename == '#' && last filename == '#') -- Ignore emacs auto-save files.
&& not (last filename == '~') -- Ignore emacs and vim backup files.
&& last filename /= '~' -- Ignore emacs and vim backup files.
&& not (head filename == '.' && ".swp" `isSuffixOf` filename) -- Ignore vim swp files.
&& not (head filename == '.' && ".un~" `isSuffixOf` filename) -- Ignore vim undo files.
2 changes: 1 addition & 1 deletion waspc/src/Wasp/Analyzer/Evaluator/TH/Decl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -144,7 +144,7 @@ genDictEntryTypesAndEvaluationForRecord :: Name -> [(Name, Type)] -> Q (ExpQ, Ex
genDictEntryTypesAndEvaluationForRecord dataConstructorName fields =
go $ reverse fields -- Reversing enables us to apply evaluations in right order.
where
go [] = pure (listE [], varE 'pure `appE` conE dataConstructorName)
go [] = pure (listE [], [|pure|] `appE` conE dataConstructorName)
go ((fieldName, fieldType) : restOfFields) = do
(restDictType, restEvaluation) <- go restOfFields
let thisDictTypeE =
Expand Down
2 changes: 0 additions & 2 deletions waspc/src/Wasp/Analyzer/TypeChecker/Monad.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,3 @@
{-# LANGUAGE TupleSections #-}

module Wasp.Analyzer.TypeChecker.Monad
( TypeChecker,
lookupType,
Expand Down
3 changes: 1 addition & 2 deletions waspc/src/Wasp/Generator/DbGenerator.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,6 @@ module Wasp.Generator.DbGenerator
where

import Data.Aeson (object, (.=))
import Data.Maybe (fromMaybe)
import StrongPath (Dir, File', Path', Rel, reldir, relfile, (</>))
import qualified StrongPath as SP
import Wasp.CompileOptions (CompileOptions)
Expand Down Expand Up @@ -64,7 +63,7 @@ genPrismaSchema wasp = createTemplateFileDraft dstPath tmplSrcPath (Just templat
"datasourceUrl" .= (datasourceUrl :: String)
]

dbSystem = fromMaybe Wasp.Db.SQLite $ Wasp.Db._system <$> Wasp.getDb wasp
dbSystem = maybe Wasp.Db.SQLite Wasp.Db._system (Wasp.getDb wasp)
(datasourceProvider, datasourceUrl) = case dbSystem of
Wasp.Db.PostgreSQL -> ("postgresql", "env(\"DATABASE_URL\")")
-- TODO: Report this error with some better mechanism, not `error`.
Expand Down
6 changes: 1 addition & 5 deletions waspc/src/Wasp/Generator/DockerGenerator.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,11 +13,7 @@ import Wasp.Wasp (Wasp)
import qualified Wasp.Wasp as Wasp

genDockerFiles :: Wasp -> CompileOptions -> [FileDraft]
genDockerFiles wasp _ =
concat
[ [genDockerfile wasp],
[genDockerignore wasp]
]
genDockerFiles wasp _ = genDockerfile wasp : [genDockerignore wasp]

-- TODO: Inject paths to server and db files/dirs, right now they are hardcoded in the templates.
genDockerfile :: Wasp -> FileDraft
Expand Down
13 changes: 7 additions & 6 deletions waspc/src/Wasp/Generator/ServerGenerator.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ module Wasp.Generator.ServerGenerator
)
where

import Control.Monad (when)
import Control.Monad (unless)
import Data.Aeson (object, (.=))
import Data.List (intercalate)
import Data.Maybe
Expand Down Expand Up @@ -72,7 +72,7 @@ preCleanup _ outDir _ = do
-- If .env gets removed but there is old .env file in generated project from previous attempts,
-- we need to make sure we remove it.
removeFile dotEnvAbsFilePath
`catch` \e -> when (not $ isDoesNotExistError e) $ throwIO e
`catch` \e -> unless (isDoesNotExistError e) $ throwIO e
where
dotEnvAbsFilePath = SP.toFilePath $ outDir </> C.serverRootDirInProjectRootDir </> dotEnvInServerRootDir

Expand Down Expand Up @@ -104,10 +104,11 @@ genPackageJson wasp waspDeps waspDevDeps =
"devDepsChunk" .= npmDevDepsToPackageJsonEntry waspDevDeps,
"nodeVersion" .= nodeVersionAsText,
"startProductionScript"
.= concat
[ if not (null $ Wasp.getPSLEntities wasp) then "npm run db-migrate-prod && " else "",
"NODE_ENV=production node ./src/server.js"
]
.= if not (null $ Wasp.getPSLEntities wasp)
then "npm run db-migrate-prod && "
else
""
++ "NODE_ENV=production node ./src/server.js"
]
)
where
Expand Down
18 changes: 6 additions & 12 deletions waspc/src/Wasp/Generator/ServerGenerator/OperationsG.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ where
import Data.Aeson (object, (.=))
import qualified Data.Aeson as Aeson
import Data.Char (toLower)
import Data.Maybe (fromJust, fromMaybe)
import Data.Maybe (fromJust)
import StrongPath (Dir, Dir', File', Path, Path', Posix, Rel, reldir, reldirP, relfile, (</>))
import qualified StrongPath as SP
import Wasp.Generator.ExternalCodeGenerator.Common (GeneratedExternalCodeDir)
Expand All @@ -24,22 +24,16 @@ import qualified Wasp.Wasp.Query as Wasp.Query

genOperations :: Wasp -> [FileDraft]
genOperations wasp =
concat
[ genQueries wasp,
genActions wasp
]
genQueries wasp
++ genActions wasp

genQueries :: Wasp -> [FileDraft]
genQueries wasp =
concat
[ map (genQuery wasp) (Wasp.getQueries wasp)
]
map (genQuery wasp) (Wasp.getQueries wasp)

genActions :: Wasp -> [FileDraft]
genActions wasp =
concat
[ map (genAction wasp) (Wasp.getActions wasp)
]
map (genAction wasp) (Wasp.getActions wasp)

-- | Here we generate JS file that basically imports JS query function provided by user,
-- decorates it (mostly injects stuff into it) and exports. Idea is that the rest of the server,
Expand Down Expand Up @@ -86,7 +80,7 @@ operationTmplData operation =
object
[ "jsFnImportStatement" .= importStmt,
"jsFnIdentifier" .= importIdentifier,
"entities" .= map buildEntityData (fromMaybe [] $ Wasp.Operation.getEntities operation)
"entities" .= maybe [] (map buildEntityData) (Wasp.Operation.getEntities operation)
]
where
(importIdentifier, importStmt) =
Expand Down
4 changes: 2 additions & 2 deletions waspc/src/Wasp/Generator/WebAppGenerator.hs
Original file line number Diff line number Diff line change
Expand Up @@ -116,8 +116,8 @@ generatePublicIndexHtml wasp =
targetPath = [relfile|public/index.html|]
templateData =
object
[ "title" .= (Wasp.App.appTitle $ getApp wasp),
"head" .= (maybe "" (intercalate "\n") (Wasp.App.appHead $ getApp wasp))
[ "title" .= Wasp.App.appTitle (getApp wasp),
"head" .= maybe "" (intercalate "\n") (Wasp.App.appHead $ getApp wasp)
]

-- * Src dir
Expand Down
4 changes: 2 additions & 2 deletions waspc/src/Wasp/Generator/WebAppGenerator/AuthG.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,8 +45,8 @@ genCreateAuthRequiredPage auth =
(Just templateData)
where
authReqPagePath = [relfile|auth/pages/createAuthRequiredPage.js|]
targetPath = C.webAppSrcDirInWebAppRootDir </> (asWebAppSrcFile authReqPagePath)
templateData = object ["onAuthFailedRedirectTo" .= (Wasp.Auth._onAuthFailedRedirectTo auth)]
targetPath = C.webAppSrcDirInWebAppRootDir </> asWebAppSrcFile authReqPagePath
templateData = object ["onAuthFailedRedirectTo" .= Wasp.Auth._onAuthFailedRedirectTo auth]

-- | Generates React hook that Wasp developer can use in a component to get
-- access to the currently logged in user (and check whether user is logged in
Expand Down
17 changes: 5 additions & 12 deletions waspc/src/Wasp/Generator/WebAppGenerator/OperationsGenerator.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,10 +8,7 @@ import Data.Aeson
(.=),
)
import Data.List (intercalate)
import Data.Maybe
( fromJust,
fromMaybe,
)
import Data.Maybe (fromJust)
import StrongPath (File', Path', Rel', parseRelFile, reldir, relfile, (</>))
import Wasp.Generator.FileDraft (FileDraft)
import qualified Wasp.Generator.ServerGenerator as ServerGenerator
Expand All @@ -35,16 +32,12 @@ genOperations wasp =

genQueries :: Wasp -> [FileDraft]
genQueries wasp =
concat
[ map (genQuery wasp) (Wasp.getQueries wasp),
[C.makeSimpleTemplateFD (C.asTmplFile [relfile|src/queries/index.js|]) wasp]
]
map (genQuery wasp) (Wasp.getQueries wasp)
++ [C.makeSimpleTemplateFD (C.asTmplFile [relfile|src/queries/index.js|]) wasp]

genActions :: Wasp -> [FileDraft]
genActions wasp =
concat
[ map (genAction wasp) (Wasp.getActions wasp)
]
map (genAction wasp) (Wasp.getActions wasp)

genQuery :: Wasp -> Wasp.Query.Query -> FileDraft
genQuery _ query = C.makeTemplateFD tmplFile dstFile (Just tmplData)
Expand Down Expand Up @@ -87,7 +80,7 @@ genAction _ action = C.makeTemplateFD tmplFile dstFile (Just tmplData)
makeJsArrayOfEntityNames :: Wasp.Operation.Operation -> String
makeJsArrayOfEntityNames operation = "[" ++ intercalate ", " entityStrings ++ "]"
where
entityStrings = map (\x -> "'" ++ x ++ "'") $ fromMaybe [] $ Wasp.Operation.getEntities operation
entityStrings = maybe [] (map (\x -> "'" ++ x ++ "'")) (Wasp.Operation.getEntities operation)

getOperationDstFileName :: Wasp.Operation.Operation -> Maybe (Path' Rel' File')
getOperationDstFileName operation = parseRelFile (Wasp.Operation.getName operation ++ ".js")
6 changes: 3 additions & 3 deletions waspc/src/Wasp/Parser/Auth.hs
Original file line number Diff line number Diff line change
Expand Up @@ -62,13 +62,13 @@ authProperty =

authPropertyOnAuthFailedRedirectTo :: Parser AuthProperty
authPropertyOnAuthFailedRedirectTo =
AuthPropertyOnAuthFailedRedirectTo <$> (P.waspPropertyStringLiteral "onAuthFailedRedirectTo")
AuthPropertyOnAuthFailedRedirectTo <$> P.waspPropertyStringLiteral "onAuthFailedRedirectTo"

authPropertyUserEntity :: Parser AuthProperty
authPropertyUserEntity = AuthPropertyUserEntity <$> (P.waspProperty "userEntity" L.identifier)
authPropertyUserEntity = AuthPropertyUserEntity <$> P.waspProperty "userEntity" L.identifier

authPropertyMethods :: Parser AuthProperty
authPropertyMethods = AuthPropertyMethods <$> P.waspProperty "methods" (L.brackets $ L.commaSep1 authMethod)

authMethod :: Parser Wasp.Auth.AuthMethod
authMethod = L.symbol "EmailAndPassword" *> (pure Wasp.Auth.EmailAndPassword)
authMethod = L.symbol "EmailAndPassword" *> pure Wasp.Auth.EmailAndPassword
9 changes: 5 additions & 4 deletions waspc/src/Wasp/Parser/Db.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module Wasp.Parser.Db
)
where

import Data.Maybe (fromMaybe, listToMaybe)
import Data.Maybe (listToMaybe)
import Text.Parsec (try, (<|>))
import Text.Parsec.String (Parser)
import qualified Wasp.Lexer as L
Expand All @@ -16,9 +16,10 @@ db = do
dbProperties <- P.waspClosure (L.commaSep1 dbProperty)

system <-
fromMaybe (fail "'system' property is required!") $
maybe
(fail "'system' property is required!")
return
<$> listToMaybe [p | DbPropertySystem p <- dbProperties]
(listToMaybe [p | DbPropertySystem p <- dbProperties])

return
Wasp.Db.Db
Expand All @@ -33,7 +34,7 @@ dbProperty =
dbPropertySystem

dbPropertySystem :: Parser DbProperty
dbPropertySystem = DbPropertySystem <$> (P.waspProperty "system" dbPropertySystemValue)
dbPropertySystem = DbPropertySystem <$> P.waspProperty "system" dbPropertySystemValue
where
dbPropertySystemValue =
try (L.symbol "PostgreSQL" >> return Wasp.Db.PostgreSQL)
Expand Down
2 changes: 1 addition & 1 deletion waspc/src/Wasp/Parser/JsCode.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,4 +9,4 @@ import qualified Wasp.Parser.Common as P
import qualified Wasp.Wasp.JsCode as WJS

jsCode :: Parser WJS.JsCode
jsCode = (WJS.JsCode . Text.pack) <$> P.waspNamedClosure "js"
jsCode = WJS.JsCode . Text.pack <$> P.waspNamedClosure "js"
2 changes: 1 addition & 1 deletion waspc/src/Wasp/Parser/Style.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,4 +17,4 @@ cssFile :: Parser Wasp.Style.Style
cssFile = Wasp.Style.ExtCodeCssFile <$> Wasp.Parser.ExternalCode.extCodeFilePathString

cssCode :: Parser Wasp.Style.Style
cssCode = (Wasp.Style.CssCode . Text.pack) <$> Wasp.Parser.Common.waspNamedClosure "css"
cssCode = Wasp.Style.CssCode . Text.pack <$> Wasp.Parser.Common.waspNamedClosure "css"
Loading