mirror of
https://github.com/wasp-lang/wasp.git
synced 2024-12-24 17:44:21 +03:00
Merge remote-tracking branch 'upstream/master' into auth_opt_out
This commit is contained in:
commit
c71eb58ea9
@ -14,9 +14,7 @@ where
|
||||
import Common (WaspProjectDir)
|
||||
import ExternalCode (SourceExternalCodeDir)
|
||||
import qualified Generator.Common
|
||||
import qualified Path as P
|
||||
import StrongPath (Dir, File, Path, Rel)
|
||||
import qualified StrongPath as SP
|
||||
import StrongPath (Dir, File', Path', Rel, reldir, relfile)
|
||||
import qualified Util.Terminal as Term
|
||||
|
||||
data DotWaspDir -- Here we put everything that wasp generates.
|
||||
@ -24,21 +22,21 @@ data DotWaspDir -- Here we put everything that wasp generates.
|
||||
data CliTemplatesDir
|
||||
|
||||
-- TODO: SHould this be renamed to include word "root"?
|
||||
dotWaspDirInWaspProjectDir :: Path (Rel WaspProjectDir) (Dir DotWaspDir)
|
||||
dotWaspDirInWaspProjectDir = SP.fromPathRelDir [P.reldir|.wasp|]
|
||||
dotWaspDirInWaspProjectDir :: Path' (Rel WaspProjectDir) (Dir DotWaspDir)
|
||||
dotWaspDirInWaspProjectDir = [reldir|.wasp|]
|
||||
|
||||
-- TODO: Hm this has different name than it has in Generator.
|
||||
generatedCodeDirInDotWaspDir :: Path (Rel DotWaspDir) (Dir Generator.Common.ProjectRootDir)
|
||||
generatedCodeDirInDotWaspDir = SP.fromPathRelDir [P.reldir|out|]
|
||||
generatedCodeDirInDotWaspDir :: Path' (Rel DotWaspDir) (Dir Generator.Common.ProjectRootDir)
|
||||
generatedCodeDirInDotWaspDir = [reldir|out|]
|
||||
|
||||
buildDirInDotWaspDir :: Path (Rel DotWaspDir) (Dir Generator.Common.ProjectRootDir)
|
||||
buildDirInDotWaspDir = SP.fromPathRelDir [P.reldir|build|]
|
||||
buildDirInDotWaspDir :: Path' (Rel DotWaspDir) (Dir Generator.Common.ProjectRootDir)
|
||||
buildDirInDotWaspDir = [reldir|build|]
|
||||
|
||||
dotWaspRootFileInWaspProjectDir :: Path (Rel WaspProjectDir) File
|
||||
dotWaspRootFileInWaspProjectDir = SP.fromPathRelFile [P.relfile|.wasproot|]
|
||||
dotWaspRootFileInWaspProjectDir :: Path' (Rel WaspProjectDir) File'
|
||||
dotWaspRootFileInWaspProjectDir = [relfile|.wasproot|]
|
||||
|
||||
extCodeDirInWaspProjectDir :: Path (Rel WaspProjectDir) (Dir SourceExternalCodeDir)
|
||||
extCodeDirInWaspProjectDir = SP.fromPathRelDir [P.reldir|ext|]
|
||||
extCodeDirInWaspProjectDir :: Path' (Rel WaspProjectDir) (Dir SourceExternalCodeDir)
|
||||
extCodeDirInWaspProjectDir = [reldir|ext|]
|
||||
|
||||
waspSays :: String -> IO ()
|
||||
waspSays what = putStrLn $ Term.applyStyles [Term.Yellow] what
|
||||
|
@ -15,7 +15,8 @@ import Control.Monad (when)
|
||||
import Control.Monad.Except (throwError)
|
||||
import Control.Monad.IO.Class (liftIO)
|
||||
import qualified Lib
|
||||
import StrongPath (Abs, Dir, Path, toFilePath, (</>))
|
||||
import StrongPath (Abs, Dir, Path', (</>))
|
||||
import qualified StrongPath as SP
|
||||
import System.Directory
|
||||
( doesDirectoryExist,
|
||||
removeDirectoryRecursive,
|
||||
@ -27,7 +28,7 @@ build = do
|
||||
let buildDir =
|
||||
waspProjectDir </> Common.dotWaspDirInWaspProjectDir
|
||||
</> Common.buildDirInDotWaspDir
|
||||
buildDirFilePath = toFilePath buildDir
|
||||
buildDirFilePath = SP.fromAbsDir buildDir
|
||||
|
||||
doesBuildDirExist <- liftIO $ doesDirectoryExist buildDirFilePath
|
||||
when doesBuildDirExist $
|
||||
@ -44,8 +45,8 @@ build = do
|
||||
liftIO $ putStrLn alphaWarningMessage
|
||||
|
||||
buildIO ::
|
||||
Path Abs (Dir Common.WaspProjectDir) ->
|
||||
Path Abs (Dir Lib.ProjectRootDir) ->
|
||||
Path' Abs (Dir Common.WaspProjectDir) ->
|
||||
Path' Abs (Dir Lib.ProjectRootDir) ->
|
||||
IO (Either String ())
|
||||
buildIO waspProjectDir buildDir = compileIOWithOptions options waspProjectDir buildDir
|
||||
where
|
||||
|
@ -16,7 +16,7 @@ import Control.Monad (unless, when)
|
||||
import Control.Monad.Except (throwError)
|
||||
import Control.Monad.IO.Class (liftIO)
|
||||
import Data.Maybe (fromJust)
|
||||
import StrongPath (Abs, Dir, Path)
|
||||
import StrongPath (Abs, Dir, Path')
|
||||
import qualified StrongPath as SP
|
||||
import System.Directory
|
||||
( doesFileExist,
|
||||
@ -25,12 +25,12 @@ import System.Directory
|
||||
)
|
||||
import qualified System.FilePath as FP
|
||||
|
||||
findWaspProjectRoot :: Path Abs (Dir ()) -> Command (Path Abs (Dir WaspProjectDir))
|
||||
findWaspProjectRoot :: Path' Abs (Dir ()) -> Command (Path' Abs (Dir WaspProjectDir))
|
||||
findWaspProjectRoot currentDir = do
|
||||
let absCurrentDirFp = SP.toFilePath currentDir
|
||||
let absCurrentDirFp = SP.fromAbsDir currentDir
|
||||
doesCurrentDirExist <- liftIO $ doesPathExist absCurrentDirFp
|
||||
unless doesCurrentDirExist (throwError notFoundError)
|
||||
let dotWaspRootFilePath = absCurrentDirFp FP.</> SP.toFilePath dotWaspRootFileInWaspProjectDir
|
||||
let dotWaspRootFilePath = absCurrentDirFp FP.</> SP.fromRelFile dotWaspRootFileInWaspProjectDir
|
||||
isCurrentDirRoot <- liftIO $ doesFileExist dotWaspRootFilePath
|
||||
if isCurrentDirRoot
|
||||
then return $ SP.castDir currentDir
|
||||
@ -45,7 +45,7 @@ findWaspProjectRoot currentDir = do
|
||||
++ " you are running this command from Wasp project."
|
||||
)
|
||||
|
||||
findWaspProjectRootDirFromCwd :: Command (Path Abs (Dir WaspProjectDir))
|
||||
findWaspProjectRootDirFromCwd :: Command (Path' Abs (Dir WaspProjectDir))
|
||||
findWaspProjectRootDirFromCwd = do
|
||||
absCurrentDir <- liftIO getCurrentDirectory
|
||||
findWaspProjectRoot (fromJust $ SP.parseAbsDir absCurrentDir)
|
||||
|
@ -20,7 +20,7 @@ import CompileOptions (CompileOptions (..))
|
||||
import Control.Monad.Except (runExceptT, throwError)
|
||||
import Control.Monad.IO.Class (liftIO)
|
||||
import qualified Lib
|
||||
import StrongPath (Abs, Dir, Path, (</>))
|
||||
import StrongPath (Abs, Dir, Path', (</>))
|
||||
|
||||
compile :: Command ()
|
||||
compile = do
|
||||
@ -38,8 +38,8 @@ compile = do
|
||||
-- | Compiles Wasp source code in waspProjectDir directory and generates a project
|
||||
-- in given outDir directory.
|
||||
compileIO ::
|
||||
Path Abs (Dir WaspProjectDir) ->
|
||||
Path Abs (Dir Lib.ProjectRootDir) ->
|
||||
Path' Abs (Dir WaspProjectDir) ->
|
||||
Path' Abs (Dir Lib.ProjectRootDir) ->
|
||||
IO (Either String ())
|
||||
compileIO waspProjectDir outDir = compileIOWithOptions options waspProjectDir outDir
|
||||
where
|
||||
@ -51,8 +51,8 @@ compileIO waspProjectDir outDir = compileIOWithOptions options waspProjectDir ou
|
||||
|
||||
compileIOWithOptions ::
|
||||
CompileOptions ->
|
||||
Path Abs (Dir Cli.Common.WaspProjectDir) ->
|
||||
Path Abs (Dir Lib.ProjectRootDir) ->
|
||||
Path' Abs (Dir Cli.Common.WaspProjectDir) ->
|
||||
Path' Abs (Dir Lib.ProjectRootDir) ->
|
||||
IO (Either String ())
|
||||
compileIOWithOptions options waspProjectDir outDir = runExceptT $ do
|
||||
-- TODO: Use throwIO instead of Either to return exceptions?
|
||||
|
@ -11,8 +11,7 @@ import Control.Monad.IO.Class (liftIO)
|
||||
import qualified Data
|
||||
import Data.Char (isLetter)
|
||||
import ExternalCode (SourceExternalCodeDir)
|
||||
import qualified Path as P
|
||||
import StrongPath (Abs, Dir, File, Path, Rel, (</>))
|
||||
import StrongPath (Abs, Dir, File', Path', Rel, reldir, relfile, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import System.Directory (createDirectory, getCurrentDirectory)
|
||||
import qualified System.Directory
|
||||
@ -62,15 +61,15 @@ createNewProject' (ProjectName projectName) = do
|
||||
writeFileSP (extCodeDir </> waspignoreFileInExtCodeDir) waspignoreFileContent
|
||||
|
||||
copyTemplateFile'
|
||||
(SP.fromPathRelFile [P.relfile|new/ext/MainPage.js|])
|
||||
[relfile|new/ext/MainPage.js|]
|
||||
mainPageJsFileInExtCodeDir
|
||||
|
||||
copyTemplateFile'
|
||||
(SP.fromPathRelFile [P.relfile|new/ext/Main.css|])
|
||||
[relfile|new/ext/Main.css|]
|
||||
mainCssFileInExtCodeDir
|
||||
|
||||
copyTemplateFile'
|
||||
(SP.fromPathRelFile [P.relfile|new/ext/waspLogo.png|])
|
||||
[relfile|new/ext/waspLogo.png|]
|
||||
waspLogoFileInExtCodeDir
|
||||
|
||||
liftIO $ do
|
||||
@ -83,21 +82,21 @@ createNewProject' (ProjectName projectName) = do
|
||||
putStrLn Command.Common.alphaWarningMessage
|
||||
where
|
||||
copyTemplateFile ::
|
||||
Path Abs (Dir Data.DataDir) ->
|
||||
Path Abs (Dir SourceExternalCodeDir) ->
|
||||
Path (Rel Common.CliTemplatesDir) File ->
|
||||
Path (Rel SourceExternalCodeDir) File ->
|
||||
Path' Abs (Dir Data.DataDir) ->
|
||||
Path' Abs (Dir SourceExternalCodeDir) ->
|
||||
Path' (Rel Common.CliTemplatesDir) File' ->
|
||||
Path' (Rel SourceExternalCodeDir) File' ->
|
||||
IO ()
|
||||
copyTemplateFile dataDir extCodeDir srcTmplFile dstExtDirFile =
|
||||
System.Directory.copyFile
|
||||
(SP.toFilePath (dataDir </> cliTemplatesDirInDataDir </> srcTmplFile))
|
||||
(SP.toFilePath (extCodeDir </> dstExtDirFile))
|
||||
(SP.fromAbsFile (dataDir </> cliTemplatesDirInDataDir </> srcTmplFile))
|
||||
(SP.fromAbsFile (extCodeDir </> dstExtDirFile))
|
||||
|
||||
cliTemplatesDirInDataDir :: Path (Rel Data.DataDir) (Dir Common.CliTemplatesDir)
|
||||
cliTemplatesDirInDataDir = SP.fromPathRelDir [P.reldir|Cli/templates|]
|
||||
cliTemplatesDirInDataDir :: Path' (Rel Data.DataDir) (Dir Common.CliTemplatesDir)
|
||||
cliTemplatesDirInDataDir = [reldir|Cli/templates|]
|
||||
|
||||
mainWaspFileInWaspProjectDir :: Path (Rel Common.WaspProjectDir) File
|
||||
mainWaspFileInWaspProjectDir = SP.fromPathRelFile [P.relfile|main.wasp|]
|
||||
mainWaspFileInWaspProjectDir :: Path' (Rel Common.WaspProjectDir) File'
|
||||
mainWaspFileInWaspProjectDir = [relfile|main.wasp|]
|
||||
|
||||
mainWaspFileContent =
|
||||
unlines
|
||||
@ -111,8 +110,8 @@ createNewProject' (ProjectName projectName) = do
|
||||
"}"
|
||||
]
|
||||
|
||||
gitignoreFileInWaspProjectDir :: Path (Rel Common.WaspProjectDir) File
|
||||
gitignoreFileInWaspProjectDir = SP.fromPathRelFile [P.relfile|.gitignore|]
|
||||
gitignoreFileInWaspProjectDir :: Path' (Rel Common.WaspProjectDir) File'
|
||||
gitignoreFileInWaspProjectDir = [relfile|.gitignore|]
|
||||
|
||||
gitignoreFileContent =
|
||||
unlines
|
||||
@ -120,8 +119,8 @@ createNewProject' (ProjectName projectName) = do
|
||||
"/.env"
|
||||
]
|
||||
|
||||
waspignoreFileInExtCodeDir :: Path (Rel SourceExternalCodeDir) File
|
||||
waspignoreFileInExtCodeDir = SP.fromPathRelFile [P.relfile|.waspignore|]
|
||||
waspignoreFileInExtCodeDir :: Path' (Rel SourceExternalCodeDir) File'
|
||||
waspignoreFileInExtCodeDir = [relfile|.waspignore|]
|
||||
|
||||
waspignoreFileContent =
|
||||
unlines
|
||||
@ -130,14 +129,14 @@ createNewProject' (ProjectName projectName) = do
|
||||
"**/#*#"
|
||||
]
|
||||
|
||||
mainPageJsFileInExtCodeDir :: Path (Rel SourceExternalCodeDir) File
|
||||
mainPageJsFileInExtCodeDir = SP.fromPathRelFile [P.relfile|MainPage.js|]
|
||||
mainPageJsFileInExtCodeDir :: Path' (Rel SourceExternalCodeDir) File'
|
||||
mainPageJsFileInExtCodeDir = [relfile|MainPage.js|]
|
||||
|
||||
mainCssFileInExtCodeDir :: Path (Rel SourceExternalCodeDir) File
|
||||
mainCssFileInExtCodeDir = SP.fromPathRelFile [P.relfile|Main.css|]
|
||||
mainCssFileInExtCodeDir :: Path' (Rel SourceExternalCodeDir) File'
|
||||
mainCssFileInExtCodeDir = [relfile|Main.css|]
|
||||
|
||||
waspLogoFileInExtCodeDir :: Path (Rel SourceExternalCodeDir) File
|
||||
waspLogoFileInExtCodeDir = SP.fromPathRelFile [P.relfile|waspLogo.png|]
|
||||
waspLogoFileInExtCodeDir :: Path' (Rel SourceExternalCodeDir) File'
|
||||
waspLogoFileInExtCodeDir = [relfile|waspLogo.png|]
|
||||
|
||||
writeFileSP = writeFile . SP.toFilePath
|
||||
createDirectorySP = createDirectory . SP.toFilePath
|
||||
writeFileSP = writeFile . SP.fromAbsFile
|
||||
createDirectorySP = createDirectory . SP.fromAbsDir
|
||||
|
@ -21,8 +21,8 @@ import Generator.DbGenerator (dbRootDirInProjectRootDir)
|
||||
import qualified Generator.DbGenerator.Operations as DbOps
|
||||
import qualified Path as P
|
||||
import qualified Path.IO as PathIO
|
||||
import StrongPath (Abs, Dir, Path, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import StrongPath (Abs, Dir, Path', reldir, (</>))
|
||||
import qualified StrongPath.Path as SP.Path
|
||||
|
||||
migrateDev :: Command ()
|
||||
migrateDev = do
|
||||
@ -69,11 +69,11 @@ data MigrationDirCopyDirection = CopyMigDirUp | CopyMigDirDown deriving (Eq)
|
||||
copyDbMigrationsDir ::
|
||||
-- | Copy direction (source -> gen or gen-> source)
|
||||
MigrationDirCopyDirection ->
|
||||
Path Abs (Dir WaspProjectDir) ->
|
||||
Path Abs (Dir ProjectRootDir) ->
|
||||
Path' Abs (Dir WaspProjectDir) ->
|
||||
Path' Abs (Dir ProjectRootDir) ->
|
||||
IO (Maybe String)
|
||||
copyDbMigrationsDir copyDirection waspProjectDir genProjectRootDir = do
|
||||
let dbMigrationsDirInDbRootDir = SP.fromPathRelDir [P.reldir|migrations|]
|
||||
let dbMigrationsDirInDbRootDir = [reldir|migrations|]
|
||||
|
||||
-- Migration folder in Wasp source (seen by Wasp dev and versioned).
|
||||
let dbMigrationsDirInWaspProjectDirAbs = waspProjectDir </> dbMigrationsDirInDbRootDir
|
||||
@ -93,12 +93,12 @@ copyDbMigrationsDir copyDirection waspProjectDir genProjectRootDir = do
|
||||
then dbMigrationsDirInWaspProjectDirAbs
|
||||
else dbMigrationsDirInGenProjectDirAbs
|
||||
|
||||
doesSrcDirExist <- PathIO.doesDirExist (SP.toPathAbsDir src)
|
||||
doesSrcDirExist <- PathIO.doesDirExist (SP.Path.toPathAbsDir src)
|
||||
if doesSrcDirExist
|
||||
then
|
||||
( ( PathIO.copyDirRecur
|
||||
(SP.toPathAbsDir src)
|
||||
(SP.toPathAbsDir target)
|
||||
(SP.Path.toPathAbsDir src)
|
||||
(SP.Path.toPathAbsDir target)
|
||||
)
|
||||
>> return Nothing
|
||||
)
|
||||
|
@ -5,25 +5,24 @@ module Command.Telemetry.Common
|
||||
)
|
||||
where
|
||||
|
||||
import Path (reldir)
|
||||
import StrongPath (Abs, Dir, Path)
|
||||
import StrongPath (Abs, Dir, Path', reldir)
|
||||
import qualified StrongPath as SP
|
||||
import qualified System.Directory as SD
|
||||
|
||||
data UserCacheDir
|
||||
|
||||
getUserCacheDirPath :: IO (Path Abs (Dir UserCacheDir))
|
||||
getUserCacheDirPath :: IO (Path' Abs (Dir UserCacheDir))
|
||||
getUserCacheDirPath = SD.getXdgDirectory SD.XdgCache "" >>= SP.parseAbsDir
|
||||
|
||||
data TelemetryCacheDir
|
||||
|
||||
ensureTelemetryCacheDirExists :: IO (Path Abs (Dir TelemetryCacheDir))
|
||||
ensureTelemetryCacheDirExists :: IO (Path' Abs (Dir TelemetryCacheDir))
|
||||
ensureTelemetryCacheDirExists = do
|
||||
userCacheDirPath <- getUserCacheDirPath
|
||||
SD.createDirectoryIfMissing False $ SP.toFilePath userCacheDirPath
|
||||
SD.createDirectoryIfMissing False $ SP.fromAbsDir userCacheDirPath
|
||||
let telemetryCacheDirPath = getTelemetryCacheDirPath userCacheDirPath
|
||||
SD.createDirectoryIfMissing True $ SP.toFilePath telemetryCacheDirPath
|
||||
SD.createDirectoryIfMissing True $ SP.fromAbsDir telemetryCacheDirPath
|
||||
return telemetryCacheDirPath
|
||||
|
||||
getTelemetryCacheDirPath :: Path Abs (Dir UserCacheDir) -> Path Abs (Dir TelemetryCacheDir)
|
||||
getTelemetryCacheDirPath userCacheDirPath = userCacheDirPath SP.</> SP.fromPathRelDir [reldir|wasp/telemetry|]
|
||||
getTelemetryCacheDirPath :: Path' Abs (Dir UserCacheDir) -> Path' Abs (Dir TelemetryCacheDir)
|
||||
getTelemetryCacheDirPath userCacheDirPath = userCacheDirPath SP.</> [reldir|wasp/telemetry|]
|
||||
|
@ -25,12 +25,12 @@ import Data.Version (showVersion)
|
||||
import GHC.Generics
|
||||
import qualified Network.HTTP.Simple as HTTP
|
||||
import Paths_waspc (version)
|
||||
import StrongPath (Abs, Dir, File, Path)
|
||||
import StrongPath (Abs, Dir, File', Path')
|
||||
import qualified StrongPath as SP
|
||||
import qualified System.Directory as SD
|
||||
import qualified System.Info
|
||||
|
||||
considerSendingData :: Path Abs (Dir TelemetryCacheDir) -> UserSignature -> ProjectHash -> Command.Call.Call -> IO ()
|
||||
considerSendingData :: Path' Abs (Dir TelemetryCacheDir) -> UserSignature -> ProjectHash -> Command.Call.Call -> IO ()
|
||||
considerSendingData telemetryCacheDirPath userSignature projectHash cmdCall = do
|
||||
projectCache <- readOrCreateProjectTelemetryFile telemetryCacheDirPath projectHash
|
||||
|
||||
@ -96,28 +96,28 @@ initialCache = ProjectTelemetryCache {_lastCheckIn = Nothing, _lastCheckInBuild
|
||||
getTimeOfLastTelemetryDataSent :: ProjectTelemetryCache -> Maybe T.UTCTime
|
||||
getTimeOfLastTelemetryDataSent cache = maximum [_lastCheckIn cache, _lastCheckInBuild cache]
|
||||
|
||||
readProjectTelemetryFile :: Path Abs (Dir TelemetryCacheDir) -> ProjectHash -> IO (Maybe ProjectTelemetryCache)
|
||||
readProjectTelemetryFile :: Path' Abs (Dir TelemetryCacheDir) -> ProjectHash -> IO (Maybe ProjectTelemetryCache)
|
||||
readProjectTelemetryFile telemetryCacheDirPath projectHash = do
|
||||
fileExists <- SD.doesFileExist filePathFP
|
||||
if fileExists then readCacheFile else return Nothing
|
||||
where
|
||||
filePathFP = SP.toFilePath $ getProjectTelemetryFilePath telemetryCacheDirPath projectHash
|
||||
filePathFP = SP.fromAbsFile $ getProjectTelemetryFilePath telemetryCacheDirPath projectHash
|
||||
readCacheFile = Aeson.decode . ByteStringLazyUTF8.fromString <$> readFile filePathFP
|
||||
|
||||
readOrCreateProjectTelemetryFile :: Path Abs (Dir TelemetryCacheDir) -> ProjectHash -> IO ProjectTelemetryCache
|
||||
readOrCreateProjectTelemetryFile :: Path' Abs (Dir TelemetryCacheDir) -> ProjectHash -> IO ProjectTelemetryCache
|
||||
readOrCreateProjectTelemetryFile telemetryCacheDirPath projectHash = do
|
||||
maybeProjectTelemetryCache <- readProjectTelemetryFile telemetryCacheDirPath projectHash
|
||||
case maybeProjectTelemetryCache of
|
||||
Just cache -> return cache
|
||||
Nothing -> writeProjectTelemetryFile telemetryCacheDirPath projectHash initialCache >> return initialCache
|
||||
|
||||
writeProjectTelemetryFile :: Path Abs (Dir TelemetryCacheDir) -> ProjectHash -> ProjectTelemetryCache -> IO ()
|
||||
writeProjectTelemetryFile :: Path' Abs (Dir TelemetryCacheDir) -> ProjectHash -> ProjectTelemetryCache -> IO ()
|
||||
writeProjectTelemetryFile telemetryCacheDirPath projectHash cache = do
|
||||
writeFile filePathFP (ByteStringLazyUTF8.toString $ Aeson.encode cache)
|
||||
where
|
||||
filePathFP = SP.toFilePath $ getProjectTelemetryFilePath telemetryCacheDirPath projectHash
|
||||
filePathFP = SP.fromAbsFile $ getProjectTelemetryFilePath telemetryCacheDirPath projectHash
|
||||
|
||||
getProjectTelemetryFilePath :: Path Abs (Dir TelemetryCacheDir) -> ProjectHash -> Path Abs File
|
||||
getProjectTelemetryFilePath :: Path' Abs (Dir TelemetryCacheDir) -> ProjectHash -> Path' Abs File'
|
||||
getProjectTelemetryFilePath telemetryCacheDir (ProjectHash projectHash) =
|
||||
telemetryCacheDir SP.</> fromJust (SP.parseRelFile $ "project-" ++ projectHash)
|
||||
|
||||
|
@ -8,18 +8,17 @@ where
|
||||
|
||||
import Command.Telemetry.Common (TelemetryCacheDir)
|
||||
import qualified Data.UUID.V4 as UUID
|
||||
import Path (relfile)
|
||||
import StrongPath (Abs, Dir, File, Path)
|
||||
import StrongPath (Abs, Dir, File', Path', relfile)
|
||||
import qualified StrongPath as SP
|
||||
import qualified System.Directory as SD
|
||||
|
||||
-- Random, non-identifyable UUID used to represent user in analytics.
|
||||
newtype UserSignature = UserSignature {_userSignatureValue :: String} deriving (Show)
|
||||
|
||||
readOrCreateUserSignatureFile :: Path Abs (Dir TelemetryCacheDir) -> IO UserSignature
|
||||
readOrCreateUserSignatureFile :: Path' Abs (Dir TelemetryCacheDir) -> IO UserSignature
|
||||
readOrCreateUserSignatureFile telemetryCacheDirPath = do
|
||||
let filePath = getUserSignatureFilePath telemetryCacheDirPath
|
||||
let filePathFP = SP.toFilePath filePath
|
||||
let filePathFP = SP.fromAbsFile filePath
|
||||
fileExists <- SD.doesFileExist filePathFP
|
||||
UserSignature
|
||||
<$> if fileExists
|
||||
@ -29,5 +28,5 @@ readOrCreateUserSignatureFile telemetryCacheDirPath = do
|
||||
writeFile filePathFP userSignature
|
||||
return userSignature
|
||||
|
||||
getUserSignatureFilePath :: Path Abs (Dir TelemetryCacheDir) -> Path Abs File
|
||||
getUserSignatureFilePath telemetryCacheDir = telemetryCacheDir SP.</> SP.fromPathRelFile [relfile|signature|]
|
||||
getUserSignatureFilePath :: Path' Abs (Dir TelemetryCacheDir) -> Path' Abs File'
|
||||
getUserSignatureFilePath telemetryCacheDir = telemetryCacheDir SP.</> [relfile|signature|]
|
||||
|
@ -10,7 +10,7 @@ import Control.Concurrent.Chan (Chan, newChan, readChan)
|
||||
import Data.List (isSuffixOf)
|
||||
import Data.Time.Clock (UTCTime, getCurrentTime)
|
||||
import qualified Lib
|
||||
import StrongPath (Abs, Dir, Path, (</>))
|
||||
import StrongPath (Abs, Dir, Path', (</>))
|
||||
import qualified StrongPath as SP
|
||||
import qualified System.FSNotify as FSN
|
||||
import qualified System.FilePath as FP
|
||||
@ -29,12 +29,12 @@ import qualified System.FilePath as FP
|
||||
|
||||
-- | Forever listens for any file changes in waspProjectDir, and if there is a change,
|
||||
-- compiles Wasp source files in waspProjectDir and regenerates files in outDir.
|
||||
watch :: Path Abs (Dir Common.WaspProjectDir) -> Path Abs (Dir Lib.ProjectRootDir) -> IO ()
|
||||
watch :: Path' Abs (Dir Common.WaspProjectDir) -> Path' Abs (Dir Lib.ProjectRootDir) -> IO ()
|
||||
watch waspProjectDir outDir = FSN.withManager $ \mgr -> do
|
||||
currentTime <- getCurrentTime
|
||||
chan <- newChan
|
||||
_ <- FSN.watchDirChan mgr (SP.toFilePath waspProjectDir) eventFilter chan
|
||||
_ <- FSN.watchTreeChan mgr (SP.toFilePath $ waspProjectDir </> Common.extCodeDirInWaspProjectDir) eventFilter chan
|
||||
_ <- FSN.watchDirChan mgr (SP.fromAbsDir waspProjectDir) eventFilter chan
|
||||
_ <- FSN.watchTreeChan mgr (SP.fromAbsDir $ waspProjectDir </> Common.extCodeDirInWaspProjectDir) eventFilter chan
|
||||
listenForEvents chan currentTime
|
||||
where
|
||||
listenForEvents :: Chan FSN.Event -> UTCTime -> IO ()
|
||||
|
@ -0,0 +1,18 @@
|
||||
-- CreateTable
|
||||
CREATE TABLE "User" (
|
||||
"id" INTEGER NOT NULL PRIMARY KEY AUTOINCREMENT,
|
||||
"email" TEXT NOT NULL,
|
||||
"password" TEXT NOT NULL
|
||||
);
|
||||
|
||||
-- CreateTable
|
||||
CREATE TABLE "Task" (
|
||||
"id" INTEGER NOT NULL PRIMARY KEY AUTOINCREMENT,
|
||||
"description" TEXT NOT NULL,
|
||||
"isDone" BOOLEAN NOT NULL DEFAULT false,
|
||||
"userId" INTEGER NOT NULL,
|
||||
FOREIGN KEY ("userId") REFERENCES "User" ("id") ON DELETE CASCADE ON UPDATE CASCADE
|
||||
);
|
||||
|
||||
-- CreateIndex
|
||||
CREATE UNIQUE INDEX "User.email_unique" ON "User"("email");
|
3
waspc/examples/todoApp/migrations/migration_lock.toml
Normal file
3
waspc/examples/todoApp/migrations/migration_lock.toml
Normal file
@ -0,0 +1,3 @@
|
||||
# Please do not edit this file manually
|
||||
# It should be added in your version-control system (i.e. Git)
|
||||
provider = "sqlite"
|
@ -2,7 +2,7 @@
|
||||
# Cabal file when you run `stack build`. See the hpack website for help with
|
||||
# this file: <https://github.com/sol/hpack>.
|
||||
name: waspc
|
||||
version: 0.2.0.1 # %WASP_VERSION% - annotation for new-release script.
|
||||
version: 0.2.1.0 # %WASP_VERSION% - annotation for new-release script.
|
||||
github: "Martinsos/waspc"
|
||||
license: MIT
|
||||
author: "wasp-lang"
|
||||
@ -64,6 +64,7 @@ library:
|
||||
- utf8-string
|
||||
- Glob
|
||||
- unliftio
|
||||
- strong-path
|
||||
|
||||
executables:
|
||||
wasp:
|
||||
@ -89,6 +90,7 @@ executables:
|
||||
- aeson
|
||||
- utf8-string
|
||||
- http-conduit
|
||||
- strong-path
|
||||
|
||||
benchmarks:
|
||||
waspc-benchmarks:
|
||||
@ -125,3 +127,4 @@ tests:
|
||||
- deepseq
|
||||
- path
|
||||
- unordered-containers
|
||||
- strong-path
|
||||
|
@ -4,12 +4,12 @@ module CompileOptions
|
||||
where
|
||||
|
||||
import ExternalCode (SourceExternalCodeDir)
|
||||
import StrongPath (Abs, Dir, Path)
|
||||
import StrongPath (Abs, Dir, Path')
|
||||
|
||||
-- TODO(martin): Should these be merged with Wasp data? Is it really a separate thing or not?
|
||||
-- It would be easier to pass around if it is part of Wasp data. But is it semantically correct?
|
||||
-- Maybe it is, even more than this!
|
||||
data CompileOptions = CompileOptions
|
||||
{ externalCodeDirPath :: !(Path Abs (Dir SourceExternalCodeDir)),
|
||||
{ externalCodeDirPath :: !(Path' Abs (Dir SourceExternalCodeDir)),
|
||||
isBuild :: !Bool
|
||||
}
|
||||
|
@ -5,10 +5,10 @@ module Data
|
||||
where
|
||||
|
||||
import qualified Paths_waspc
|
||||
import StrongPath (Abs, Dir, Path)
|
||||
import StrongPath (Abs, Dir, Path')
|
||||
import qualified StrongPath as SP
|
||||
|
||||
data DataDir
|
||||
|
||||
getAbsDataDirPath :: IO (Path Abs (Dir DataDir))
|
||||
getAbsDataDirPath :: IO (Path' Abs (Dir DataDir))
|
||||
getAbsDataDirPath = Paths_waspc.getDataDir >>= SP.parseAbsDir
|
||||
|
@ -12,9 +12,9 @@ import Data.Maybe (catMaybes)
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text.Lazy as TextL
|
||||
import qualified Data.Text.Lazy.IO as TextL.IO
|
||||
import qualified Path as P
|
||||
import StrongPath (Abs, Dir, Path, Rel, (</>))
|
||||
import StrongPath (Abs, Dir, File', Path', Rel, relfile, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import qualified StrongPath.Path as SP.Path
|
||||
import System.IO.Error (isDoesNotExistError)
|
||||
import UnliftIO.Exception (catch, throwIO)
|
||||
import qualified Util.IO
|
||||
@ -24,8 +24,8 @@ import WaspignoreFile (ignores, readWaspignoreFile)
|
||||
data SourceExternalCodeDir
|
||||
|
||||
data File = File
|
||||
{ _pathInExtCodeDir :: !(Path (Rel SourceExternalCodeDir) SP.File),
|
||||
_extCodeDirPath :: !(Path Abs (Dir SourceExternalCodeDir)),
|
||||
{ _pathInExtCodeDir :: !(Path' (Rel SourceExternalCodeDir) File'),
|
||||
_extCodeDirPath :: !(Path' Abs (Dir SourceExternalCodeDir)),
|
||||
-- | File content. It will throw error when evaluated if file is not textual file.
|
||||
_text :: TextL.Text
|
||||
}
|
||||
@ -37,7 +37,7 @@ instance Eq File where
|
||||
f1 == f2 = _pathInExtCodeDir f1 == _pathInExtCodeDir f2
|
||||
|
||||
-- | Returns path relative to the external code directory.
|
||||
filePathInExtCodeDir :: File -> Path (Rel SourceExternalCodeDir) SP.File
|
||||
filePathInExtCodeDir :: File -> Path' (Rel SourceExternalCodeDir) File'
|
||||
filePathInExtCodeDir = _pathInExtCodeDir
|
||||
|
||||
-- | Unsafe method: throws error if text could not be read (if file is not a textual file)!
|
||||
@ -45,22 +45,22 @@ fileText :: File -> Text
|
||||
fileText = TextL.toStrict . _text
|
||||
|
||||
-- | Returns absolute path of the external code file.
|
||||
fileAbsPath :: ExternalCode.File -> Path Abs SP.File
|
||||
fileAbsPath :: ExternalCode.File -> Path' Abs File'
|
||||
fileAbsPath file = _extCodeDirPath file </> _pathInExtCodeDir file
|
||||
|
||||
waspignorePathInExtCodeDir :: Path (Rel SourceExternalCodeDir) SP.File
|
||||
waspignorePathInExtCodeDir = SP.fromPathRelFile [P.relfile|.waspignore|]
|
||||
waspignorePathInExtCodeDir :: Path' (Rel SourceExternalCodeDir) File'
|
||||
waspignorePathInExtCodeDir = [relfile|.waspignore|]
|
||||
|
||||
-- | Returns all files contained in the specified external code dir, recursively,
|
||||
-- except files ignores by the specified waspignore file.
|
||||
readFiles :: Path Abs (Dir SourceExternalCodeDir) -> IO [File]
|
||||
readFiles :: Path' Abs (Dir SourceExternalCodeDir) -> IO [File]
|
||||
readFiles extCodeDirPath = do
|
||||
let waspignoreFilePath = extCodeDirPath </> waspignorePathInExtCodeDir
|
||||
waspignoreFile <- readWaspignoreFile waspignoreFilePath
|
||||
relFilePaths <-
|
||||
filter (not . ignores waspignoreFile . SP.toFilePath)
|
||||
. map SP.fromPathRelFile
|
||||
<$> Util.IO.listDirectoryDeep (SP.toPathAbsDir extCodeDirPath)
|
||||
. map SP.Path.fromPathRelFile
|
||||
<$> Util.IO.listDirectoryDeep (SP.Path.toPathAbsDir extCodeDirPath)
|
||||
let absFilePaths = map (extCodeDirPath </>) relFilePaths
|
||||
-- NOTE: We read text from all the files, regardless if they are text files or not, because
|
||||
-- we don't know if they are a text file or not.
|
||||
|
@ -1,11 +1,9 @@
|
||||
module Path.Extra
|
||||
module FilePath.Extra
|
||||
( reversePosixPath,
|
||||
toPosixFilePath,
|
||||
)
|
||||
where
|
||||
|
||||
import Control.Exception (assert)
|
||||
import Path
|
||||
import qualified System.FilePath.Posix as FPP
|
||||
|
||||
-- | For given posix path P, returns posix path P', such that (terminal pseudocode incoming)
|
||||
@ -22,6 +20,3 @@ reversePosixPath path
|
||||
where
|
||||
parts :: [String]
|
||||
parts = filter (/= ".") $ FPP.splitDirectories path
|
||||
|
||||
toPosixFilePath :: Path Rel a -> FilePath
|
||||
toPosixFilePath path = map (\c -> if c == '\\' then '/' else c) $ toFilePath path
|
@ -19,9 +19,8 @@ import qualified Generator.ServerGenerator as ServerGenerator
|
||||
import qualified Generator.Setup
|
||||
import qualified Generator.Start
|
||||
import Generator.WebAppGenerator (generateWebApp)
|
||||
import qualified Path as P
|
||||
import qualified Paths_waspc
|
||||
import StrongPath (Abs, Dir, Path, (</>))
|
||||
import StrongPath (Abs, Dir, Path', relfile, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import Wasp (Wasp)
|
||||
|
||||
@ -30,7 +29,7 @@ import Wasp (Wasp)
|
||||
-- NOTE(martin): What if there is already smth in the dstDir? It is probably best
|
||||
-- if we clean it up first? But we don't want this to end up with us deleting stuff
|
||||
-- from user's machine. Maybe we just overwrite and we are good?
|
||||
writeWebAppCode :: Wasp -> Path Abs (Dir ProjectRootDir) -> CompileOptions -> IO ()
|
||||
writeWebAppCode :: Wasp -> Path' Abs (Dir ProjectRootDir) -> CompileOptions -> IO ()
|
||||
writeWebAppCode wasp dstDir compileOptions = do
|
||||
writeFileDrafts dstDir (generateWebApp wasp compileOptions)
|
||||
ServerGenerator.preCleanup wasp dstDir compileOptions
|
||||
@ -42,14 +41,14 @@ writeWebAppCode wasp dstDir compileOptions = do
|
||||
-- | Writes file drafts while using given destination dir as root dir.
|
||||
-- TODO(martin): We could/should parallelize this.
|
||||
-- We could also skip writing files that are already on the disk with same checksum.
|
||||
writeFileDrafts :: Path Abs (Dir ProjectRootDir) -> [FileDraft] -> IO ()
|
||||
writeFileDrafts :: Path' Abs (Dir ProjectRootDir) -> [FileDraft] -> IO ()
|
||||
writeFileDrafts dstDir = mapM_ (write dstDir)
|
||||
|
||||
-- | Writes .waspinfo, which contains some basic metadata about how/when wasp generated the code.
|
||||
writeDotWaspInfo :: Path Abs (Dir ProjectRootDir) -> IO ()
|
||||
writeDotWaspInfo :: Path' Abs (Dir ProjectRootDir) -> IO ()
|
||||
writeDotWaspInfo dstDir = do
|
||||
currentTime <- getCurrentTime
|
||||
let version = Data.Version.showVersion Paths_waspc.version
|
||||
let content = "Generated on " ++ (show currentTime) ++ " by waspc version " ++ (show version) ++ " ."
|
||||
let dstPath = dstDir </> SP.fromPathRelFile [P.relfile|.waspinfo|]
|
||||
let content = "Generated on " ++ show currentTime ++ " by waspc version " ++ show version ++ " ."
|
||||
let dstPath = dstDir </> [relfile|.waspinfo|]
|
||||
Data.Text.IO.writeFile (SP.toFilePath dstPath) (Data.Text.pack content)
|
||||
|
@ -11,10 +11,9 @@ import Data.Maybe (fromMaybe)
|
||||
import Generator.Common (ProjectRootDir)
|
||||
import Generator.FileDraft (FileDraft, createTemplateFileDraft)
|
||||
import Generator.Templates (TemplatesDir)
|
||||
import qualified Path as P
|
||||
import qualified Psl.Ast.Model
|
||||
import qualified Psl.Generator.Model
|
||||
import StrongPath (Dir, File, Path, Rel, (</>))
|
||||
import StrongPath (Dir, File', Path', Rel, reldir, relfile, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import Wasp (Wasp)
|
||||
import qualified Wasp
|
||||
@ -28,21 +27,21 @@ data DbRootDir
|
||||
|
||||
data DbTemplatesDir
|
||||
|
||||
dbRootDirInProjectRootDir :: Path (Rel ProjectRootDir) (Dir DbRootDir)
|
||||
dbRootDirInProjectRootDir = SP.fromPathRelDir [P.reldir|db|]
|
||||
dbRootDirInProjectRootDir :: Path' (Rel ProjectRootDir) (Dir DbRootDir)
|
||||
dbRootDirInProjectRootDir = [reldir|db|]
|
||||
|
||||
dbTemplatesDirInTemplatesDir :: Path (Rel TemplatesDir) (Dir DbTemplatesDir)
|
||||
dbTemplatesDirInTemplatesDir = SP.fromPathRelDir [P.reldir|db|]
|
||||
dbTemplatesDirInTemplatesDir :: Path' (Rel TemplatesDir) (Dir DbTemplatesDir)
|
||||
dbTemplatesDirInTemplatesDir = [reldir|db|]
|
||||
|
||||
dbSchemaFileInDbTemplatesDir :: Path (Rel DbTemplatesDir) File
|
||||
dbSchemaFileInDbTemplatesDir = SP.fromPathRelFile [P.relfile|schema.prisma|]
|
||||
dbSchemaFileInDbTemplatesDir :: Path' (Rel DbTemplatesDir) File'
|
||||
dbSchemaFileInDbTemplatesDir = [relfile|schema.prisma|]
|
||||
|
||||
dbSchemaFileInDbRootDir :: Path (Rel DbRootDir) File
|
||||
dbSchemaFileInDbRootDir :: Path' (Rel DbRootDir) File'
|
||||
-- Generated schema file will be in the same relative location as the
|
||||
-- template file within templates dir.
|
||||
dbSchemaFileInDbRootDir = SP.castRel dbSchemaFileInDbTemplatesDir
|
||||
|
||||
dbSchemaFileInProjectRootDir :: Path (Rel ProjectRootDir) File
|
||||
dbSchemaFileInProjectRootDir :: Path' (Rel ProjectRootDir) File'
|
||||
dbSchemaFileInProjectRootDir = dbRootDirInProjectRootDir </> dbSchemaFileInDbRootDir
|
||||
|
||||
-- * Db generator
|
||||
|
@ -9,11 +9,11 @@ import Generator.DbGenerator (dbSchemaFileInProjectRootDir)
|
||||
import qualified Generator.Job as J
|
||||
import Generator.Job.Process (runNodeCommandAsJob)
|
||||
import Generator.ServerGenerator.Common (serverRootDirInProjectRootDir)
|
||||
import StrongPath (Abs, Dir, Path, (</>))
|
||||
import StrongPath (Abs, Dir, Path', (</>))
|
||||
import qualified StrongPath as SP
|
||||
import qualified System.Info
|
||||
|
||||
migrateDev :: Path Abs (Dir ProjectRootDir) -> J.Job
|
||||
migrateDev :: Path' Abs (Dir ProjectRootDir) -> J.Job
|
||||
migrateDev projectDir = do
|
||||
let serverDir = projectDir </> serverRootDirInProjectRootDir
|
||||
let schemaFile = projectDir </> dbSchemaFileInProjectRootDir
|
||||
@ -38,7 +38,7 @@ migrateDev projectDir = do
|
||||
runNodeCommandAsJob serverDir "script" scriptArgs J.Db
|
||||
|
||||
-- | Runs `prisma studio` - Prisma's db inspector.
|
||||
runStudio :: Path Abs (Dir ProjectRootDir) -> J.Job
|
||||
runStudio :: Path' Abs (Dir ProjectRootDir) -> J.Job
|
||||
runStudio projectDir = do
|
||||
let serverDir = projectDir </> serverRootDirInProjectRootDir
|
||||
let schemaFile = projectDir </> dbSchemaFileInProjectRootDir
|
||||
|
@ -10,7 +10,7 @@ import qualified Generator.DbGenerator.Jobs as DbJobs
|
||||
import Generator.Job (JobMessage)
|
||||
import qualified Generator.Job as J
|
||||
import Generator.Job.IO (printJobMessage)
|
||||
import StrongPath (Abs, Dir, Path)
|
||||
import StrongPath (Abs, Dir, Path')
|
||||
import System.Exit (ExitCode (..))
|
||||
|
||||
printJobMsgsUntilExitReceived :: Chan JobMessage -> IO ()
|
||||
@ -20,7 +20,7 @@ printJobMsgsUntilExitReceived chan = do
|
||||
J.JobOutput {} -> printJobMessage jobMsg >> printJobMsgsUntilExitReceived chan
|
||||
J.JobExit {} -> return ()
|
||||
|
||||
migrateDev :: Path Abs (Dir ProjectRootDir) -> IO (Either String ())
|
||||
migrateDev :: Path' Abs (Dir ProjectRootDir) -> IO (Either String ())
|
||||
migrateDev projectDir = do
|
||||
chan <- newChan
|
||||
(_, dbExitCode) <-
|
||||
|
@ -8,9 +8,7 @@ import Data.Aeson (object, (.=))
|
||||
import Generator.Common (ProjectRootDir)
|
||||
import Generator.FileDraft (FileDraft, createTemplateFileDraft)
|
||||
import Generator.Templates (TemplatesDir)
|
||||
import qualified Path as P
|
||||
import StrongPath (File, Path, Rel)
|
||||
import qualified StrongPath as SP
|
||||
import StrongPath (File', Path', Rel, relfile)
|
||||
import Wasp (Wasp)
|
||||
import qualified Wasp
|
||||
|
||||
@ -25,8 +23,8 @@ genDockerFiles wasp _ =
|
||||
genDockerfile :: Wasp -> FileDraft
|
||||
genDockerfile wasp =
|
||||
createTemplateFileDraft
|
||||
(SP.fromPathRelFile [P.relfile|Dockerfile|] :: Path (Rel ProjectRootDir) File)
|
||||
(SP.fromPathRelFile [P.relfile|Dockerfile|] :: Path (Rel TemplatesDir) File)
|
||||
([relfile|Dockerfile|] :: Path' (Rel ProjectRootDir) File')
|
||||
([relfile|Dockerfile|] :: Path' (Rel TemplatesDir) File')
|
||||
( Just $
|
||||
object
|
||||
[ "usingPrisma" .= not (null $ Wasp.getPSLEntities wasp)
|
||||
@ -36,6 +34,6 @@ genDockerfile wasp =
|
||||
genDockerignore :: Wasp -> FileDraft
|
||||
genDockerignore _ =
|
||||
createTemplateFileDraft
|
||||
(SP.fromPathRelFile [P.relfile|.dockerignore|] :: Path (Rel ProjectRootDir) File)
|
||||
(SP.fromPathRelFile [P.relfile|dockerignore|] :: Path (Rel TemplatesDir) File)
|
||||
([relfile|.dockerignore|] :: Path' (Rel ProjectRootDir) File')
|
||||
([relfile|dockerignore|] :: Path' (Rel TemplatesDir) File')
|
||||
Nothing
|
||||
|
@ -7,7 +7,7 @@ import qualified ExternalCode as EC
|
||||
import qualified Generator.ExternalCodeGenerator.Common as C
|
||||
import Generator.ExternalCodeGenerator.Js (generateJsFile)
|
||||
import qualified Generator.FileDraft as FD
|
||||
import StrongPath (File, Path, Rel, (</>))
|
||||
import StrongPath (File', Path', Rel, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import qualified System.FilePath as FP
|
||||
import Wasp (Wasp)
|
||||
@ -26,13 +26,11 @@ generateFile :: C.ExternalCodeGeneratorStrategy -> EC.File -> FD.FileDraft
|
||||
generateFile strategy file
|
||||
| extension `elem` [".js", ".jsx"] = generateJsFile strategy file
|
||||
| otherwise =
|
||||
let relDstPath =
|
||||
(C._extCodeDirInProjectRootDir strategy)
|
||||
</> dstPathInGenExtCodeDir
|
||||
let relDstPath = C._extCodeDirInProjectRootDir strategy </> dstPathInGenExtCodeDir
|
||||
absSrcPath = EC.fileAbsPath file
|
||||
in FD.createCopyFileDraft relDstPath absSrcPath
|
||||
where
|
||||
dstPathInGenExtCodeDir :: Path (Rel C.GeneratedExternalCodeDir) File
|
||||
dstPathInGenExtCodeDir :: Path' (Rel C.GeneratedExternalCodeDir) File'
|
||||
dstPathInGenExtCodeDir = C.castRelPathFromSrcToGenExtCodeDir $ EC.filePathInExtCodeDir file
|
||||
|
||||
extension = FP.takeExtension $ SP.toFilePath $ EC.filePathInExtCodeDir file
|
||||
|
@ -9,23 +9,22 @@ where
|
||||
import Data.Text (Text)
|
||||
import ExternalCode (SourceExternalCodeDir)
|
||||
import Generator.Common (ProjectRootDir)
|
||||
import qualified Path as P
|
||||
import StrongPath (Dir, File, Path, Rel)
|
||||
import StrongPath (Dir, File', Path', Rel)
|
||||
import qualified StrongPath as SP
|
||||
|
||||
-- | Path to the directory where ext code will be generated.
|
||||
data GeneratedExternalCodeDir
|
||||
|
||||
asGenExtFile :: P.Path P.Rel P.File -> Path (Rel GeneratedExternalCodeDir) File
|
||||
asGenExtFile = SP.fromPathRelFile
|
||||
asGenExtFile :: Path' (Rel d) File' -> Path' (Rel GeneratedExternalCodeDir) File'
|
||||
asGenExtFile = SP.castRel
|
||||
|
||||
castRelPathFromSrcToGenExtCodeDir :: Path (Rel SourceExternalCodeDir) a -> Path (Rel GeneratedExternalCodeDir) a
|
||||
castRelPathFromSrcToGenExtCodeDir :: Path' (Rel SourceExternalCodeDir) a -> Path' (Rel GeneratedExternalCodeDir) a
|
||||
castRelPathFromSrcToGenExtCodeDir = SP.castRel
|
||||
|
||||
data ExternalCodeGeneratorStrategy = ExternalCodeGeneratorStrategy
|
||||
{ -- | Takes a path where the external code js file will be generated.
|
||||
-- Also takes text of the file. Returns text where special @wasp imports have been replaced with
|
||||
-- imports that will work.
|
||||
_resolveJsFileWaspImports :: Path (Rel GeneratedExternalCodeDir) File -> Text -> Text,
|
||||
_extCodeDirInProjectRootDir :: Path (Rel ProjectRootDir) (Dir GeneratedExternalCodeDir)
|
||||
_resolveJsFileWaspImports :: Path' (Rel GeneratedExternalCodeDir) File' -> Text -> Text,
|
||||
_extCodeDirInProjectRootDir :: Path' (Rel ProjectRootDir) (Dir GeneratedExternalCodeDir)
|
||||
}
|
||||
|
@ -4,14 +4,15 @@ module Generator.ExternalCodeGenerator.Js
|
||||
)
|
||||
where
|
||||
|
||||
import Data.Maybe (fromJust)
|
||||
import Data.Text (Text, unpack)
|
||||
import qualified Data.Text as T
|
||||
import qualified ExternalCode as EC
|
||||
import FilePath.Extra (reversePosixPath)
|
||||
import Generator.ExternalCodeGenerator.Common (GeneratedExternalCodeDir)
|
||||
import qualified Generator.ExternalCodeGenerator.Common as C
|
||||
import qualified Generator.FileDraft as FD
|
||||
import Path.Extra (reversePosixPath, toPosixFilePath)
|
||||
import StrongPath (Dir, File, Path, Rel, (</>))
|
||||
import StrongPath (Dir, File', Path', Rel, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import qualified Text.Regex.TDFA as TR
|
||||
|
||||
@ -20,19 +21,19 @@ generateJsFile strategy file = FD.createTextFileDraft dstPath text'
|
||||
where
|
||||
filePathInSrcExtCodeDir = EC.filePathInExtCodeDir file
|
||||
|
||||
filePathInGenExtCodeDir :: Path (Rel C.GeneratedExternalCodeDir) File
|
||||
filePathInGenExtCodeDir :: Path' (Rel C.GeneratedExternalCodeDir) File'
|
||||
filePathInGenExtCodeDir = C.castRelPathFromSrcToGenExtCodeDir filePathInSrcExtCodeDir
|
||||
|
||||
text = EC.fileText file
|
||||
text' = (C._resolveJsFileWaspImports strategy) filePathInGenExtCodeDir text
|
||||
dstPath = (C._extCodeDirInProjectRootDir strategy) </> filePathInGenExtCodeDir
|
||||
dstPath = C._extCodeDirInProjectRootDir strategy </> filePathInGenExtCodeDir
|
||||
|
||||
-- | Replaces imports that start with "@wasp/" with imports that start from the src dir of the app.
|
||||
resolveJsFileWaspImportsForExtCodeDir ::
|
||||
-- | Relative path of ext code dir in src dir of app (web app, server (app), ...)
|
||||
Path (Rel ()) (Dir GeneratedExternalCodeDir) ->
|
||||
Path' (Rel ()) (Dir GeneratedExternalCodeDir) ->
|
||||
-- | Path where this JS file will be generated.
|
||||
Path (Rel GeneratedExternalCodeDir) File ->
|
||||
Path' (Rel GeneratedExternalCodeDir) File' ->
|
||||
-- | Original text of the file.
|
||||
Text ->
|
||||
-- | Text of the file with special "@wasp" imports resolved (replaced with normal JS imports).
|
||||
@ -42,6 +43,6 @@ resolveJsFileWaspImportsForExtCodeDir extCodeDirInAppSrcDir jsFileDstPathInExtCo
|
||||
in foldr replaceFromWasp jsFileText matches
|
||||
where
|
||||
replaceFromWasp fromWasp = T.replace (T.pack fromWasp) (T.pack $ transformFromWasp fromWasp)
|
||||
transformFromWasp fromWasp = (reverse $ drop (length ("@wasp/" :: String)) $ reverse fromWasp) ++ pathPrefix ++ "/"
|
||||
pathPrefix = reversePosixPath $ toPosixFilePath $ SP.toPathRelDir $ SP.parent jsFileDstPathInAppSrcDir
|
||||
transformFromWasp fromWasp = reverse (drop (length ("@wasp/" :: String)) $ reverse fromWasp) ++ pathPrefix ++ "/"
|
||||
pathPrefix = reversePosixPath $ SP.fromRelDirP $ fromJust $ SP.relDirToPosix $ SP.parent jsFileDstPathInAppSrcDir
|
||||
jsFileDstPathInAppSrcDir = extCodeDirInAppSrcDir </> jsFileDstPathInExtCodeDir
|
||||
|
@ -16,7 +16,7 @@ import qualified Generator.FileDraft.TemplateFileDraft as TmplFD
|
||||
import qualified Generator.FileDraft.TextFileDraft as TextFD
|
||||
import Generator.FileDraft.Writeable
|
||||
import Generator.Templates (TemplatesDir)
|
||||
import StrongPath (Abs, File, Path, Rel)
|
||||
import StrongPath (Abs, File', Path', Rel)
|
||||
|
||||
-- | FileDraft unites different file draft types into a single type,
|
||||
-- so that in the rest of the system they can be passed around as heterogeneous
|
||||
@ -33,8 +33,8 @@ instance Writeable FileDraft where
|
||||
write dstDir (FileDraftTextFd draft) = write dstDir draft
|
||||
|
||||
createTemplateFileDraft ::
|
||||
Path (Rel ProjectRootDir) File ->
|
||||
Path (Rel TemplatesDir) File ->
|
||||
Path' (Rel ProjectRootDir) File' ->
|
||||
Path' (Rel TemplatesDir) File' ->
|
||||
Maybe Aeson.Value ->
|
||||
FileDraft
|
||||
createTemplateFileDraft dstPath tmplSrcPath tmplData =
|
||||
@ -45,7 +45,7 @@ createTemplateFileDraft dstPath tmplSrcPath tmplData =
|
||||
TmplFD._tmplData = tmplData
|
||||
}
|
||||
|
||||
createCopyFileDraft :: Path (Rel ProjectRootDir) File -> Path Abs File -> FileDraft
|
||||
createCopyFileDraft :: Path' (Rel ProjectRootDir) File' -> Path' Abs File' -> FileDraft
|
||||
createCopyFileDraft dstPath srcPath =
|
||||
FileDraftCopyFd $
|
||||
CopyFD.CopyFileDraft
|
||||
@ -54,7 +54,7 @@ createCopyFileDraft dstPath srcPath =
|
||||
CopyFD._failIfSrcDoesNotExist = True
|
||||
}
|
||||
|
||||
createCopyFileDraftIfExists :: Path (Rel ProjectRootDir) File -> Path Abs File -> FileDraft
|
||||
createCopyFileDraftIfExists :: Path' (Rel ProjectRootDir) File' -> Path' Abs File' -> FileDraft
|
||||
createCopyFileDraftIfExists dstPath srcPath =
|
||||
FileDraftCopyFd $
|
||||
CopyFD.CopyFileDraft
|
||||
@ -63,6 +63,6 @@ createCopyFileDraftIfExists dstPath srcPath =
|
||||
CopyFD._failIfSrcDoesNotExist = False
|
||||
}
|
||||
|
||||
createTextFileDraft :: Path (Rel ProjectRootDir) File -> Text -> FileDraft
|
||||
createTextFileDraft :: Path' (Rel ProjectRootDir) File' -> Text -> FileDraft
|
||||
createTextFileDraft dstPath content =
|
||||
FileDraftTextFd $ TextFD.TextFileDraft {TextFD._dstPath = dstPath, TextFD._content = content}
|
||||
|
@ -9,8 +9,8 @@ import Generator.FileDraft.Writeable
|
||||
import Generator.FileDraft.WriteableMonad
|
||||
import StrongPath
|
||||
( Abs,
|
||||
File,
|
||||
Path,
|
||||
File',
|
||||
Path',
|
||||
Rel,
|
||||
(</>),
|
||||
)
|
||||
@ -20,9 +20,9 @@ import System.IO.Error (doesNotExistErrorType, mkIOError)
|
||||
-- | File draft based purely on another file, that is just copied.
|
||||
data CopyFileDraft = CopyFileDraft
|
||||
{ -- | Path where the file will be copied to.
|
||||
_dstPath :: !(Path (Rel ProjectRootDir) File),
|
||||
_dstPath :: !(Path' (Rel ProjectRootDir) File'),
|
||||
-- | Absolute path of source file to copy.
|
||||
_srcPath :: !(Path Abs File),
|
||||
_srcPath :: !(Path' Abs File'),
|
||||
_failIfSrcDoesNotExist :: Bool
|
||||
}
|
||||
deriving (Show, Eq)
|
||||
@ -32,8 +32,8 @@ instance Writeable CopyFileDraft where
|
||||
srcFileExists <- doesFileExist srcFilePath
|
||||
if srcFileExists
|
||||
then do
|
||||
createDirectoryIfMissing True (SP.toFilePath $ SP.parent absDraftDstPath)
|
||||
copyFile srcFilePath (SP.toFilePath absDraftDstPath)
|
||||
createDirectoryIfMissing True (SP.fromAbsDir $ SP.parent absDraftDstPath)
|
||||
copyFile srcFilePath (SP.fromAbsFile absDraftDstPath)
|
||||
else
|
||||
when
|
||||
(_failIfSrcDoesNotExist draft)
|
||||
@ -45,5 +45,5 @@ instance Writeable CopyFileDraft where
|
||||
(Just srcFilePath)
|
||||
)
|
||||
where
|
||||
srcFilePath = SP.toFilePath $ _srcPath draft
|
||||
srcFilePath = SP.fromAbsFile $ _srcPath draft
|
||||
absDraftDstPath = absDstDirPath </> _dstPath draft
|
||||
|
@ -8,15 +8,15 @@ import Generator.Common (ProjectRootDir)
|
||||
import Generator.FileDraft.Writeable
|
||||
import Generator.FileDraft.WriteableMonad
|
||||
import Generator.Templates (TemplatesDir)
|
||||
import StrongPath (Abs, File, Path, Rel, (</>))
|
||||
import StrongPath (Abs, File', Path', Rel, (</>))
|
||||
import qualified StrongPath as SP
|
||||
|
||||
-- | File draft based on template file that gets combined with data.
|
||||
data TemplateFileDraft = TemplateFileDraft
|
||||
{ -- | Path where file will be generated.
|
||||
_dstPath :: !(Path (Rel ProjectRootDir) File),
|
||||
_dstPath :: !(Path' (Rel ProjectRootDir) File'),
|
||||
-- | Path of template source file.
|
||||
_srcPathInTmplDir :: !(Path (Rel TemplatesDir) File),
|
||||
_srcPathInTmplDir :: !(Path' (Rel TemplatesDir) File'),
|
||||
-- | Data to be fed to the template while rendering it.
|
||||
_tmplData :: Maybe Aeson.Value
|
||||
}
|
||||
@ -24,14 +24,14 @@ data TemplateFileDraft = TemplateFileDraft
|
||||
|
||||
instance Writeable TemplateFileDraft where
|
||||
write absDstDirPath draft = do
|
||||
createDirectoryIfMissing True (SP.toFilePath $ SP.parent absDraftDstPath)
|
||||
createDirectoryIfMissing True (SP.fromAbsDir $ SP.parent absDraftDstPath)
|
||||
case _tmplData draft of
|
||||
Nothing -> do
|
||||
absDraftSrcPath <- getTemplateFileAbsPath (_srcPathInTmplDir draft)
|
||||
copyFile (SP.toFilePath absDraftSrcPath) (SP.toFilePath absDraftDstPath)
|
||||
copyFile (SP.fromAbsFile absDraftSrcPath) (SP.fromAbsFile absDraftDstPath)
|
||||
Just tmplData -> do
|
||||
content <- compileAndRenderTemplate (_srcPathInTmplDir draft) tmplData
|
||||
writeFileFromText (SP.toFilePath absDraftDstPath) content
|
||||
where
|
||||
absDraftDstPath :: Path Abs File
|
||||
absDraftDstPath = absDstDirPath </> (_dstPath draft)
|
||||
absDraftDstPath :: Path' Abs File'
|
||||
absDraftDstPath = absDstDirPath </> _dstPath draft
|
||||
|
@ -7,20 +7,20 @@ import Data.Text (Text)
|
||||
import Generator.Common (ProjectRootDir)
|
||||
import Generator.FileDraft.Writeable
|
||||
import Generator.FileDraft.WriteableMonad
|
||||
import StrongPath (File, Path, Rel, (</>))
|
||||
import StrongPath (File', Path', Rel, (</>))
|
||||
import qualified StrongPath as SP
|
||||
|
||||
-- | File draft based on text, that is to be written to file when time comes.
|
||||
data TextFileDraft = TextFileDraft
|
||||
{ -- | Path where file will be generated.
|
||||
_dstPath :: !(Path (Rel ProjectRootDir) File),
|
||||
_dstPath :: !(Path' (Rel ProjectRootDir) File'),
|
||||
_content :: Text
|
||||
}
|
||||
deriving (Show, Eq)
|
||||
|
||||
instance Writeable TextFileDraft where
|
||||
write dstDir draft = do
|
||||
createDirectoryIfMissing True (SP.toFilePath $ SP.parent absDraftDstPath)
|
||||
writeFileFromText (SP.toFilePath absDraftDstPath) (_content draft)
|
||||
createDirectoryIfMissing True (SP.fromAbsDir $ SP.parent absDraftDstPath)
|
||||
writeFileFromText (SP.fromAbsFile absDraftDstPath) (_content draft)
|
||||
where
|
||||
absDraftDstPath = dstDir </> (_dstPath draft)
|
||||
absDraftDstPath = dstDir </> _dstPath draft
|
||||
|
@ -5,12 +5,12 @@ where
|
||||
|
||||
import Generator.Common (ProjectRootDir)
|
||||
import Generator.FileDraft.WriteableMonad
|
||||
import StrongPath (Abs, Dir, Path)
|
||||
import StrongPath (Abs, Dir, Path')
|
||||
|
||||
class Writeable w where
|
||||
-- | Write file somewhere in the provided project root directory.
|
||||
write ::
|
||||
(WriteableMonad m) =>
|
||||
Path Abs (Dir ProjectRootDir) ->
|
||||
Path' Abs (Dir ProjectRootDir) ->
|
||||
w ->
|
||||
m ()
|
||||
|
@ -8,7 +8,7 @@ import Data.Aeson as Aeson
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text.IO
|
||||
import qualified Generator.Templates as Templates
|
||||
import StrongPath (Abs, Dir, File, Path, Rel)
|
||||
import StrongPath (Abs, Dir, File', Path', Rel)
|
||||
import qualified System.Directory
|
||||
import System.IO.Error (isDoesNotExistError)
|
||||
import UnliftIO.Exception (Exception, catch)
|
||||
@ -39,14 +39,14 @@ class (MonadIO m) => WriteableMonad m where
|
||||
|
||||
getTemplateFileAbsPath ::
|
||||
-- | Template file path.
|
||||
Path (Rel Templates.TemplatesDir) File ->
|
||||
m (Path Abs File)
|
||||
Path' (Rel Templates.TemplatesDir) File' ->
|
||||
m (Path' Abs File')
|
||||
|
||||
getTemplatesDirAbsPath :: m (Path Abs (Dir Templates.TemplatesDir))
|
||||
getTemplatesDirAbsPath :: m (Path' Abs (Dir Templates.TemplatesDir))
|
||||
|
||||
compileAndRenderTemplate ::
|
||||
-- | Template file path.
|
||||
Path (Rel Templates.TemplatesDir) File ->
|
||||
Path' (Rel Templates.TemplatesDir) File' ->
|
||||
-- | JSON to be provided as template data.
|
||||
Aeson.Value ->
|
||||
m Text
|
||||
|
@ -15,7 +15,7 @@ import qualified Data.Text as T
|
||||
import Data.Text.Encoding (decodeUtf8)
|
||||
import qualified Generator.Common as C
|
||||
import qualified Generator.Job as J
|
||||
import StrongPath (Abs, Dir, Path)
|
||||
import StrongPath (Abs, Dir, Path')
|
||||
import qualified StrongPath as SP
|
||||
import System.Exit (ExitCode (..))
|
||||
import System.IO.Error (catchIOError, isDoesNotExistError)
|
||||
@ -82,7 +82,7 @@ runProcessAsJob process jobType chan =
|
||||
P.terminateProcess processHandle
|
||||
return $ ExitFailure 1
|
||||
|
||||
runNodeCommandAsJob :: Path Abs (Dir a) -> String -> [String] -> J.JobType -> J.Job
|
||||
runNodeCommandAsJob :: Path' Abs (Dir a) -> String -> [String] -> J.JobType -> J.Job
|
||||
runNodeCommandAsJob fromDir command args jobType chan = do
|
||||
errorOrNodeVersion <- getNodeVersion
|
||||
case errorOrNodeVersion of
|
||||
@ -94,7 +94,7 @@ runNodeCommandAsJob fromDir command args jobType chan = do
|
||||
(ExitFailure 1)
|
||||
(T.pack $ "Your node version is too low. " ++ waspNodeRequirementMessage)
|
||||
else do
|
||||
let process = (P.proc command args) {P.cwd = Just $ SP.toFilePath fromDir}
|
||||
let process = (P.proc command args) {P.cwd = Just $ SP.fromAbsDir fromDir}
|
||||
runProcessAsJob process jobType chan
|
||||
where
|
||||
exitWithError exitCode errorMsg = do
|
||||
|
@ -34,8 +34,7 @@ import qualified Generator.ServerGenerator.ExternalCodeGenerator as ServerExtern
|
||||
import Generator.ServerGenerator.OperationsG (genOperations)
|
||||
import Generator.ServerGenerator.OperationsRoutesG (genOperationsRoutes)
|
||||
import qualified NpmDependency as ND
|
||||
import qualified Path as P
|
||||
import StrongPath (Abs, Dir, File, Path, Rel, (</>))
|
||||
import StrongPath (Abs, Dir, File', Path', Rel, reldir, relfile, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import System.Directory (removeFile)
|
||||
import System.IO.Error (isDoesNotExistError)
|
||||
@ -63,7 +62,7 @@ genServer wasp _ =
|
||||
-- TODO: Once we implement a fancier method of removing old/redundant files in outDir,
|
||||
-- we will not need this method any more. Check https://github.com/wasp-lang/wasp/issues/209
|
||||
-- for progress of this.
|
||||
preCleanup :: Wasp -> Path Abs (Dir ProjectRootDir) -> CompileOptions -> IO ()
|
||||
preCleanup :: Wasp -> Path' Abs (Dir ProjectRootDir) -> CompileOptions -> IO ()
|
||||
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.
|
||||
@ -82,17 +81,17 @@ genDotEnv wasp =
|
||||
]
|
||||
Nothing -> []
|
||||
|
||||
dotEnvInServerRootDir :: Path (Rel C.ServerRootDir) File
|
||||
dotEnvInServerRootDir = asServerFile [P.relfile|.env|]
|
||||
dotEnvInServerRootDir :: Path' (Rel C.ServerRootDir) File'
|
||||
dotEnvInServerRootDir = [relfile|.env|]
|
||||
|
||||
genReadme :: Wasp -> FileDraft
|
||||
genReadme _ = C.copyTmplAsIs (asTmplFile [P.relfile|README.md|])
|
||||
genReadme _ = C.copyTmplAsIs (asTmplFile [relfile|README.md|])
|
||||
|
||||
genPackageJson :: Wasp -> [ND.NpmDependency] -> [ND.NpmDependency] -> FileDraft
|
||||
genPackageJson wasp waspDeps waspDevDeps =
|
||||
C.makeTemplateFD
|
||||
(asTmplFile [P.relfile|package.json|])
|
||||
(asServerFile [P.relfile|package.json|])
|
||||
(asTmplFile [relfile|package.json|])
|
||||
(asServerFile [relfile|package.json|])
|
||||
( Just $
|
||||
object
|
||||
[ "wasp" .= wasp,
|
||||
@ -141,31 +140,31 @@ waspNpmDevDeps =
|
||||
genNpmrc :: Wasp -> FileDraft
|
||||
genNpmrc _ =
|
||||
C.makeTemplateFD
|
||||
(asTmplFile [P.relfile|npmrc|])
|
||||
(asServerFile [P.relfile|.npmrc|])
|
||||
(asTmplFile [relfile|npmrc|])
|
||||
(asServerFile [relfile|.npmrc|])
|
||||
Nothing
|
||||
|
||||
genNvmrc :: Wasp -> FileDraft
|
||||
genNvmrc _ =
|
||||
C.makeTemplateFD
|
||||
(asTmplFile [P.relfile|nvmrc|])
|
||||
(asServerFile [P.relfile|.nvmrc|])
|
||||
(asTmplFile [relfile|nvmrc|])
|
||||
(asServerFile [relfile|.nvmrc|])
|
||||
(Just (object ["nodeVersion" .= ('v' : nodeVersionAsText)]))
|
||||
|
||||
genGitignore :: Wasp -> FileDraft
|
||||
genGitignore _ =
|
||||
C.makeTemplateFD
|
||||
(asTmplFile [P.relfile|gitignore|])
|
||||
(asServerFile [P.relfile|.gitignore|])
|
||||
(asTmplFile [relfile|gitignore|])
|
||||
(asServerFile [relfile|.gitignore|])
|
||||
Nothing
|
||||
|
||||
genSrcDir :: Wasp -> [FileDraft]
|
||||
genSrcDir wasp =
|
||||
concat
|
||||
[ [C.copySrcTmplAsIs $ C.asTmplSrcFile [P.relfile|app.js|]],
|
||||
[C.copySrcTmplAsIs $ C.asTmplSrcFile [P.relfile|server.js|]],
|
||||
[C.copySrcTmplAsIs $ C.asTmplSrcFile [P.relfile|utils.js|]],
|
||||
[C.copySrcTmplAsIs $ C.asTmplSrcFile [P.relfile|core/HttpError.js|]],
|
||||
[ [C.copySrcTmplAsIs $ C.asTmplSrcFile [relfile|app.js|]],
|
||||
[C.copySrcTmplAsIs $ C.asTmplSrcFile [relfile|server.js|]],
|
||||
[C.copySrcTmplAsIs $ C.asTmplSrcFile [relfile|utils.js|]],
|
||||
[C.copySrcTmplAsIs $ C.asTmplSrcFile [relfile|core/HttpError.js|]],
|
||||
[genDbClient wasp],
|
||||
[genConfigFile wasp],
|
||||
genRoutesDir wasp,
|
||||
@ -179,8 +178,8 @@ genDbClient wasp = C.makeTemplateFD tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
maybeAuth = getAuth wasp
|
||||
|
||||
dbClientRelToSrcP = [P.relfile|dbClient.js|]
|
||||
tmplFile = C.asTmplFile $ [P.reldir|src|] P.</> dbClientRelToSrcP
|
||||
dbClientRelToSrcP = [relfile|dbClient.js|]
|
||||
tmplFile = C.asTmplFile $ [reldir|src|] </> dbClientRelToSrcP
|
||||
dstFile = C.serverSrcDirInServerRootDir </> C.asServerSrcFile dbClientRelToSrcP
|
||||
|
||||
tmplData =
|
||||
@ -197,8 +196,8 @@ genRoutesDir wasp =
|
||||
-- TODO(martin): We will probably want to extract "routes" path here same as we did with "src", to avoid hardcoding,
|
||||
-- but I did not bother with it yet since it is used only here for now.
|
||||
[ C.makeTemplateFD
|
||||
(asTmplFile [P.relfile|src/routes/index.js|])
|
||||
(asServerFile [P.relfile|src/routes/index.js|])
|
||||
(asTmplFile [relfile|src/routes/index.js|])
|
||||
(asServerFile [relfile|src/routes/index.js|])
|
||||
( Just $
|
||||
object
|
||||
[ "operationsRouteInRootRouter" .= operationsRouteInRootRouter,
|
||||
|
@ -6,8 +6,7 @@ where
|
||||
import Data.Aeson (object, (.=))
|
||||
import Generator.FileDraft (FileDraft)
|
||||
import qualified Generator.ServerGenerator.Common as C
|
||||
import qualified Path as P
|
||||
import StrongPath ((</>))
|
||||
import StrongPath (reldir, relfile, (</>))
|
||||
import qualified Util
|
||||
import Wasp (Wasp, getAuth)
|
||||
import qualified Wasp.Auth
|
||||
@ -30,29 +29,29 @@ genAuth wasp = case maybeAuth of
|
||||
genCoreAuth :: Wasp.Auth.Auth -> FileDraft
|
||||
genCoreAuth auth = C.makeTemplateFD tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
coreAuthRelToSrc = [P.relfile|core/auth.js|]
|
||||
tmplFile = C.asTmplFile $ [P.reldir|src|] P.</> coreAuthRelToSrc
|
||||
dstFile = C.serverSrcDirInServerRootDir </> (C.asServerSrcFile coreAuthRelToSrc)
|
||||
coreAuthRelToSrc = [relfile|core/auth.js|]
|
||||
tmplFile = C.asTmplFile $ [reldir|src|] </> coreAuthRelToSrc
|
||||
dstFile = C.serverSrcDirInServerRootDir </> C.asServerSrcFile coreAuthRelToSrc
|
||||
|
||||
tmplData =
|
||||
let userEntity = (Wasp.Auth._userEntity auth)
|
||||
let userEntity = Wasp.Auth._userEntity auth
|
||||
in object
|
||||
[ "userEntityUpper" .= userEntity,
|
||||
"userEntityLower" .= Util.toLowerFirst userEntity
|
||||
]
|
||||
|
||||
genAuthRoutesIndex :: FileDraft
|
||||
genAuthRoutesIndex = C.copySrcTmplAsIs (C.asTmplSrcFile [P.relfile|routes/auth/index.js|])
|
||||
genAuthRoutesIndex = C.copySrcTmplAsIs (C.asTmplSrcFile [relfile|routes/auth/index.js|])
|
||||
|
||||
genLoginRoute :: Wasp.Auth.Auth -> FileDraft
|
||||
genLoginRoute auth = C.makeTemplateFD tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
loginRouteRelToSrc = [P.relfile|routes/auth/login.js|]
|
||||
tmplFile = C.asTmplFile $ [P.reldir|src|] P.</> loginRouteRelToSrc
|
||||
dstFile = C.serverSrcDirInServerRootDir </> (C.asServerSrcFile loginRouteRelToSrc)
|
||||
loginRouteRelToSrc = [relfile|routes/auth/login.js|]
|
||||
tmplFile = C.asTmplFile $ [reldir|src|] </> loginRouteRelToSrc
|
||||
dstFile = C.serverSrcDirInServerRootDir </> C.asServerSrcFile loginRouteRelToSrc
|
||||
|
||||
tmplData =
|
||||
let userEntity = (Wasp.Auth._userEntity auth)
|
||||
let userEntity = Wasp.Auth._userEntity auth
|
||||
in object
|
||||
[ "userEntityUpper" .= userEntity,
|
||||
"userEntityLower" .= Util.toLowerFirst userEntity
|
||||
@ -61,9 +60,9 @@ genLoginRoute auth = C.makeTemplateFD tmplFile dstFile (Just tmplData)
|
||||
genSignupRoute :: Wasp.Auth.Auth -> FileDraft
|
||||
genSignupRoute auth = C.makeTemplateFD tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
signupRouteRelToSrc = [P.relfile|routes/auth/signup.js|]
|
||||
tmplFile = C.asTmplFile $ [P.reldir|src|] P.</> signupRouteRelToSrc
|
||||
dstFile = C.serverSrcDirInServerRootDir </> (C.asServerSrcFile signupRouteRelToSrc)
|
||||
signupRouteRelToSrc = [relfile|routes/auth/signup.js|]
|
||||
tmplFile = C.asTmplFile $ [reldir|src|] </> signupRouteRelToSrc
|
||||
dstFile = C.serverSrcDirInServerRootDir </> C.asServerSrcFile signupRouteRelToSrc
|
||||
|
||||
tmplData =
|
||||
object
|
||||
@ -73,9 +72,9 @@ genSignupRoute auth = C.makeTemplateFD tmplFile dstFile (Just tmplData)
|
||||
genMeRoute :: Wasp.Auth.Auth -> FileDraft
|
||||
genMeRoute auth = C.makeTemplateFD tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
meRouteRelToSrc = [P.relfile|routes/auth/me.js|]
|
||||
tmplFile = C.asTmplFile $ [P.reldir|src|] P.</> meRouteRelToSrc
|
||||
dstFile = C.serverSrcDirInServerRootDir </> (C.asServerSrcFile meRouteRelToSrc)
|
||||
meRouteRelToSrc = [relfile|routes/auth/me.js|]
|
||||
tmplFile = C.asTmplFile $ [reldir|src|] </> meRouteRelToSrc
|
||||
dstFile = C.serverSrcDirInServerRootDir </> C.asServerSrcFile meRouteRelToSrc
|
||||
|
||||
tmplData =
|
||||
object
|
||||
|
@ -22,8 +22,7 @@ import qualified Data.Aeson as Aeson
|
||||
import Generator.Common (ProjectRootDir)
|
||||
import Generator.FileDraft (FileDraft, createTemplateFileDraft)
|
||||
import Generator.Templates (TemplatesDir)
|
||||
import qualified Path as P
|
||||
import StrongPath (Dir, File, Path, Rel, (</>))
|
||||
import StrongPath (Dir, File', Path', Rel, reldir, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import Wasp (Wasp)
|
||||
|
||||
@ -35,46 +34,46 @@ data ServerTemplatesDir
|
||||
|
||||
data ServerTemplatesSrcDir
|
||||
|
||||
asTmplFile :: P.Path P.Rel P.File -> Path (Rel ServerTemplatesDir) File
|
||||
asTmplFile = SP.fromPathRelFile
|
||||
asTmplFile :: Path' (Rel d) File' -> Path' (Rel ServerTemplatesDir) File'
|
||||
asTmplFile = SP.castRel
|
||||
|
||||
asTmplSrcFile :: P.Path P.Rel P.File -> Path (Rel ServerTemplatesSrcDir) File
|
||||
asTmplSrcFile = SP.fromPathRelFile
|
||||
asTmplSrcFile :: Path' (Rel d) File' -> Path' (Rel ServerTemplatesSrcDir) File'
|
||||
asTmplSrcFile = SP.castRel
|
||||
|
||||
asServerFile :: P.Path P.Rel P.File -> Path (Rel ServerRootDir) File
|
||||
asServerFile = SP.fromPathRelFile
|
||||
asServerFile :: Path' (Rel d) File' -> Path' (Rel ServerRootDir) File'
|
||||
asServerFile = SP.castRel
|
||||
|
||||
asServerSrcFile :: P.Path P.Rel P.File -> Path (Rel ServerSrcDir) File
|
||||
asServerSrcFile = SP.fromPathRelFile
|
||||
asServerSrcFile :: Path' (Rel d) File' -> Path' (Rel ServerSrcDir) File'
|
||||
asServerSrcFile = SP.castRel
|
||||
|
||||
-- * Paths
|
||||
|
||||
-- | Path where server root dir is generated.
|
||||
serverRootDirInProjectRootDir :: Path (Rel ProjectRootDir) (Dir ServerRootDir)
|
||||
serverRootDirInProjectRootDir = SP.fromPathRelDir [P.reldir|server|]
|
||||
serverRootDirInProjectRootDir :: Path' (Rel ProjectRootDir) (Dir ServerRootDir)
|
||||
serverRootDirInProjectRootDir = [reldir|server|]
|
||||
|
||||
-- | Path to generated server src/ directory.
|
||||
serverSrcDirInServerRootDir :: Path (Rel ServerRootDir) (Dir ServerSrcDir)
|
||||
serverSrcDirInServerRootDir = SP.fromPathRelDir [P.reldir|src|]
|
||||
serverSrcDirInServerRootDir :: Path' (Rel ServerRootDir) (Dir ServerSrcDir)
|
||||
serverSrcDirInServerRootDir = [reldir|src|]
|
||||
|
||||
serverSrcDirInProjectRootDir :: Path (Rel ProjectRootDir) (Dir ServerSrcDir)
|
||||
serverSrcDirInProjectRootDir :: Path' (Rel ProjectRootDir) (Dir ServerSrcDir)
|
||||
serverSrcDirInProjectRootDir = serverRootDirInProjectRootDir </> serverSrcDirInServerRootDir
|
||||
|
||||
-- * Templates
|
||||
|
||||
copyTmplAsIs :: Path (Rel ServerTemplatesDir) File -> FileDraft
|
||||
copyTmplAsIs :: Path' (Rel ServerTemplatesDir) File' -> FileDraft
|
||||
copyTmplAsIs srcPath = makeTemplateFD srcPath dstPath Nothing
|
||||
where
|
||||
dstPath = (SP.castRel srcPath) :: Path (Rel ServerRootDir) File
|
||||
dstPath = SP.castRel srcPath :: Path' (Rel ServerRootDir) File'
|
||||
|
||||
makeSimpleTemplateFD :: Path (Rel ServerTemplatesDir) File -> Wasp -> FileDraft
|
||||
makeSimpleTemplateFD :: Path' (Rel ServerTemplatesDir) File' -> Wasp -> FileDraft
|
||||
makeSimpleTemplateFD srcPath wasp = makeTemplateFD srcPath dstPath (Just $ Aeson.toJSON wasp)
|
||||
where
|
||||
dstPath = (SP.castRel srcPath) :: Path (Rel ServerRootDir) File
|
||||
dstPath = SP.castRel srcPath :: Path' (Rel ServerRootDir) File'
|
||||
|
||||
makeTemplateFD ::
|
||||
Path (Rel ServerTemplatesDir) File ->
|
||||
Path (Rel ServerRootDir) File ->
|
||||
Path' (Rel ServerTemplatesDir) File' ->
|
||||
Path' (Rel ServerRootDir) File' ->
|
||||
Maybe Aeson.Value ->
|
||||
FileDraft
|
||||
makeTemplateFD relSrcPath relDstPath tmplData =
|
||||
@ -83,17 +82,17 @@ makeTemplateFD relSrcPath relDstPath tmplData =
|
||||
(serverTemplatesDirInTemplatesDir </> relSrcPath)
|
||||
tmplData
|
||||
|
||||
copySrcTmplAsIs :: Path (Rel ServerTemplatesSrcDir) File -> FileDraft
|
||||
copySrcTmplAsIs :: Path' (Rel ServerTemplatesSrcDir) File' -> FileDraft
|
||||
copySrcTmplAsIs pathInTemplatesSrcDir = makeTemplateFD srcPath dstPath Nothing
|
||||
where
|
||||
srcPath = srcDirInServerTemplatesDir </> pathInTemplatesSrcDir
|
||||
dstPath =
|
||||
serverSrcDirInServerRootDir
|
||||
</> ((SP.castRel pathInTemplatesSrcDir) :: Path (Rel ServerSrcDir) File)
|
||||
</> (SP.castRel pathInTemplatesSrcDir :: Path' (Rel ServerSrcDir) File')
|
||||
|
||||
-- | Path where server app templates reside.
|
||||
serverTemplatesDirInTemplatesDir :: Path (Rel TemplatesDir) (Dir ServerTemplatesDir)
|
||||
serverTemplatesDirInTemplatesDir = SP.fromPathRelDir [P.reldir|server|]
|
||||
serverTemplatesDirInTemplatesDir :: Path' (Rel TemplatesDir) (Dir ServerTemplatesDir)
|
||||
serverTemplatesDirInTemplatesDir = [reldir|server|]
|
||||
|
||||
srcDirInServerTemplatesDir :: Path (Rel ServerTemplatesDir) (Dir ServerTemplatesSrcDir)
|
||||
srcDirInServerTemplatesDir = SP.fromPathRelDir [P.reldir|src|]
|
||||
srcDirInServerTemplatesDir :: Path' (Rel ServerTemplatesDir) (Dir ServerTemplatesSrcDir)
|
||||
srcDirInServerTemplatesDir = [reldir|src|]
|
||||
|
@ -8,8 +8,7 @@ import Data.Aeson (object, (.=))
|
||||
import Data.Maybe (isJust)
|
||||
import Generator.FileDraft (FileDraft)
|
||||
import qualified Generator.ServerGenerator.Common as C
|
||||
import qualified Path as P
|
||||
import StrongPath (File, Path, Rel, (</>))
|
||||
import StrongPath (File', Path', Rel, relfile, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import Wasp (Wasp, getAuth)
|
||||
|
||||
@ -23,5 +22,5 @@ genConfigFile wasp = C.makeTemplateFD tmplFile dstFile (Just tmplData)
|
||||
[ "isAuthEnabled" .= isJust (getAuth wasp)
|
||||
]
|
||||
|
||||
configFileInSrcDir :: Path (Rel C.ServerSrcDir) File
|
||||
configFileInSrcDir = SP.fromPathRelFile [P.relfile|config.js|]
|
||||
configFileInSrcDir :: Path' (Rel C.ServerSrcDir) File'
|
||||
configFileInSrcDir = [relfile|config.js|]
|
||||
|
@ -7,13 +7,12 @@ where
|
||||
import Generator.ExternalCodeGenerator.Common (ExternalCodeGeneratorStrategy (..), GeneratedExternalCodeDir)
|
||||
import Generator.ExternalCodeGenerator.Js (resolveJsFileWaspImportsForExtCodeDir)
|
||||
import qualified Generator.ServerGenerator.Common as C
|
||||
import qualified Path as P
|
||||
import StrongPath (Dir, Path, Rel, (</>))
|
||||
import StrongPath (Dir, Path', Rel, reldir, (</>))
|
||||
import qualified StrongPath as SP
|
||||
|
||||
-- | Relative path to directory where external code will be generated.
|
||||
extCodeDirInServerSrcDir :: Path (Rel C.ServerSrcDir) (Dir GeneratedExternalCodeDir)
|
||||
extCodeDirInServerSrcDir = SP.fromPathRelDir [P.reldir|ext-src|]
|
||||
extCodeDirInServerSrcDir :: Path' (Rel C.ServerSrcDir) (Dir GeneratedExternalCodeDir)
|
||||
extCodeDirInServerSrcDir = [reldir|ext-src|]
|
||||
|
||||
generatorStrategy :: ExternalCodeGeneratorStrategy
|
||||
generatorStrategy =
|
||||
|
@ -12,8 +12,7 @@ import Data.Char (toLower)
|
||||
import Data.Maybe (fromJust, fromMaybe)
|
||||
import Generator.FileDraft (FileDraft)
|
||||
import qualified Generator.ServerGenerator.Common as C
|
||||
import qualified Path as P
|
||||
import StrongPath (File, Path, Rel, (</>))
|
||||
import StrongPath (File', Path', Rel, reldir, relfile, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import Wasp (Wasp)
|
||||
import qualified Wasp
|
||||
@ -48,7 +47,7 @@ genQuery :: Wasp -> Wasp.Query.Query -> FileDraft
|
||||
genQuery _ query = C.makeTemplateFD tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
operation = Wasp.Operation.QueryOp query
|
||||
tmplFile = C.asTmplFile [P.relfile|src/queries/_query.js|]
|
||||
tmplFile = C.asTmplFile [relfile|src/queries/_query.js|]
|
||||
dstFile = C.serverSrcDirInServerRootDir </> queryFileInSrcDir query
|
||||
tmplData = operationTmplData operation
|
||||
|
||||
@ -57,25 +56,23 @@ genAction :: Wasp -> Wasp.Action.Action -> FileDraft
|
||||
genAction _ action = C.makeTemplateFD tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
operation = Wasp.Operation.ActionOp action
|
||||
tmplFile = C.asTmplFile [P.relfile|src/actions/_action.js|]
|
||||
tmplFile = [relfile|src/actions/_action.js|]
|
||||
dstFile = C.serverSrcDirInServerRootDir </> actionFileInSrcDir action
|
||||
tmplData = operationTmplData operation
|
||||
|
||||
queryFileInSrcDir :: Wasp.Query.Query -> Path (Rel C.ServerSrcDir) File
|
||||
queryFileInSrcDir :: Wasp.Query.Query -> Path' (Rel C.ServerSrcDir) File'
|
||||
queryFileInSrcDir query =
|
||||
SP.fromPathRelFile $
|
||||
[P.reldir|queries|]
|
||||
-- TODO: fromJust here could fail if there is some problem with the name, we should handle this.
|
||||
P.</> fromJust (P.parseRelFile $ Wasp.Query._name query ++ ".js")
|
||||
[reldir|queries|]
|
||||
-- TODO: fromJust here could fail if there is some problem with the name, we should handle this.
|
||||
</> fromJust (SP.parseRelFile $ Wasp.Query._name query ++ ".js")
|
||||
|
||||
actionFileInSrcDir :: Wasp.Action.Action -> Path (Rel C.ServerSrcDir) File
|
||||
actionFileInSrcDir :: Wasp.Action.Action -> Path' (Rel C.ServerSrcDir) File'
|
||||
actionFileInSrcDir action =
|
||||
SP.fromPathRelFile $
|
||||
[P.reldir|actions|]
|
||||
-- TODO: fromJust here could fail if there is some problem with the name, we should handle this.
|
||||
P.</> fromJust (P.parseRelFile $ Wasp.Action._name action ++ ".js")
|
||||
[reldir|actions|]
|
||||
-- TODO: fromJust here could fail if there is some problem with the name, we should handle this.
|
||||
</> fromJust (SP.parseRelFile $ Wasp.Action._name action ++ ".js")
|
||||
|
||||
operationFileInSrcDir :: Wasp.Operation.Operation -> Path (Rel C.ServerSrcDir) File
|
||||
operationFileInSrcDir :: Wasp.Operation.Operation -> Path' (Rel C.ServerSrcDir) File'
|
||||
operationFileInSrcDir (Wasp.Operation.QueryOp query) = queryFileInSrcDir query
|
||||
operationFileInSrcDir (Wasp.Operation.ActionOp action) = actionFileInSrcDir action
|
||||
|
||||
|
@ -10,16 +10,8 @@ import Data.Maybe (fromJust)
|
||||
import Generator.FileDraft (FileDraft)
|
||||
import qualified Generator.ServerGenerator.Common as C
|
||||
import Generator.ServerGenerator.OperationsG (operationFileInSrcDir)
|
||||
import qualified Path as P
|
||||
import StrongPath
|
||||
( Dir,
|
||||
File,
|
||||
Path,
|
||||
Rel,
|
||||
(</>),
|
||||
)
|
||||
import StrongPath (Dir, File', Path, Path', Posix, Rel, reldir, reldirP, relfile, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import qualified System.FilePath.Posix as FPPosix
|
||||
import qualified Util as U
|
||||
import Wasp (Wasp, getAuth)
|
||||
import qualified Wasp
|
||||
@ -40,15 +32,15 @@ genActionRoute :: Wasp -> Wasp.Action.Action -> FileDraft
|
||||
genActionRoute wasp action = genOperationRoute wasp op tmplFile
|
||||
where
|
||||
op = Wasp.Operation.ActionOp action
|
||||
tmplFile = C.asTmplFile [P.relfile|src/routes/operations/_action.js|]
|
||||
tmplFile = C.asTmplFile [relfile|src/routes/operations/_action.js|]
|
||||
|
||||
genQueryRoute :: Wasp -> Wasp.Query.Query -> FileDraft
|
||||
genQueryRoute wasp query = genOperationRoute wasp op tmplFile
|
||||
where
|
||||
op = Wasp.Operation.QueryOp query
|
||||
tmplFile = C.asTmplFile [P.relfile|src/routes/operations/_query.js|]
|
||||
tmplFile = C.asTmplFile [relfile|src/routes/operations/_query.js|]
|
||||
|
||||
genOperationRoute :: Wasp -> Wasp.Operation.Operation -> Path (Rel C.ServerTemplatesDir) File -> FileDraft
|
||||
genOperationRoute :: Wasp -> Wasp.Operation.Operation -> Path' (Rel C.ServerTemplatesDir) File' -> FileDraft
|
||||
genOperationRoute wasp operation tmplFile = C.makeTemplateFD tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
dstFile = operationsRoutesDirInServerRootDir </> operationRouteFileInOperationsRoutesDir operation
|
||||
@ -59,38 +51,38 @@ genOperationRoute wasp operation tmplFile = C.makeTemplateFD tmplFile dstFile (J
|
||||
"operationName" .= Wasp.Operation.getName operation
|
||||
]
|
||||
|
||||
tmplData = case (Wasp.getAuth wasp) of
|
||||
tmplData = case Wasp.getAuth wasp of
|
||||
Nothing -> baseTmplData
|
||||
Just auth ->
|
||||
U.jsonSet
|
||||
("userEntityLower")
|
||||
"userEntityLower"
|
||||
(Aeson.toJSON (U.toLowerFirst $ Wasp.Auth._userEntity auth))
|
||||
baseTmplData
|
||||
|
||||
operationImportPath =
|
||||
relPosixPathFromOperationsRoutesDirToSrcDir
|
||||
FPPosix.</> SP.toFilePath (SP.relFileToPosix' $ operationFileInSrcDir operation)
|
||||
SP.fromRelFileP $
|
||||
relPosixPathFromOperationsRoutesDirToSrcDir
|
||||
</> fromJust (SP.relFileToPosix $ operationFileInSrcDir operation)
|
||||
|
||||
data OperationsRoutesDir
|
||||
|
||||
operationsRoutesDirInServerSrcDir :: Path (Rel C.ServerSrcDir) (Dir OperationsRoutesDir)
|
||||
operationsRoutesDirInServerSrcDir = SP.fromPathRelDir [P.reldir|routes/operations/|]
|
||||
operationsRoutesDirInServerSrcDir :: Path' (Rel C.ServerSrcDir) (Dir OperationsRoutesDir)
|
||||
operationsRoutesDirInServerSrcDir = [reldir|routes/operations/|]
|
||||
|
||||
operationsRoutesDirInServerRootDir :: Path (Rel C.ServerRootDir) (Dir OperationsRoutesDir)
|
||||
operationsRoutesDirInServerRootDir :: Path' (Rel C.ServerRootDir) (Dir OperationsRoutesDir)
|
||||
operationsRoutesDirInServerRootDir = C.serverSrcDirInServerRootDir </> operationsRoutesDirInServerSrcDir
|
||||
|
||||
operationRouteFileInOperationsRoutesDir :: Wasp.Operation.Operation -> Path (Rel OperationsRoutesDir) File
|
||||
operationRouteFileInOperationsRoutesDir :: Wasp.Operation.Operation -> Path' (Rel OperationsRoutesDir) File'
|
||||
operationRouteFileInOperationsRoutesDir operation = fromJust $ SP.parseRelFile $ Wasp.Operation.getName operation ++ ".js"
|
||||
|
||||
-- | TODO: Make this not hardcoded! Maybe even use StrongPath? But I can't because of ../../ .
|
||||
relPosixPathFromOperationsRoutesDirToSrcDir :: FilePath -- Posix
|
||||
relPosixPathFromOperationsRoutesDirToSrcDir = "../.."
|
||||
relPosixPathFromOperationsRoutesDirToSrcDir :: Path Posix (Rel OperationsRoutesDir) (Dir C.ServerSrcDir)
|
||||
relPosixPathFromOperationsRoutesDirToSrcDir = [reldirP|../..|]
|
||||
|
||||
genOperationsRouter :: Wasp -> FileDraft
|
||||
genOperationsRouter wasp = C.makeTemplateFD tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
tmplFile = C.asTmplFile [P.relfile|src/routes/operations/index.js|]
|
||||
dstFile = operationsRoutesDirInServerRootDir </> SP.fromPathRelFile [P.relfile|index.js|]
|
||||
tmplFile = C.asTmplFile [relfile|src/routes/operations/index.js|]
|
||||
dstFile = operationsRoutesDirInServerRootDir </> [relfile|index.js|]
|
||||
operations =
|
||||
map Wasp.Operation.ActionOp (Wasp.getActions wasp)
|
||||
++ map Wasp.Operation.QueryOp (Wasp.getQueries wasp)
|
||||
@ -103,8 +95,8 @@ genOperationsRouter wasp = C.makeTemplateFD tmplFile dstFile (Just tmplData)
|
||||
let operationName = Wasp.Operation.getName operation
|
||||
in object
|
||||
[ "importIdentifier" .= operationName,
|
||||
"importPath" .= ("./" ++ SP.toFilePath (SP.relFileToPosix' $ operationRouteFileInOperationsRoutesDir operation)),
|
||||
"routePath" .= ("/" ++ operationRouteInOperationsRouter operation),
|
||||
"importPath" .= ("./" ++ SP.fromRelFileP (fromJust $ SP.relFileToPosix $ operationRouteFileInOperationsRoutesDir operation)),
|
||||
"routePath" .= ("/" ++ operationRouteInOperationsRouter operation)
|
||||
"isAuthEnabled" .= (authEnabled operation)
|
||||
]
|
||||
|
||||
|
@ -7,9 +7,9 @@ import Generator.Common (ProjectRootDir)
|
||||
import qualified Generator.Job as J
|
||||
import Generator.Job.Process (runNodeCommandAsJob)
|
||||
import qualified Generator.ServerGenerator.Common as Common
|
||||
import StrongPath (Abs, Dir, Path, (</>))
|
||||
import StrongPath (Abs, Dir, Path', (</>))
|
||||
|
||||
setupServer :: Path Abs (Dir ProjectRootDir) -> J.Job
|
||||
setupServer :: Path' Abs (Dir ProjectRootDir) -> J.Job
|
||||
setupServer projectDir = do
|
||||
let serverDir = projectDir </> Common.serverRootDirInProjectRootDir
|
||||
runNodeCommandAsJob serverDir "npm" ["install"] J.Server
|
||||
|
@ -7,9 +7,9 @@ import Generator.Common (ProjectRootDir)
|
||||
import qualified Generator.Job as J
|
||||
import Generator.Job.Process (runNodeCommandAsJob)
|
||||
import qualified Generator.ServerGenerator.Common as Common
|
||||
import StrongPath (Abs, Dir, Path, (</>))
|
||||
import StrongPath (Abs, Dir, Path', (</>))
|
||||
|
||||
startServer :: Path Abs (Dir ProjectRootDir) -> J.Job
|
||||
startServer :: Path' Abs (Dir ProjectRootDir) -> J.Job
|
||||
startServer projectDir = do
|
||||
let serverDir = projectDir </> Common.serverRootDirInProjectRootDir
|
||||
runNodeCommandAsJob serverDir "npm" ["start"] J.Server
|
||||
|
@ -10,10 +10,10 @@ import qualified Generator.Job as J
|
||||
import Generator.Job.IO (printPrefixedJobMessage)
|
||||
import Generator.ServerGenerator.Setup (setupServer)
|
||||
import Generator.WebAppGenerator.Setup (setupWebApp)
|
||||
import StrongPath (Abs, Dir, Path)
|
||||
import StrongPath (Abs, Dir, Path')
|
||||
import System.Exit (ExitCode (..))
|
||||
|
||||
setup :: Path Abs (Dir ProjectRootDir) -> IO (Either String ())
|
||||
setup :: Path' Abs (Dir ProjectRootDir) -> IO (Either String ())
|
||||
setup projectDir = do
|
||||
chan <- newChan
|
||||
let runSetupJobs = concurrently (setupServer projectDir chan) (setupWebApp projectDir chan)
|
||||
|
@ -9,11 +9,11 @@ import Generator.Common (ProjectRootDir)
|
||||
import Generator.Job.IO (readJobMessagesAndPrintThemPrefixed)
|
||||
import Generator.ServerGenerator.Start (startServer)
|
||||
import Generator.WebAppGenerator.Start (startWebApp)
|
||||
import StrongPath (Abs, Dir, Path)
|
||||
import StrongPath (Abs, Dir, Path')
|
||||
|
||||
-- | This is a blocking action, that will start the processes that run web app and server.
|
||||
-- It will run as long as one of those processes does not fail.
|
||||
start :: Path Abs (Dir ProjectRootDir) -> IO (Either String ())
|
||||
start :: Path' Abs (Dir ProjectRootDir) -> IO (Either String ())
|
||||
start projectDir = do
|
||||
chan <- newChan
|
||||
let runStartJobs = race (startServer projectDir chan) (startWebApp projectDir chan)
|
||||
|
@ -9,8 +9,7 @@ where
|
||||
import qualified Data
|
||||
import qualified Data.Aeson as Aeson
|
||||
import Data.Text (Text)
|
||||
import qualified Path as P
|
||||
import StrongPath (Abs, Dir, File, Path, Rel, (</>))
|
||||
import StrongPath (Abs, Dir, File', Path', Rel, reldir, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import qualified Text.Mustache as Mustache
|
||||
import Text.Mustache.Render (SubstitutionError (..))
|
||||
@ -22,20 +21,20 @@ import Text.Printf (printf)
|
||||
data TemplatesDir
|
||||
|
||||
-- | Returns absolute path of templates root directory.
|
||||
getTemplatesDirAbsPath :: IO (Path Abs (Dir TemplatesDir))
|
||||
getTemplatesDirAbsPath :: IO (Path' Abs (Dir TemplatesDir))
|
||||
getTemplatesDirAbsPath = (</> templatesDirPathInDataDir) <$> Data.getAbsDataDirPath
|
||||
|
||||
-- | Takes template file path relative to templates root directory and returns
|
||||
-- its absolute path.
|
||||
getTemplateFileAbsPath :: Path (Rel TemplatesDir) File -> IO (Path Abs File)
|
||||
getTemplateFileAbsPath :: Path' (Rel TemplatesDir) File' -> IO (Path' Abs File')
|
||||
getTemplateFileAbsPath relTmplFilePath = (</> relTmplFilePath) <$> getTemplatesDirAbsPath
|
||||
|
||||
templatesDirPathInDataDir :: Path (Rel Data.DataDir) (Dir TemplatesDir)
|
||||
templatesDirPathInDataDir = SP.fromPathRelDir [P.reldir|Generator/templates|]
|
||||
templatesDirPathInDataDir :: Path' (Rel Data.DataDir) (Dir TemplatesDir)
|
||||
templatesDirPathInDataDir = [reldir|Generator/templates|]
|
||||
|
||||
compileAndRenderTemplate ::
|
||||
-- | Path to the template file.
|
||||
Path (Rel TemplatesDir) File ->
|
||||
Path' (Rel TemplatesDir) File' ->
|
||||
-- | JSON to be provided as template data.
|
||||
Aeson.Value ->
|
||||
IO Text
|
||||
@ -45,15 +44,15 @@ compileAndRenderTemplate relTmplPath tmplData = do
|
||||
|
||||
compileMustacheTemplate ::
|
||||
-- | Path to the template file.
|
||||
Path (Rel TemplatesDir) File ->
|
||||
Path' (Rel TemplatesDir) File' ->
|
||||
IO Mustache.Template
|
||||
compileMustacheTemplate relTmplPath = do
|
||||
templatesDirAbsPath <- getTemplatesDirAbsPath
|
||||
absTmplPath <- getTemplateFileAbsPath relTmplPath
|
||||
eitherTemplate <-
|
||||
Mustache.automaticCompile
|
||||
[SP.toFilePath templatesDirAbsPath]
|
||||
(SP.toFilePath absTmplPath)
|
||||
[SP.fromAbsDir templatesDirAbsPath]
|
||||
(SP.fromAbsFile absTmplPath)
|
||||
return $ either raiseCompileError id eitherTemplate
|
||||
where
|
||||
raiseCompileError err =
|
||||
|
@ -28,14 +28,14 @@ import qualified Generator.WebAppGenerator.ExternalCodeGenerator as WebAppExtern
|
||||
import Generator.WebAppGenerator.OperationsGenerator (genOperations)
|
||||
import qualified Generator.WebAppGenerator.RouterGenerator as RouterGenerator
|
||||
import qualified NpmDependency as ND
|
||||
import qualified Path as P
|
||||
import StrongPath
|
||||
( Dir,
|
||||
Path,
|
||||
Path',
|
||||
Rel,
|
||||
reldir,
|
||||
relfile,
|
||||
(</>),
|
||||
)
|
||||
import qualified StrongPath as SP
|
||||
import Wasp
|
||||
import qualified Wasp.App
|
||||
import qualified Wasp.NpmDependencies as WND
|
||||
@ -49,17 +49,17 @@ generateWebApp wasp _ =
|
||||
generatePublicDir wasp,
|
||||
generateSrcDir wasp,
|
||||
generateExternalCodeDir WebAppExternalCodeGenerator.generatorStrategy wasp,
|
||||
[C.makeSimpleTemplateFD (asTmplFile [P.relfile|netlify.toml|]) wasp]
|
||||
[C.makeSimpleTemplateFD (asTmplFile [relfile|netlify.toml|]) wasp]
|
||||
]
|
||||
|
||||
generateReadme :: Wasp -> FileDraft
|
||||
generateReadme wasp = C.makeSimpleTemplateFD (asTmplFile [P.relfile|README.md|]) wasp
|
||||
generateReadme wasp = C.makeSimpleTemplateFD (asTmplFile [relfile|README.md|]) wasp
|
||||
|
||||
genPackageJson :: Wasp -> [ND.NpmDependency] -> FileDraft
|
||||
genPackageJson wasp waspDeps =
|
||||
C.makeTemplateFD
|
||||
(C.asTmplFile [P.relfile|package.json|])
|
||||
(C.asWebAppFile [P.relfile|package.json|])
|
||||
(C.asTmplFile [relfile|package.json|])
|
||||
(C.asWebAppFile [relfile|package.json|])
|
||||
( Just $
|
||||
object
|
||||
[ "wasp" .= wasp,
|
||||
@ -93,27 +93,27 @@ waspNpmDeps =
|
||||
generateGitignore :: Wasp -> FileDraft
|
||||
generateGitignore wasp =
|
||||
C.makeTemplateFD
|
||||
(asTmplFile [P.relfile|gitignore|])
|
||||
(asWebAppFile [P.relfile|.gitignore|])
|
||||
(asTmplFile [relfile|gitignore|])
|
||||
(asWebAppFile [relfile|.gitignore|])
|
||||
(Just $ toJSON wasp)
|
||||
|
||||
generatePublicDir :: Wasp -> [FileDraft]
|
||||
generatePublicDir wasp =
|
||||
C.copyTmplAsIs (asTmplFile [P.relfile|public/favicon.ico|]) :
|
||||
C.copyTmplAsIs (asTmplFile [relfile|public/favicon.ico|]) :
|
||||
generatePublicIndexHtml wasp :
|
||||
map
|
||||
(\path -> C.makeSimpleTemplateFD (asTmplFile $ [P.reldir|public|] P.</> path) wasp)
|
||||
[ [P.relfile|manifest.json|]
|
||||
(\path -> C.makeSimpleTemplateFD (asTmplFile $ [reldir|public|] </> path) wasp)
|
||||
[ [relfile|manifest.json|]
|
||||
]
|
||||
|
||||
generatePublicIndexHtml :: Wasp -> FileDraft
|
||||
generatePublicIndexHtml wasp =
|
||||
C.makeTemplateFD
|
||||
(asTmplFile $ [P.relfile|public/index.html|])
|
||||
(asTmplFile [relfile|public/index.html|])
|
||||
targetPath
|
||||
(Just templateData)
|
||||
where
|
||||
targetPath = SP.fromPathRelFile [P.relfile|public/index.html|]
|
||||
targetPath = [relfile|public/index.html|]
|
||||
templateData =
|
||||
object
|
||||
[ "title" .= (Wasp.App.appTitle $ getApp wasp),
|
||||
@ -122,7 +122,7 @@ generatePublicIndexHtml wasp =
|
||||
|
||||
-- * Src dir
|
||||
|
||||
srcDir :: Path (Rel C.WebAppRootDir) (Dir C.WebAppSrcDir)
|
||||
srcDir :: Path' (Rel C.WebAppRootDir) (Dir C.WebAppSrcDir)
|
||||
srcDir = C.webAppSrcDirInWebAppRootDir
|
||||
|
||||
-- TODO(matija): Currently we also generate auth-specific parts in this file (e.g. token management),
|
||||
@ -132,7 +132,7 @@ srcDir = C.webAppSrcDirInWebAppRootDir
|
||||
|
||||
-- | Generates api.js file which contains token management and configured api (e.g. axios) instance.
|
||||
genApi :: FileDraft
|
||||
genApi = C.copyTmplAsIs (C.asTmplFile [P.relfile|src/api.js|])
|
||||
genApi = C.copyTmplAsIs (C.asTmplFile [relfile|src/api.js|])
|
||||
|
||||
generateSrcDir :: Wasp -> [FileDraft]
|
||||
generateSrcDir wasp =
|
||||
@ -141,22 +141,22 @@ generateSrcDir wasp =
|
||||
genApi :
|
||||
map
|
||||
makeSimpleSrcTemplateFD
|
||||
[ [P.relfile|index.js|],
|
||||
[P.relfile|index.css|],
|
||||
[P.relfile|serviceWorker.js|],
|
||||
[P.relfile|config.js|],
|
||||
[P.relfile|queryCache.js|]
|
||||
[ [relfile|index.js|],
|
||||
[relfile|index.css|],
|
||||
[relfile|serviceWorker.js|],
|
||||
[relfile|config.js|],
|
||||
[relfile|queryCache.js|]
|
||||
]
|
||||
++ genOperations wasp
|
||||
++ AuthG.genAuth wasp
|
||||
where
|
||||
generateLogo =
|
||||
C.makeTemplateFD
|
||||
(asTmplFile [P.relfile|src/logo.png|])
|
||||
(srcDir </> asWebAppSrcFile [P.relfile|logo.png|])
|
||||
(asTmplFile [relfile|src/logo.png|])
|
||||
(srcDir </> asWebAppSrcFile [relfile|logo.png|])
|
||||
Nothing
|
||||
makeSimpleSrcTemplateFD path =
|
||||
C.makeTemplateFD
|
||||
(asTmplFile $ [P.reldir|src|] P.</> path)
|
||||
(asTmplFile $ [reldir|src|] </> path)
|
||||
(srcDir </> asWebAppSrcFile path)
|
||||
(Just $ toJSON wasp)
|
||||
|
@ -6,8 +6,7 @@ where
|
||||
import Data.Aeson (object, (.=))
|
||||
import Generator.FileDraft (FileDraft)
|
||||
import Generator.WebAppGenerator.Common as C
|
||||
import qualified Path as P
|
||||
import StrongPath ((</>))
|
||||
import StrongPath (reldir, relfile, (</>))
|
||||
import Wasp (Wasp, getAuth)
|
||||
import qualified Wasp.Auth
|
||||
|
||||
@ -27,25 +26,25 @@ genAuth wasp = case maybeAuth of
|
||||
|
||||
-- | Generates file with signup function to be used by Wasp developer.
|
||||
genSignup :: FileDraft
|
||||
genSignup = C.copyTmplAsIs (C.asTmplFile [P.relfile|src/auth/signup.js|])
|
||||
genSignup = C.copyTmplAsIs (C.asTmplFile [relfile|src/auth/signup.js|])
|
||||
|
||||
-- | Generates file with login function to be used by Wasp developer.
|
||||
genLogin :: FileDraft
|
||||
genLogin = C.copyTmplAsIs (C.asTmplFile [P.relfile|src/auth/login.js|])
|
||||
genLogin = C.copyTmplAsIs (C.asTmplFile [relfile|src/auth/login.js|])
|
||||
|
||||
-- | Generates file with logout function to be used by Wasp developer.
|
||||
genLogout :: FileDraft
|
||||
genLogout = C.copyTmplAsIs (C.asTmplFile [P.relfile|src/auth/logout.js|])
|
||||
genLogout = C.copyTmplAsIs (C.asTmplFile [relfile|src/auth/logout.js|])
|
||||
|
||||
-- | Generates HOC that handles auth for the given page.
|
||||
genCreateAuthRequiredPage :: Wasp.Auth.Auth -> FileDraft
|
||||
genCreateAuthRequiredPage auth =
|
||||
C.makeTemplateFD
|
||||
(asTmplFile $ [P.reldir|src|] P.</> authReqPagePath)
|
||||
(asTmplFile $ [reldir|src|] </> authReqPagePath)
|
||||
targetPath
|
||||
(Just templateData)
|
||||
where
|
||||
authReqPagePath = [P.relfile|auth/pages/createAuthRequiredPage.js|]
|
||||
authReqPagePath = [relfile|auth/pages/createAuthRequiredPage.js|]
|
||||
targetPath = C.webAppSrcDirInWebAppRootDir </> (asWebAppSrcFile authReqPagePath)
|
||||
templateData = object ["onAuthFailedRedirectTo" .= (Wasp.Auth._onAuthFailedRedirectTo auth)]
|
||||
|
||||
@ -53,7 +52,7 @@ genCreateAuthRequiredPage auth =
|
||||
-- access to the currently logged in user (and check whether user is logged in
|
||||
-- ot not).
|
||||
genUseAuth :: FileDraft
|
||||
genUseAuth = C.copyTmplAsIs (C.asTmplFile [P.relfile|src/auth/useAuth.js|])
|
||||
genUseAuth = C.copyTmplAsIs (C.asTmplFile [relfile|src/auth/useAuth.js|])
|
||||
|
||||
genAuthForms :: [FileDraft]
|
||||
genAuthForms =
|
||||
@ -62,7 +61,7 @@ genAuthForms =
|
||||
]
|
||||
|
||||
genLoginForm :: FileDraft
|
||||
genLoginForm = C.copyTmplAsIs (C.asTmplFile [P.relfile|src/auth/forms/Login.js|])
|
||||
genLoginForm = C.copyTmplAsIs (C.asTmplFile [relfile|src/auth/forms/Login.js|])
|
||||
|
||||
genSignupForm :: FileDraft
|
||||
genSignupForm = C.copyTmplAsIs (C.asTmplFile [P.relfile|src/auth/forms/Signup.js|])
|
||||
genSignupForm = C.copyTmplAsIs (C.asTmplFile [relfile|src/auth/forms/Signup.js|])
|
||||
|
@ -19,8 +19,7 @@ import qualified Data.Aeson as Aeson
|
||||
import Generator.Common (ProjectRootDir)
|
||||
import Generator.FileDraft (FileDraft, createTemplateFileDraft)
|
||||
import Generator.Templates (TemplatesDir)
|
||||
import qualified Path as P
|
||||
import StrongPath (Dir, File, Path, Rel, (</>))
|
||||
import StrongPath (Dir, File', Path', Rel, reldir, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import Wasp (Wasp)
|
||||
|
||||
@ -30,43 +29,43 @@ data WebAppSrcDir
|
||||
|
||||
data WebAppTemplatesDir
|
||||
|
||||
asTmplFile :: P.Path P.Rel P.File -> Path (Rel WebAppTemplatesDir) File
|
||||
asTmplFile = SP.fromPathRelFile
|
||||
asTmplFile :: Path' (Rel d) File' -> Path' (Rel WebAppTemplatesDir) File'
|
||||
asTmplFile = SP.castRel
|
||||
|
||||
asWebAppFile :: P.Path P.Rel P.File -> Path (Rel WebAppRootDir) File
|
||||
asWebAppFile = SP.fromPathRelFile
|
||||
asWebAppFile :: Path' (Rel d) File' -> Path' (Rel WebAppRootDir) File'
|
||||
asWebAppFile = SP.castRel
|
||||
|
||||
asWebAppSrcFile :: P.Path P.Rel P.File -> Path (Rel WebAppSrcDir) File
|
||||
asWebAppSrcFile = SP.fromPathRelFile
|
||||
asWebAppSrcFile :: Path' (Rel d) File' -> Path' (Rel WebAppSrcDir) File'
|
||||
asWebAppSrcFile = SP.castRel
|
||||
|
||||
-- * Paths
|
||||
|
||||
-- | Path where web app root dir is generated, relative to the root directory of the whole generated project.
|
||||
webAppRootDirInProjectRootDir :: Path (Rel ProjectRootDir) (Dir WebAppRootDir)
|
||||
webAppRootDirInProjectRootDir = SP.fromPathRelDir [P.reldir|web-app|]
|
||||
webAppRootDirInProjectRootDir :: Path' (Rel ProjectRootDir) (Dir WebAppRootDir)
|
||||
webAppRootDirInProjectRootDir = [reldir|web-app|]
|
||||
|
||||
-- | Path to generated web app src/ directory, relative to the root directory of generated web app.
|
||||
webAppSrcDirInWebAppRootDir :: Path (Rel WebAppRootDir) (Dir WebAppSrcDir)
|
||||
webAppSrcDirInWebAppRootDir = SP.fromPathRelDir [P.reldir|src|]
|
||||
webAppSrcDirInWebAppRootDir :: Path' (Rel WebAppRootDir) (Dir WebAppSrcDir)
|
||||
webAppSrcDirInWebAppRootDir = [reldir|src|]
|
||||
|
||||
webAppSrcDirInProjectRootDir :: Path (Rel ProjectRootDir) (Dir WebAppSrcDir)
|
||||
webAppSrcDirInProjectRootDir :: Path' (Rel ProjectRootDir) (Dir WebAppSrcDir)
|
||||
webAppSrcDirInProjectRootDir = webAppRootDirInProjectRootDir </> webAppSrcDirInWebAppRootDir
|
||||
|
||||
-- * Templates
|
||||
|
||||
-- | Path in templates directory where web app templates reside.
|
||||
webAppTemplatesDirInTemplatesDir :: Path (Rel TemplatesDir) (Dir WebAppTemplatesDir)
|
||||
webAppTemplatesDirInTemplatesDir = SP.fromPathRelDir [P.reldir|react-app|]
|
||||
webAppTemplatesDirInTemplatesDir :: Path' (Rel TemplatesDir) (Dir WebAppTemplatesDir)
|
||||
webAppTemplatesDirInTemplatesDir = [reldir|react-app|]
|
||||
|
||||
copyTmplAsIs :: Path (Rel WebAppTemplatesDir) File -> FileDraft
|
||||
copyTmplAsIs :: Path' (Rel WebAppTemplatesDir) File' -> FileDraft
|
||||
copyTmplAsIs path = makeTemplateFD path (SP.castRel path) Nothing
|
||||
|
||||
makeSimpleTemplateFD :: Path (Rel WebAppTemplatesDir) File -> Wasp -> FileDraft
|
||||
makeSimpleTemplateFD :: Path' (Rel WebAppTemplatesDir) File' -> Wasp -> FileDraft
|
||||
makeSimpleTemplateFD path wasp = makeTemplateFD path (SP.castRel path) (Just $ Aeson.toJSON wasp)
|
||||
|
||||
makeTemplateFD ::
|
||||
Path (Rel WebAppTemplatesDir) File ->
|
||||
Path (Rel WebAppRootDir) File ->
|
||||
Path' (Rel WebAppTemplatesDir) File' ->
|
||||
Path' (Rel WebAppRootDir) File' ->
|
||||
Maybe Aeson.Value ->
|
||||
FileDraft
|
||||
makeTemplateFD srcPathInWebAppTemplatesDir dstPathInWebAppRootDir tmplData =
|
||||
|
@ -7,14 +7,13 @@ where
|
||||
import Generator.ExternalCodeGenerator.Common (ExternalCodeGeneratorStrategy (..), GeneratedExternalCodeDir)
|
||||
import Generator.ExternalCodeGenerator.Js (resolveJsFileWaspImportsForExtCodeDir)
|
||||
import qualified Generator.WebAppGenerator.Common as C
|
||||
import qualified Path as P
|
||||
import StrongPath (Dir, Path, Rel, (</>))
|
||||
import StrongPath (Dir, Path', Rel, reldir, (</>))
|
||||
import qualified StrongPath as SP
|
||||
|
||||
-- | Relative path to directory where external code will be generated.
|
||||
-- Relative to web app src dir.
|
||||
extCodeDirInWebAppSrcDir :: Path (Rel C.WebAppSrcDir) (Dir GeneratedExternalCodeDir)
|
||||
extCodeDirInWebAppSrcDir = SP.fromPathRelDir [P.reldir|ext-src|]
|
||||
extCodeDirInWebAppSrcDir :: Path' (Rel C.WebAppSrcDir) (Dir GeneratedExternalCodeDir)
|
||||
extCodeDirInWebAppSrcDir = [reldir|ext-src|]
|
||||
|
||||
generatorStrategy :: ExternalCodeGeneratorStrategy
|
||||
generatorStrategy =
|
||||
|
@ -17,7 +17,7 @@ import qualified Generator.ServerGenerator as ServerGenerator
|
||||
import qualified Generator.ServerGenerator.OperationsRoutesG as ServerOperationsRoutesG
|
||||
import qualified Generator.WebAppGenerator.Common as C
|
||||
import qualified Generator.WebAppGenerator.OperationsGenerator.ResourcesG as Resources
|
||||
import qualified Path as P
|
||||
import StrongPath (File', Path', Rel', parseRelFile, reldir, relfile, (</>))
|
||||
import Wasp (Wasp)
|
||||
import qualified Wasp
|
||||
import qualified Wasp.Action
|
||||
@ -29,7 +29,7 @@ genOperations wasp =
|
||||
concat
|
||||
[ genQueries wasp,
|
||||
genActions wasp,
|
||||
[C.makeSimpleTemplateFD (C.asTmplFile [P.relfile|src/operations/index.js|]) wasp],
|
||||
[C.makeSimpleTemplateFD (C.asTmplFile [relfile|src/operations/index.js|]) wasp],
|
||||
Resources.genResources wasp
|
||||
]
|
||||
|
||||
@ -37,7 +37,7 @@ genQueries :: Wasp -> [FileDraft]
|
||||
genQueries wasp =
|
||||
concat
|
||||
[ map (genQuery wasp) (Wasp.getQueries wasp),
|
||||
[C.makeSimpleTemplateFD (C.asTmplFile [P.relfile|src/queries/index.js|]) wasp]
|
||||
[C.makeSimpleTemplateFD (C.asTmplFile [relfile|src/queries/index.js|]) wasp]
|
||||
]
|
||||
|
||||
genActions :: Wasp -> [FileDraft]
|
||||
@ -49,9 +49,9 @@ genActions wasp =
|
||||
genQuery :: Wasp -> Wasp.Query.Query -> FileDraft
|
||||
genQuery _ query = C.makeTemplateFD tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
tmplFile = C.asTmplFile [P.relfile|src/queries/_query.js|]
|
||||
tmplFile = C.asTmplFile [relfile|src/queries/_query.js|]
|
||||
|
||||
dstFile = C.asWebAppFile $ [P.reldir|src/queries/|] P.</> fromJust (getOperationDstFileName operation)
|
||||
dstFile = C.asWebAppFile $ [reldir|src/queries/|] </> fromJust (getOperationDstFileName operation)
|
||||
tmplData =
|
||||
object
|
||||
[ "queryFnName" .= Wasp.Query._name query,
|
||||
@ -67,9 +67,9 @@ genQuery _ query = C.makeTemplateFD tmplFile dstFile (Just tmplData)
|
||||
genAction :: Wasp -> Wasp.Action.Action -> FileDraft
|
||||
genAction _ action = C.makeTemplateFD tmplFile dstFile (Just tmplData)
|
||||
where
|
||||
tmplFile = C.asTmplFile [P.relfile|src/actions/_action.js|]
|
||||
tmplFile = C.asTmplFile [relfile|src/actions/_action.js|]
|
||||
|
||||
dstFile = C.asWebAppFile $ [P.reldir|src/actions/|] P.</> fromJust (getOperationDstFileName operation)
|
||||
dstFile = C.asWebAppFile $ [reldir|src/actions/|] </> fromJust (getOperationDstFileName operation)
|
||||
tmplData =
|
||||
object
|
||||
[ "actionFnName" .= Wasp.Action._name action,
|
||||
@ -89,5 +89,5 @@ makeJsArrayOfEntityNames operation = "[" ++ intercalate ", " entityStrings ++ "]
|
||||
where
|
||||
entityStrings = map (\x -> "'" ++ x ++ "'") $ fromMaybe [] $ Wasp.Operation.getEntities operation
|
||||
|
||||
getOperationDstFileName :: Wasp.Operation.Operation -> Maybe (P.Path P.Rel P.File)
|
||||
getOperationDstFileName operation = P.parseRelFile (Wasp.Operation.getName operation ++ ".js")
|
||||
getOperationDstFileName :: Wasp.Operation.Operation -> Maybe (Path' Rel' File')
|
||||
getOperationDstFileName operation = parseRelFile (Wasp.Operation.getName operation ++ ".js")
|
||||
|
@ -6,12 +6,12 @@ where
|
||||
import Data.Aeson (object)
|
||||
import Generator.FileDraft (FileDraft)
|
||||
import qualified Generator.WebAppGenerator.Common as C
|
||||
import qualified Path as P
|
||||
import StrongPath (relfile)
|
||||
import Wasp (Wasp)
|
||||
|
||||
genResources :: Wasp -> [FileDraft]
|
||||
genResources _ = [C.makeTemplateFD tmplFile dstFile (Just tmplData)]
|
||||
where
|
||||
tmplFile = C.asTmplFile [P.relfile|src/operations/resources.js|]
|
||||
dstFile = C.asWebAppFile $ [P.relfile|src/operations/resources.js|] -- TODO: Un-hardcode this by combining path to operations dir with path to resources file in it.
|
||||
tmplFile = C.asTmplFile [relfile|src/operations/resources.js|]
|
||||
dstFile = C.asWebAppFile [relfile|src/operations/resources.js|] -- TODO: Un-hardcode this by combining path to operations dir with path to resources file in it.
|
||||
tmplData = object []
|
||||
|
@ -4,12 +4,11 @@ module Generator.WebAppGenerator.RouterGenerator
|
||||
where
|
||||
|
||||
import Data.Aeson (ToJSON (..), object, (.=))
|
||||
import Data.Maybe (isJust)
|
||||
import Data.Maybe (fromJust, isJust)
|
||||
import Generator.FileDraft (FileDraft)
|
||||
import Generator.WebAppGenerator.Common (asTmplFile, asWebAppSrcFile)
|
||||
import qualified Generator.WebAppGenerator.Common as C
|
||||
import qualified Path as P
|
||||
import StrongPath ((</>))
|
||||
import StrongPath (reldir, relfile, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import Wasp (Wasp)
|
||||
import qualified Wasp
|
||||
@ -59,11 +58,11 @@ instance ToJSON PageTemplateData where
|
||||
generateRouter :: Wasp -> FileDraft
|
||||
generateRouter wasp =
|
||||
C.makeTemplateFD
|
||||
(asTmplFile $ [P.reldir|src|] P.</> routerPath)
|
||||
(asTmplFile $ [reldir|src|] </> routerPath)
|
||||
targetPath
|
||||
(Just $ toJSON templateData)
|
||||
where
|
||||
routerPath = [P.relfile|router.js|]
|
||||
routerPath = [relfile|router.js|]
|
||||
templateData = createRouterTemplateData wasp
|
||||
targetPath = C.webAppSrcDirInWebAppRootDir </> asWebAppSrcFile routerPath
|
||||
|
||||
@ -108,7 +107,7 @@ createPageTemplateData page =
|
||||
PageTemplateData
|
||||
{ _importFrom =
|
||||
relPathToExtSrcDir
|
||||
++ SP.toFilePath (SP.relFileToPosix' $ Wasp.JsImport._from pageComponent),
|
||||
++ SP.fromRelFileP (fromJust $ SP.relFileToPosix $ Wasp.JsImport._from pageComponent),
|
||||
_importWhat = case Wasp.JsImport._namedImports pageComponent of
|
||||
-- If no named imports, we go with the default import.
|
||||
[] -> pageName
|
||||
|
@ -7,9 +7,9 @@ import Generator.Common (ProjectRootDir)
|
||||
import qualified Generator.Job as J
|
||||
import Generator.Job.Process (runNodeCommandAsJob)
|
||||
import qualified Generator.WebAppGenerator.Common as Common
|
||||
import StrongPath (Abs, Dir, Path, (</>))
|
||||
import StrongPath (Abs, Dir, Path', (</>))
|
||||
|
||||
setupWebApp :: Path Abs (Dir ProjectRootDir) -> J.Job
|
||||
setupWebApp :: Path' Abs (Dir ProjectRootDir) -> J.Job
|
||||
setupWebApp projectDir = do
|
||||
let webAppDir = projectDir </> Common.webAppRootDirInProjectRootDir
|
||||
runNodeCommandAsJob webAppDir "npm" ["install"] J.WebApp
|
||||
|
@ -7,9 +7,9 @@ import Generator.Common (ProjectRootDir)
|
||||
import qualified Generator.Job as J
|
||||
import Generator.Job.Process (runNodeCommandAsJob)
|
||||
import qualified Generator.WebAppGenerator.Common as Common
|
||||
import StrongPath (Abs, Dir, Path, (</>))
|
||||
import StrongPath (Abs, Dir, Path', (</>))
|
||||
|
||||
startWebApp :: Path Abs (Dir ProjectRootDir) -> J.Job
|
||||
startWebApp :: Path' Abs (Dir ProjectRootDir) -> J.Job
|
||||
startWebApp projectDir = do
|
||||
let webAppDir = projectDir </> Common.webAppRootDirInProjectRootDir
|
||||
runNodeCommandAsJob webAppDir "npm" ["start"] J.WebApp
|
||||
|
@ -9,15 +9,14 @@ where
|
||||
import Common (WaspProjectDir)
|
||||
import CompileOptions (CompileOptions)
|
||||
import qualified CompileOptions
|
||||
import Control.Monad.IO.Class (liftIO)
|
||||
import Data.List (find, isSuffixOf)
|
||||
import qualified ExternalCode
|
||||
import qualified Generator
|
||||
import Generator.Common (ProjectRootDir)
|
||||
import qualified Parser
|
||||
import qualified Path as P
|
||||
import StrongPath (Abs, Dir, Path)
|
||||
import StrongPath (Abs, Dir, File', Path', relfile)
|
||||
import qualified StrongPath as SP
|
||||
import qualified StrongPath.Path as SP.Path
|
||||
import System.Directory (doesFileExist)
|
||||
import qualified Util.IO
|
||||
import Wasp (Wasp)
|
||||
@ -26,8 +25,8 @@ import qualified Wasp
|
||||
type CompileError = String
|
||||
|
||||
compile ::
|
||||
Path Abs (Dir WaspProjectDir) ->
|
||||
Path Abs (Dir ProjectRootDir) ->
|
||||
Path' Abs (Dir WaspProjectDir) ->
|
||||
Path' Abs (Dir ProjectRootDir) ->
|
||||
CompileOptions ->
|
||||
IO (Either CompileError ())
|
||||
compile waspDir outDir options = do
|
||||
@ -58,18 +57,17 @@ enrichWaspASTBasedOnCompileOptions wasp options = do
|
||||
`Wasp.setIsBuild` CompileOptions.isBuild options
|
||||
)
|
||||
|
||||
findWaspFile :: Path Abs (Dir WaspProjectDir) -> IO (Maybe (Path Abs SP.File))
|
||||
findWaspFile :: Path' Abs (Dir WaspProjectDir) -> IO (Maybe (Path' Abs File'))
|
||||
findWaspFile waspDir = do
|
||||
(files, _) <- liftIO $ Util.IO.listDirectory (SP.toPathAbsDir waspDir)
|
||||
return $ (waspDir SP.</>) . SP.fromPathRelFile <$> find isWaspFile files
|
||||
files <- map SP.Path.fromPathRelFile . fst <$> Util.IO.listDirectory (SP.Path.toPathAbsDir waspDir)
|
||||
return $ (waspDir SP.</>) <$> find isWaspFile files
|
||||
where
|
||||
isWaspFile :: P.Path P.Rel P.File -> Bool
|
||||
isWaspFile path =
|
||||
".wasp" `isSuffixOf` P.toFilePath path
|
||||
&& (length (P.toFilePath path) > length (".wasp" :: String))
|
||||
".wasp" `isSuffixOf` SP.toFilePath path
|
||||
&& (length (SP.toFilePath path) > length (".wasp" :: String))
|
||||
|
||||
findDotEnvFile :: Path Abs (Dir WaspProjectDir) -> IO (Maybe (Path Abs SP.File))
|
||||
findDotEnvFile :: Path' Abs (Dir WaspProjectDir) -> IO (Maybe (Path' Abs File'))
|
||||
findDotEnvFile waspDir = do
|
||||
let dotEnvAbsPath = waspDir SP.</> SP.fromPathRelFile [P.relfile|.env|]
|
||||
let dotEnvAbsPath = waspDir SP.</> [relfile|.env|]
|
||||
dotEnvExists <- doesFileExist (SP.toFilePath dotEnvAbsPath)
|
||||
return $ if dotEnvExists then Just dotEnvAbsPath else Nothing
|
||||
|
@ -6,8 +6,8 @@ module Parser.Common where
|
||||
|
||||
import qualified Data.Text as T
|
||||
import qualified Lexer as L
|
||||
import qualified Path as P
|
||||
import qualified Path.Posix as PPosix
|
||||
import StrongPath (File, Path, Posix, Rel, System)
|
||||
import qualified StrongPath as SP
|
||||
import Text.Parsec
|
||||
( ParseError,
|
||||
anyChar,
|
||||
@ -162,19 +162,19 @@ strip :: String -> String
|
||||
strip = T.unpack . T.strip . T.pack
|
||||
|
||||
-- | Parses relative file path, e.g. "my/file.txt".
|
||||
relFilePathString :: Parser (P.Path P.Rel P.File)
|
||||
relFilePathString :: Parser (Path System (Rel d) (File f))
|
||||
relFilePathString = do
|
||||
path <- L.stringLiteral
|
||||
maybe
|
||||
(unexpected $ "string \"" ++ path ++ "\": Expected relative file path.")
|
||||
return
|
||||
(P.parseRelFile path)
|
||||
(SP.parseRelFile path)
|
||||
|
||||
-- | Parses relative posix file path, e.g. "my/file.txt".
|
||||
relPosixFilePathString :: Parser (PPosix.Path PPosix.Rel PPosix.File)
|
||||
relPosixFilePathString :: Parser (Path Posix (Rel d) (File f))
|
||||
relPosixFilePathString = do
|
||||
path <- L.stringLiteral
|
||||
maybe
|
||||
(unexpected $ "string \"" ++ path ++ "\": Expected relative file path.")
|
||||
return
|
||||
(PPosix.parseRelFile path)
|
||||
(SP.parseRelFileP path)
|
||||
|
@ -6,18 +6,19 @@ where
|
||||
import ExternalCode (SourceExternalCodeDir)
|
||||
import qualified Parser.Common
|
||||
import qualified Path.Posix as PPosix
|
||||
import StrongPath (File, Path', Posix, Rel)
|
||||
import qualified StrongPath as SP
|
||||
import StrongPath (File', Path, Posix, Rel)
|
||||
import qualified StrongPath.Path as SP.Path
|
||||
import Text.Parsec (unexpected)
|
||||
import Text.Parsec.String (Parser)
|
||||
|
||||
-- Parses string literal that is file path to file in source external code dir.
|
||||
-- Returns file path relative to the external code dir.
|
||||
-- Example of input: "@ext/some/file.txt". Output would be: "some/file.txt".
|
||||
extCodeFilePathString :: Parser (Path' Posix (Rel SourceExternalCodeDir) File)
|
||||
extCodeFilePathString :: Parser (Path Posix (Rel SourceExternalCodeDir) File')
|
||||
extCodeFilePathString = do
|
||||
path <- Parser.Common.relPosixFilePathString
|
||||
maybe
|
||||
(unexpected $ "string \"" ++ show path ++ "\": External code file path should start with \"@ext/\".")
|
||||
(return . SP.fromPathRelFileP)
|
||||
(PPosix.stripProperPrefix [PPosix.reldir|@ext|] path)
|
||||
return
|
||||
-- TODO: Once StrongPath supports stripProperPrefix method, use that instead of transforming it to Path and back.
|
||||
(SP.Path.fromPathRelFileP <$> PPosix.stripProperPrefix [PPosix.reldir|@ext|] (SP.Path.toPathRelFileP path))
|
||||
|
@ -1,489 +0,0 @@
|
||||
{-# LANGUAGE PartialTypeSignatures #-}
|
||||
|
||||
module StrongPath
|
||||
( Path,
|
||||
Path',
|
||||
Abs,
|
||||
Rel,
|
||||
Dir,
|
||||
File,
|
||||
File',
|
||||
System,
|
||||
Windows,
|
||||
Posix,
|
||||
parseRelDir,
|
||||
parseRelFile,
|
||||
parseAbsDir,
|
||||
parseAbsFile,
|
||||
parseRelDirW,
|
||||
parseRelFileW,
|
||||
parseAbsDirW,
|
||||
parseAbsFileW,
|
||||
parseRelDirP,
|
||||
parseRelFileP,
|
||||
parseAbsDirP,
|
||||
parseAbsFileP,
|
||||
fromPathRelDir,
|
||||
fromPathRelFile,
|
||||
fromPathAbsDir,
|
||||
fromPathAbsFile,
|
||||
fromPathRelDirW,
|
||||
fromPathRelFileW,
|
||||
fromPathAbsDirW,
|
||||
fromPathAbsFileW,
|
||||
fromPathRelDirP,
|
||||
fromPathRelFileP,
|
||||
fromPathAbsDirP,
|
||||
fromPathAbsFileP,
|
||||
toPathRelDir,
|
||||
toPathRelFile,
|
||||
toPathAbsDir,
|
||||
toPathAbsFile,
|
||||
toPathRelDirW,
|
||||
toPathRelFileW,
|
||||
toPathAbsDirW,
|
||||
toPathAbsFileW,
|
||||
toPathRelDirP,
|
||||
toPathRelFileP,
|
||||
toPathAbsDirP,
|
||||
toPathAbsFileP,
|
||||
fromRelDir,
|
||||
fromRelFile,
|
||||
fromAbsDir,
|
||||
fromAbsFile,
|
||||
fromRelDirP,
|
||||
fromRelFileP,
|
||||
fromAbsDirP,
|
||||
fromAbsFileP,
|
||||
fromRelDirW,
|
||||
fromRelFileW,
|
||||
fromAbsDirW,
|
||||
fromAbsFileW,
|
||||
toFilePath,
|
||||
(</>),
|
||||
castRel,
|
||||
castDir,
|
||||
parent,
|
||||
relDirToPosix,
|
||||
relFileToPosix,
|
||||
relDirToPosix',
|
||||
relFileToPosix',
|
||||
)
|
||||
where
|
||||
|
||||
import Control.Monad.Catch (MonadThrow)
|
||||
import Data.List (intercalate)
|
||||
import Data.Maybe (fromJust)
|
||||
import qualified Path as P
|
||||
import qualified Path.Posix as PP
|
||||
import qualified Path.Windows as PW
|
||||
import StrongPath.Internal
|
||||
import qualified System.FilePath as FP
|
||||
import qualified System.FilePath.Posix as FPP
|
||||
import qualified System.FilePath.Windows as FPW
|
||||
|
||||
-- TODO: We still depend on Path for creating hardcoded paths via generics. Any way to go around that?
|
||||
-- Maybe implement our own mechanism for that, so that people don't have to know about / use Path?
|
||||
-- This means we would implement our own [reldir|foobar|] stuff.
|
||||
|
||||
-- TODO: Can I use type classes and return type polymorhipsm to make all this shorter and reduce duplication?
|
||||
-- class Path, and then I have PathWindows and PathPosix and PathSystem implement it, smth like that?
|
||||
-- And then fromPathRelDir has polymorhic return type based on standard? I tried a little bit but it is complicated.
|
||||
|
||||
-- TODO: If there is no other solution to all this duplication, do some template haskell magic to simplify it.
|
||||
|
||||
-- TODO: Redo the types naming? Normal types should be Path Rel Dir File, while shortened ones should be
|
||||
-- Path' Rel' Dir' File'.
|
||||
-- This means that Path' is alias for Path System, Rel' for Rel (), Dir' for Dir (), File' for File ().
|
||||
|
||||
-- Constructors
|
||||
-- TODO: Although here I specify which exact type of Path (P.Path, PP.Path or PW.Path) is to be
|
||||
-- given as first argument, I realized that if I do:
|
||||
-- SP.fromPathRelDirW [P.reldir|test\file|]
|
||||
-- compiler will not complain, although I put P instead of PW!
|
||||
-- I am not sure why is this happening, we should figure it out.
|
||||
-- This is not great because it means somebody can by accident construct
|
||||
-- StrongPath that should be Windows but is really Posix.
|
||||
-- Or can they? I am not sure if P.Path is just considered the same as PW.Path,
|
||||
-- or P.relfile and PW.relfile and PP.relfile for some weird reason are polymorhic
|
||||
-- in return type, or what is happening. I believe it is something close to the latter,
|
||||
-- in which case it is less of a problem, but I am not sure.
|
||||
-- Actually, it also does not complain if I do:
|
||||
-- SP.fromPathRelFileP [P.reldir|test/file|]
|
||||
-- so although I put reldir, and it should be relfile, it does not complain! How is that possible!?
|
||||
-- If I put absdir, then it does complain, however not if I put reldir. Very weird.
|
||||
-- NOTE: In Path, Path.Windows.Path and Path.Posix.Path are actually the same Path it seems
|
||||
-- so compiler does not differentiate them (because they are all exporting the same module containing Path),
|
||||
-- but Path.Windows.Rel and Path.Posix.Rel (and same for Abs/Dir/File) are not the same,
|
||||
-- because they are done via Include mechanism.
|
||||
fromPathRelDir :: P.Path P.Rel P.Dir -> Path' System (Rel a) (Dir b)
|
||||
fromPathRelFile :: P.Path P.Rel P.File -> Path' System (Rel a) (File' f)
|
||||
fromPathAbsDir :: P.Path P.Abs P.Dir -> Path' System Abs (Dir a)
|
||||
fromPathAbsFile :: P.Path P.Abs P.File -> Path' System Abs (File' f)
|
||||
fromPathRelDirW :: PW.Path PW.Rel PW.Dir -> Path' Windows (Rel a) (Dir b)
|
||||
fromPathRelFileW :: PW.Path PW.Rel PW.File -> Path' Windows (Rel a) (File' f)
|
||||
fromPathAbsDirW :: PW.Path PW.Abs PW.Dir -> Path' Windows Abs (Dir a)
|
||||
fromPathAbsFileW :: PW.Path PW.Abs PW.File -> Path' Windows Abs (File' f)
|
||||
fromPathRelDirP :: PP.Path PP.Rel PP.Dir -> Path' Posix (Rel a) (Dir b)
|
||||
fromPathRelFileP :: PP.Path PP.Rel PP.File -> Path' Posix (Rel a) (File' f)
|
||||
fromPathAbsDirP :: PP.Path PP.Abs PP.Dir -> Path' Posix Abs (Dir a)
|
||||
fromPathAbsFileP :: PP.Path PP.Abs PP.File -> Path' Posix Abs (File' f)
|
||||
---- System
|
||||
fromPathRelDir p = RelDir p NoPrefix
|
||||
|
||||
fromPathRelFile p = RelFile p NoPrefix
|
||||
|
||||
fromPathAbsDir = AbsDir
|
||||
|
||||
fromPathAbsFile = AbsFile
|
||||
|
||||
---- Windows
|
||||
fromPathRelDirW p = RelDirW p NoPrefix
|
||||
|
||||
fromPathRelFileW p = RelFileW p NoPrefix
|
||||
|
||||
fromPathAbsDirW = AbsDirW
|
||||
|
||||
fromPathAbsFileW = AbsFileW
|
||||
|
||||
---- Posix
|
||||
fromPathRelDirP p = RelDirP p NoPrefix
|
||||
|
||||
fromPathRelFileP p = RelFileP p NoPrefix
|
||||
|
||||
fromPathAbsDirP = AbsDirP
|
||||
|
||||
fromPathAbsFileP = AbsFileP
|
||||
|
||||
-- TODO: Should I go with MonadThrow here instead of just throwing error? Probably!
|
||||
-- I could, as error, return actual Path + info on how many ../ were there in StrongPath,
|
||||
-- so user can recover from error and continue, if they wish.
|
||||
-- Deconstructors
|
||||
toPathRelDir :: Path' System (Rel a) (Dir b) -> P.Path P.Rel P.Dir
|
||||
toPathRelFile :: Path' System (Rel a) (File' f) -> P.Path P.Rel P.File
|
||||
toPathAbsDir :: Path' System Abs (Dir a) -> P.Path P.Abs P.Dir
|
||||
toPathAbsFile :: Path' System Abs (File' f) -> P.Path P.Abs P.File
|
||||
toPathRelDirW :: Path' Windows (Rel a) (Dir b) -> PW.Path PW.Rel PW.Dir
|
||||
toPathRelFileW :: Path' Windows (Rel a) (File' f) -> PW.Path PW.Rel PW.File
|
||||
toPathAbsDirW :: Path' Windows Abs (Dir a) -> PW.Path PW.Abs PW.Dir
|
||||
toPathAbsFileW :: Path' Windows Abs (File' f) -> PW.Path PW.Abs PW.File
|
||||
toPathRelDirP :: Path' Posix (Rel a) (Dir b) -> PP.Path PP.Rel PP.Dir
|
||||
toPathRelFileP :: Path' Posix (Rel a) (File' f) -> PP.Path PP.Rel PP.File
|
||||
toPathAbsDirP :: Path' Posix Abs (Dir a) -> PP.Path PP.Abs PP.Dir
|
||||
toPathAbsFileP :: Path' Posix Abs (File' f) -> PP.Path PP.Abs PP.File
|
||||
---- System
|
||||
toPathRelDir (RelDir p NoPrefix) = p
|
||||
toPathRelDir (RelDir _ _) = relativeStrongPathWithPrefixToPathError
|
||||
toPathRelDir _ = impossible
|
||||
|
||||
toPathRelFile (RelFile p NoPrefix) = p
|
||||
toPathRelFile (RelFile _ _) = relativeStrongPathWithPrefixToPathError
|
||||
toPathRelFile _ = impossible
|
||||
|
||||
toPathAbsDir (AbsDir p) = p
|
||||
toPathAbsDir _ = impossible
|
||||
|
||||
toPathAbsFile (AbsFile p) = p
|
||||
toPathAbsFile _ = impossible
|
||||
|
||||
---- Windows
|
||||
toPathRelDirW (RelDirW p NoPrefix) = p
|
||||
toPathRelDirW (RelDirW _ _) = relativeStrongPathWithPrefixToPathError
|
||||
toPathRelDirW _ = impossible
|
||||
|
||||
toPathRelFileW (RelFileW p NoPrefix) = p
|
||||
toPathRelFileW (RelFileW _ _) = relativeStrongPathWithPrefixToPathError
|
||||
toPathRelFileW _ = impossible
|
||||
|
||||
toPathAbsDirW (AbsDirW p) = p
|
||||
toPathAbsDirW _ = impossible
|
||||
|
||||
toPathAbsFileW (AbsFileW p) = p
|
||||
toPathAbsFileW _ = impossible
|
||||
|
||||
---- Posix
|
||||
toPathRelDirP (RelDirP p NoPrefix) = p
|
||||
toPathRelDirP (RelDirP _ _) = relativeStrongPathWithPrefixToPathError
|
||||
toPathRelDirP _ = impossible
|
||||
|
||||
toPathRelFileP (RelFileP p NoPrefix) = p
|
||||
toPathRelFileP (RelFileP _ _) = relativeStrongPathWithPrefixToPathError
|
||||
toPathRelFileP _ = impossible
|
||||
|
||||
toPathAbsDirP (AbsDirP p) = p
|
||||
toPathAbsDirP _ = impossible
|
||||
|
||||
toPathAbsFileP (AbsFileP p) = p
|
||||
toPathAbsFileP _ = impossible
|
||||
|
||||
relativeStrongPathWithPrefixToPathError :: a
|
||||
relativeStrongPathWithPrefixToPathError =
|
||||
error "Relative StrongPath.Path with prefix can't be converted into Path.Path."
|
||||
|
||||
-- | Parsers.
|
||||
-- How parsers work:
|
||||
-- Parsers From To
|
||||
-- parseRel[Dir|File] System/Posix System
|
||||
-- parseRel[Dir|File]W Win/Posix Win
|
||||
-- parseRel[Dir|File]P Posix Posix
|
||||
-- parseAbs[Dir|File] System/Posix* System
|
||||
-- parseAbs[Dir|File]W Win/Posix* Win
|
||||
-- parseAbs[Dir|File]P Posix Posix
|
||||
--
|
||||
-- NOTE: System/Posix* means that path has to be System with exception of separators
|
||||
-- that can be Posix besides being System (but e.g. root can't be Posix).
|
||||
-- Win/Posix* is analogous to System/Posix*.
|
||||
parseRelDir :: MonadThrow m => FilePath -> m (Path' System (Rel d1) (Dir d2))
|
||||
parseRelFile :: MonadThrow m => FilePath -> m (Path' System (Rel d) (File' f))
|
||||
parseAbsDir :: MonadThrow m => FilePath -> m (Path' System Abs (Dir d))
|
||||
parseAbsFile :: MonadThrow m => FilePath -> m (Path' System Abs (File' f))
|
||||
parseRelDirW :: MonadThrow m => FilePath -> m (Path' Windows (Rel d1) (Dir d2))
|
||||
parseRelFileW :: MonadThrow m => FilePath -> m (Path' Windows (Rel d) (File' f))
|
||||
parseAbsDirW :: MonadThrow m => FilePath -> m (Path' Windows Abs (Dir d))
|
||||
parseAbsFileW :: MonadThrow m => FilePath -> m (Path' Windows Abs (File' f))
|
||||
parseRelDirP :: MonadThrow m => FilePath -> m (Path' Posix (Rel d1) (Dir d2))
|
||||
parseRelFileP :: MonadThrow m => FilePath -> m (Path' Posix (Rel d) (File' f))
|
||||
parseAbsDirP :: MonadThrow m => FilePath -> m (Path' Posix Abs (Dir d))
|
||||
parseAbsFileP :: MonadThrow m => FilePath -> m (Path' Posix Abs (File' f))
|
||||
---- System
|
||||
parseRelDir = parseRelFP RelDir [FP.pathSeparator, FPP.pathSeparator] P.parseRelDir
|
||||
|
||||
parseRelFile = parseRelFP RelFile [FP.pathSeparator, FPP.pathSeparator] P.parseRelFile
|
||||
|
||||
parseAbsDir fp = fromPathAbsDir <$> P.parseAbsDir fp
|
||||
|
||||
parseAbsFile fp = fromPathAbsFile <$> P.parseAbsFile fp
|
||||
|
||||
---- Windows
|
||||
parseRelDirW = parseRelFP RelDirW [FPW.pathSeparator, FPP.pathSeparator] PW.parseRelDir
|
||||
|
||||
parseRelFileW = parseRelFP RelFileW [FPW.pathSeparator, FPP.pathSeparator] PW.parseRelFile
|
||||
|
||||
parseAbsDirW fp = fromPathAbsDirW <$> PW.parseAbsDir fp
|
||||
|
||||
parseAbsFileW fp = fromPathAbsFileW <$> PW.parseAbsFile fp
|
||||
|
||||
---- Posix
|
||||
parseRelDirP = parseRelFP RelDirP [FPP.pathSeparator] PP.parseRelDir
|
||||
|
||||
parseRelFileP = parseRelFP RelFileP [FPP.pathSeparator] PP.parseRelFile
|
||||
|
||||
parseAbsDirP fp = fromPathAbsDirP <$> PP.parseAbsDir fp
|
||||
|
||||
parseAbsFileP fp = fromPathAbsFileP <$> PP.parseAbsFile fp
|
||||
|
||||
toFilePath :: Path' s b t -> FilePath
|
||||
toFilePath sp = case sp of
|
||||
---- System
|
||||
RelDir p prefix -> relPathToFilePath P.toFilePath FP.pathSeparator prefix p
|
||||
RelFile p prefix -> relPathToFilePath P.toFilePath FP.pathSeparator prefix p
|
||||
AbsDir p -> P.toFilePath p
|
||||
AbsFile p -> P.toFilePath p
|
||||
---- Windows
|
||||
RelDirW p prefix -> relPathToFilePath PW.toFilePath FPW.pathSeparator prefix p
|
||||
RelFileW p prefix -> relPathToFilePath PW.toFilePath FPW.pathSeparator prefix p
|
||||
AbsDirW p -> PW.toFilePath p
|
||||
AbsFileW p -> PW.toFilePath p
|
||||
---- Posix
|
||||
RelDirP p prefix -> relPathToFilePath PP.toFilePath FPP.pathSeparator prefix p
|
||||
RelFileP p prefix -> relPathToFilePath PP.toFilePath FPP.pathSeparator prefix p
|
||||
AbsDirP p -> PP.toFilePath p
|
||||
AbsFileP p -> PP.toFilePath p
|
||||
where
|
||||
relPathToFilePath pathToFilePath sep prefix path =
|
||||
combinePrefixWithPath sep (relPathPrefixToFilePath sep prefix) (pathToFilePath path)
|
||||
|
||||
relPathPrefixToFilePath :: Char -> RelPathPrefix -> FilePath
|
||||
relPathPrefixToFilePath _ NoPrefix = ""
|
||||
relPathPrefixToFilePath sep (ParentDir n) =
|
||||
intercalate [sep] (replicate n "..") ++ [sep]
|
||||
|
||||
-- TODO: This function and helper functions above are somewhat too loose and hard to
|
||||
-- follow, implement them in better way.
|
||||
-- Here we are assuming that prefix is of form (../)*, therefore it ends with separator,
|
||||
-- and it could also be empty.
|
||||
combinePrefixWithPath :: Char -> String -> FilePath -> FilePath
|
||||
combinePrefixWithPath sep prefix path
|
||||
| path `elem` [".", ['.', sep], "./"] && not (null prefix) = prefix
|
||||
combinePrefixWithPath _ prefix path = prefix ++ path
|
||||
|
||||
-- These functions just call toFilePath, but their value is in
|
||||
-- their type: they allow you to capture expected type of the strong path
|
||||
-- that you want to convert into FilePath.
|
||||
fromRelDir :: Path' System (Rel r) (Dir d) -> FilePath
|
||||
fromRelDir = toFilePath
|
||||
|
||||
fromRelFile :: Path' System (Rel r) (File' f) -> FilePath
|
||||
fromRelFile = toFilePath
|
||||
|
||||
fromAbsDir :: Path' System Abs (Dir d) -> FilePath
|
||||
fromAbsDir = toFilePath
|
||||
|
||||
fromAbsFile :: Path' System Abs (File' f) -> FilePath
|
||||
fromAbsFile = toFilePath
|
||||
|
||||
fromRelDirP :: Path' Posix (Rel r) (Dir d) -> FilePath
|
||||
fromRelDirP = toFilePath
|
||||
|
||||
fromRelFileP :: Path' Posix (Rel r) (File' f) -> FilePath
|
||||
fromRelFileP = toFilePath
|
||||
|
||||
fromAbsDirP :: Path' Posix Abs (Dir d) -> FilePath
|
||||
fromAbsDirP = toFilePath
|
||||
|
||||
fromAbsFileP :: Path' Posix Abs (File' f) -> FilePath
|
||||
fromAbsFileP = toFilePath
|
||||
|
||||
fromRelDirW :: Path' Windows (Rel r) (Dir d) -> FilePath
|
||||
fromRelDirW = toFilePath
|
||||
|
||||
fromRelFileW :: Path' Windows (Rel r) (File' f) -> FilePath
|
||||
fromRelFileW = toFilePath
|
||||
|
||||
fromAbsDirW :: Path' Windows Abs (Dir d) -> FilePath
|
||||
fromAbsDirW = toFilePath
|
||||
|
||||
fromAbsFileW :: Path' Windows Abs (File' f) -> FilePath
|
||||
fromAbsFileW = toFilePath
|
||||
|
||||
-- | Either removes last entry or if there are no entries and just "../"s, adds one more "../".
|
||||
-- If path is absolute root and it has no parent, it will return unchanged path, same like Path.
|
||||
parent :: Path' s b t -> Path' s b (Dir d)
|
||||
parent path = case path of
|
||||
---- System
|
||||
RelDir p prefix -> relDirPathParent RelDir P.parent p prefix
|
||||
RelFile p prefix -> RelDir (P.parent p) prefix
|
||||
AbsDir p -> AbsDir $ P.parent p
|
||||
AbsFile p -> AbsDir $ P.parent p
|
||||
---- Windows
|
||||
RelDirW p prefix -> relDirPathParent RelDirW PW.parent p prefix
|
||||
RelFileW p prefix -> RelDirW (PW.parent p) prefix
|
||||
AbsDirW p -> AbsDirW $ PW.parent p
|
||||
AbsFileW p -> AbsDirW $ PW.parent p
|
||||
---- Posix
|
||||
RelDirP p prefix -> relDirPathParent RelDirP PP.parent p prefix
|
||||
RelFileP p prefix -> RelDirP (PP.parent p) prefix
|
||||
AbsDirP p -> AbsDirP $ PP.parent p
|
||||
AbsFileP p -> AbsDirP $ PP.parent p
|
||||
where
|
||||
-- NOTE: We need this special logic for RelDir, because if we have RelDir Path,
|
||||
-- it is possible that it is "." or smth like that and no parent can be obtained,
|
||||
-- in which case we want to add "../" to our prefix.
|
||||
-- For file though, we don't have that concern, because it will always be possible to
|
||||
-- get a parent, as per current Path implementation.
|
||||
relDirPathParent constructor pathParent p prefix =
|
||||
if pathParent p == p
|
||||
then
|
||||
let prefix' = case prefix of
|
||||
ParentDir n -> ParentDir (n + 1)
|
||||
NoPrefix -> ParentDir 1
|
||||
in constructor p prefix'
|
||||
else
|
||||
let p' = pathParent p
|
||||
in constructor p' prefix
|
||||
|
||||
-- | How "../"s are resolved:
|
||||
-- For each "../" at the start of the right hand path, one most right entry is removed
|
||||
-- from the left hand path.
|
||||
-- Example: "a/b" </> "../c" = "a/c"
|
||||
-- If left path is absolute and right path has too many "../"s, they go "over" the root
|
||||
-- and are effectively ignored.
|
||||
-- Example: "/a/b" </> "../../../c" = "/c"
|
||||
-- If left path is relative and right path has more "../"s then left has entries,
|
||||
-- the leftover "../"s are carried over.
|
||||
-- Example: "a/b" </> "../../../c" = "../c"
|
||||
(</>) :: Path' s a (Dir d) -> Path' s (Rel d) c -> Path' s a c
|
||||
---- System
|
||||
lsp@(RelDir _ _) </> (RelFile rp rprefix) =
|
||||
let (RelDir lp' lprefix') = iterate parent lsp !! prefixNumParentDirs rprefix
|
||||
in RelFile (lp' P.</> rp) lprefix'
|
||||
lsp@(RelDir _ _) </> (RelDir rp rprefix) =
|
||||
let (RelDir lp' lprefix') = iterate parent lsp !! prefixNumParentDirs rprefix
|
||||
in RelDir (lp' P.</> rp) lprefix'
|
||||
lsp@(AbsDir _) </> (RelFile rp rprefix) =
|
||||
let (AbsDir lp') = iterate parent lsp !! prefixNumParentDirs rprefix
|
||||
in AbsFile (lp' P.</> rp)
|
||||
lsp@(AbsDir _) </> (RelDir rp rprefix) =
|
||||
let (AbsDir lp') = iterate parent lsp !! prefixNumParentDirs rprefix
|
||||
in AbsDir (lp' P.</> rp)
|
||||
---- Windows
|
||||
lsp@(RelDirW _ _) </> (RelFileW rp rprefix) =
|
||||
let (RelDirW lp' lprefix') = iterate parent lsp !! prefixNumParentDirs rprefix
|
||||
in RelFileW (lp' `pathWinCombineRelDirAndRelFile` rp) lprefix'
|
||||
lsp@(RelDirW _ _) </> (RelDirW rp rprefix) =
|
||||
let (RelDirW lp' lprefix') = iterate parent lsp !! prefixNumParentDirs rprefix
|
||||
in RelDirW (lp' `pathWinCombineRelDirAndRelDir` rp) lprefix'
|
||||
lsp@(AbsDirW _) </> (RelFileW rp rprefix) =
|
||||
let (AbsDirW lp') = iterate parent lsp !! prefixNumParentDirs rprefix
|
||||
in AbsFileW (lp' PW.</> rp)
|
||||
lsp@(AbsDirW _) </> (RelDirW rp rprefix) =
|
||||
let (AbsDirW lp') = iterate parent lsp !! prefixNumParentDirs rprefix
|
||||
in AbsDirW (lp' `pathWinCombineAbsDirAndRelDir` rp)
|
||||
---- Posix
|
||||
lsp@(RelDirP _ _) </> (RelFileP rp rprefix) =
|
||||
let (RelDirP lp' lprefix') = iterate parent lsp !! prefixNumParentDirs rprefix
|
||||
in RelFileP (lp' `pathPosixCombineRelDirAndRelFile` rp) lprefix'
|
||||
lsp@(RelDirP _ _) </> (RelDirP rp rprefix) =
|
||||
let (RelDirP lp' lprefix') = iterate parent lsp !! prefixNumParentDirs rprefix
|
||||
in RelDirP (lp' `pathPosixCombineRelDirAndRelDir` rp) lprefix'
|
||||
lsp@(AbsDirP _) </> (RelFileP rp rprefix) =
|
||||
let (AbsDirP lp') = iterate parent lsp !! prefixNumParentDirs rprefix
|
||||
in AbsFileP (lp' PP.</> rp)
|
||||
lsp@(AbsDirP _) </> (RelDirP rp rprefix) =
|
||||
let (AbsDirP lp') = iterate parent lsp !! prefixNumParentDirs rprefix
|
||||
in AbsDirP (lp' `pathPosixCombineAbsDirAndRelDir` rp)
|
||||
_ </> _ = impossible
|
||||
|
||||
castRel :: Path' s (Rel d1) a -> Path' s (Rel d2) a
|
||||
---- System
|
||||
castRel (RelDir p pr) = RelDir p pr
|
||||
castRel (RelFile p pr) = RelFile p pr
|
||||
---- Windows
|
||||
castRel (RelDirW p pr) = RelDirW p pr
|
||||
castRel (RelFileW p pr) = RelFileW p pr
|
||||
---- Posix
|
||||
castRel (RelDirP p pr) = RelDirP p pr
|
||||
castRel (RelFileP p pr) = RelFileP p pr
|
||||
castRel _ = impossible
|
||||
|
||||
castDir :: Path' s a (Dir d1) -> Path' s a (Dir d2)
|
||||
---- System
|
||||
castDir (AbsDir p) = AbsDir p
|
||||
castDir (RelDir p pr) = RelDir p pr
|
||||
---- Windows
|
||||
castDir (AbsDirW p) = AbsDirW p
|
||||
castDir (RelDirW p pr) = RelDirW p pr
|
||||
---- Posix
|
||||
castDir (AbsDirP p) = AbsDirP p
|
||||
castDir (RelDirP p pr) = RelDirP p pr
|
||||
castDir _ = impossible
|
||||
|
||||
-- TODO: I was not able to unite these two functions (`relDirToPosix` and `relFileToPosix`) into just `toPosix``
|
||||
-- because Haskell did not believe me that I would be returning same "t" (Dir/File) in Path
|
||||
-- as was in first argument. I wonder if there is easy way to go around that or if
|
||||
-- we have to redo significant part of the StrongPath to be able to do smth like this.
|
||||
|
||||
-- | Converts relative path to posix by replacing current path separators with posix path separators.
|
||||
-- Works well for "normal" relative paths like "a\b\c" (Win) or "a/b/c" (Posix).
|
||||
-- If path is weird but still considered relative, like just "C:" on Win,
|
||||
-- results can be unxpected, most likely resulting with error thrown.
|
||||
-- If path is already Posix, it will not change.
|
||||
relDirToPosix :: MonadThrow m => Path' s (Rel d1) (Dir d2) -> m (Path' Posix (Rel d1) (Dir d2))
|
||||
relDirToPosix sp@(RelDir _ _) = parseRelDirP $ FPP.joinPath $ FP.splitDirectories $ toFilePath sp
|
||||
relDirToPosix sp@(RelDirW _ _) = parseRelDirP $ FPP.joinPath $ FPW.splitDirectories $ toFilePath sp
|
||||
relDirToPosix (RelDirP p pr) = return $ RelDirP p pr
|
||||
relDirToPosix _ = impossible
|
||||
|
||||
relFileToPosix :: MonadThrow m => Path' s (Rel d1) (File' f) -> m (Path' Posix (Rel d1) (File' f))
|
||||
relFileToPosix sp@(RelFile _ _) = parseRelFileP $ FPP.joinPath $ FP.splitDirectories $ toFilePath sp
|
||||
relFileToPosix sp@(RelFileW _ _) = parseRelFileP $ FPP.joinPath $ FPW.splitDirectories $ toFilePath sp
|
||||
relFileToPosix (RelFileP p pr) = return $ RelFileP p pr
|
||||
relFileToPosix _ = impossible
|
||||
|
||||
-- TODO: Should I name these unsafe versions differently? Maybe relDirToPosixU?
|
||||
-- Unsafe versions:
|
||||
relDirToPosix' :: Path' s (Rel d1) (Dir d2) -> Path' Posix (Rel d1) (Dir d2)
|
||||
relDirToPosix' = fromJust . relDirToPosix
|
||||
|
||||
relFileToPosix' :: Path' s (Rel d1) (File' f) -> Path' Posix (Rel d1) (File' f)
|
||||
relFileToPosix' = fromJust . relFileToPosix
|
@ -1,160 +0,0 @@
|
||||
module StrongPath.Internal where
|
||||
|
||||
import Control.Monad.Catch (MonadThrow)
|
||||
import qualified Path as P
|
||||
import qualified Path.Posix as PP
|
||||
import qualified Path.Windows as PW
|
||||
import qualified System.FilePath.Posix as FPP
|
||||
import qualified System.FilePath.Windows as FPW
|
||||
|
||||
-- | s -> standard, b -> base, t -> type
|
||||
data Path' s b t
|
||||
= -- System
|
||||
RelDir (P.Path P.Rel P.Dir) RelPathPrefix
|
||||
| RelFile (P.Path P.Rel P.File) RelPathPrefix
|
||||
| AbsDir (P.Path P.Abs P.Dir)
|
||||
| AbsFile (P.Path P.Abs P.File)
|
||||
| -- Windows
|
||||
RelDirW (PW.Path PW.Rel PW.Dir) RelPathPrefix
|
||||
| RelFileW (PW.Path PW.Rel PW.File) RelPathPrefix
|
||||
| AbsDirW (PW.Path PW.Abs PW.Dir)
|
||||
| AbsFileW (PW.Path PW.Abs PW.File)
|
||||
| -- Posix
|
||||
RelDirP (PP.Path PP.Rel PP.Dir) RelPathPrefix
|
||||
| RelFileP (PP.Path PP.Rel PP.File) RelPathPrefix
|
||||
| AbsDirP (PP.Path PP.Abs PP.Dir)
|
||||
| AbsFileP (PP.Path PP.Abs PP.File)
|
||||
deriving (Show, Eq)
|
||||
|
||||
data RelPathPrefix
|
||||
= -- | ../, Int saying how many times it repeats.
|
||||
ParentDir Int
|
||||
| NoPrefix
|
||||
deriving (Show, Eq)
|
||||
|
||||
type Path = Path' System
|
||||
|
||||
-- | base
|
||||
data Abs
|
||||
|
||||
data Rel dir
|
||||
|
||||
-- | type
|
||||
data Dir dir
|
||||
|
||||
data File' file
|
||||
|
||||
type File = File' ()
|
||||
|
||||
-- | standard
|
||||
data System -- Depends on the platform, it is either Posix or Windows.
|
||||
|
||||
data Windows
|
||||
|
||||
data Posix
|
||||
|
||||
parseRelFP ::
|
||||
MonadThrow m =>
|
||||
(P.Path pb pt -> RelPathPrefix -> Path' s (Rel d) t) ->
|
||||
[Char] ->
|
||||
(FilePath -> m (P.Path pb pt)) ->
|
||||
FilePath ->
|
||||
m (Path' s (Rel d) t)
|
||||
parseRelFP constructor validSeparators pathParser fp =
|
||||
let (prefix, fp') = extractRelPathPrefix validSeparators fp
|
||||
fp'' = if fp' == "" then "." else fp' -- Because Path Rel parsers can't handle just "".
|
||||
in (\p -> constructor p prefix) <$> pathParser fp''
|
||||
|
||||
-- | Extracts a multiple "../" from start of the file path.
|
||||
-- If path is completely ../../.., also handles the last one.
|
||||
-- NOTE: We don't normalize path in any way.
|
||||
extractRelPathPrefix :: [Char] -> FilePath -> (RelPathPrefix, FilePath)
|
||||
extractRelPathPrefix validSeparators path =
|
||||
let (n, path') = dropParentDirs path
|
||||
in (if n == 0 then NoPrefix else ParentDir n, path')
|
||||
where
|
||||
parentDirStrings :: [String]
|
||||
parentDirStrings = [['.', '.', s] | s <- validSeparators]
|
||||
|
||||
pathStartsWithParentDir :: FilePath -> Bool
|
||||
pathStartsWithParentDir p = take 3 p `elem` parentDirStrings
|
||||
|
||||
dropParentDirs :: FilePath -> (Int, FilePath)
|
||||
dropParentDirs p
|
||||
| pathStartsWithParentDir p =
|
||||
let (n, p') = dropParentDirs (drop 3 p)
|
||||
in (1 + n, p')
|
||||
| p == ".." = (1, "")
|
||||
| otherwise = (0, p)
|
||||
|
||||
-- NOTE: These three funtions, pathWinCombine... exist only to fix
|
||||
-- Path.Windows.</> behaviour regarding concatenating '.' rel dirs
|
||||
-- with other paths. While for Path.System and Path.Posix this concatenation
|
||||
-- behaves as expected on Linux, Path.Windows behaves differently!
|
||||
-- In more details:
|
||||
-- [P.reldir|.|] P.</> [P.reldir|a|] results in [P.reldir|a|]
|
||||
-- however
|
||||
-- [PW.reldir|.|] PW.</> [PW.reldir|a|] results in [PW.reldir|.\\a|]
|
||||
-- To summarize it, for System/Posix, Path behaves as:
|
||||
-- . </> a = a
|
||||
-- . </> . = .
|
||||
-- a </> a = a
|
||||
-- While for Windows, Path behaves as:
|
||||
-- . </> a = .\a
|
||||
-- . </> . = .\.
|
||||
-- a </> . = a\.
|
||||
-- which we don't want, we want it to behave same as for System/Posix.
|
||||
-- That is why we handle these cases as special cases and then we let the Path.Windows.</>
|
||||
-- do the rest of the work.
|
||||
pathWinCombineRelDirAndRelFile :: PW.Path PW.Rel PW.Dir -> PW.Path PW.Rel PW.File -> PW.Path PW.Rel PW.File
|
||||
pathWinCombineRelDirAndRelFile lp rp
|
||||
| PW.toFilePath lp == ['.', FPW.pathSeparator] = rp
|
||||
| otherwise = lp PW.</> rp
|
||||
|
||||
pathWinCombineRelDirAndRelDir :: PW.Path PW.Rel PW.Dir -> PW.Path PW.Rel PW.Dir -> PW.Path PW.Rel PW.Dir
|
||||
pathWinCombineRelDirAndRelDir lp rp
|
||||
| PW.toFilePath lp == ['.', FPW.pathSeparator] = rp
|
||||
| PW.toFilePath rp == ['.', FPW.pathSeparator] = lp
|
||||
| otherwise = lp PW.</> rp
|
||||
|
||||
pathWinCombineAbsDirAndRelDir :: PW.Path PW.Abs PW.Dir -> PW.Path PW.Rel PW.Dir -> PW.Path PW.Abs PW.Dir
|
||||
pathWinCombineAbsDirAndRelDir lp rp
|
||||
| PW.toFilePath rp == ['.', FPW.pathSeparator] = lp
|
||||
| otherwise = lp PW.</> rp
|
||||
|
||||
-- NOTE: Same as pathWinCombineRelDirAndRelFile but for Posix (Path has the same problem).
|
||||
pathPosixCombineRelDirAndRelFile :: PP.Path PP.Rel PP.Dir -> PP.Path PP.Rel PP.File -> PP.Path PP.Rel PP.File
|
||||
pathPosixCombineRelDirAndRelFile lp rp
|
||||
| PP.toFilePath lp == ['.', FPP.pathSeparator] = rp
|
||||
| otherwise = lp PP.</> rp
|
||||
|
||||
pathPosixCombineRelDirAndRelDir :: PP.Path PP.Rel PP.Dir -> PP.Path PP.Rel PP.Dir -> PP.Path PP.Rel PP.Dir
|
||||
pathPosixCombineRelDirAndRelDir lp rp
|
||||
| PP.toFilePath lp == ['.', FPP.pathSeparator] = rp
|
||||
| PP.toFilePath rp == ['.', FPP.pathSeparator] = lp
|
||||
| otherwise = lp PP.</> rp
|
||||
|
||||
pathPosixCombineAbsDirAndRelDir :: PP.Path PP.Abs PP.Dir -> PP.Path PP.Rel PP.Dir -> PP.Path PP.Abs PP.Dir
|
||||
pathPosixCombineAbsDirAndRelDir lp rp
|
||||
| PP.toFilePath rp == ['.', FPP.pathSeparator] = lp
|
||||
| otherwise = lp PP.</> rp
|
||||
|
||||
prefixNumParentDirs :: RelPathPrefix -> Int
|
||||
prefixNumParentDirs NoPrefix = 0
|
||||
prefixNumParentDirs (ParentDir n) = n
|
||||
|
||||
relPathNumParentDirs :: Path' s (Rel r) t -> Int
|
||||
relPathNumParentDirs = prefixNumParentDirs . relPathPrefix
|
||||
|
||||
relPathPrefix :: Path' s (Rel r) t -> RelPathPrefix
|
||||
relPathPrefix sp = case sp of
|
||||
RelDir _ pr -> pr
|
||||
RelFile _ pr -> pr
|
||||
RelDirW _ pr -> pr
|
||||
RelFileW _ pr -> pr
|
||||
RelDirP _ pr -> pr
|
||||
RelFileP _ pr -> pr
|
||||
_ -> impossible
|
||||
|
||||
impossible :: a
|
||||
impossible = error "This should be impossible."
|
@ -11,6 +11,8 @@ import qualified System.FilePath as FilePath
|
||||
import System.IO.Error (isDoesNotExistError)
|
||||
import UnliftIO.Exception (catch, throwIO)
|
||||
|
||||
-- TODO: Convert these to use StrongPath?
|
||||
|
||||
-- TODO: write tests.
|
||||
|
||||
-- | Lists all files in the directory recursively.
|
||||
|
@ -35,7 +35,7 @@ where
|
||||
|
||||
import Data.Aeson (ToJSON (..), object, (.=))
|
||||
import qualified ExternalCode
|
||||
import StrongPath (Abs, File, Path)
|
||||
import StrongPath (Abs, File', Path')
|
||||
import qualified Util as U
|
||||
import qualified Wasp.Action
|
||||
import Wasp.App
|
||||
@ -55,7 +55,7 @@ data Wasp = Wasp
|
||||
{ waspElements :: [WaspElement],
|
||||
waspJsImports :: [JsImport],
|
||||
externalCodeFiles :: [ExternalCode.File],
|
||||
dotEnvFile :: Maybe (Path Abs File),
|
||||
dotEnvFile :: Maybe (Path' Abs File'),
|
||||
isBuild :: Bool
|
||||
}
|
||||
deriving (Show, Eq)
|
||||
@ -100,10 +100,10 @@ setExternalCodeFiles wasp files = wasp {externalCodeFiles = files}
|
||||
|
||||
-- * Dot env files
|
||||
|
||||
getDotEnvFile :: Wasp -> Maybe (Path Abs File)
|
||||
getDotEnvFile :: Wasp -> Maybe (Path' Abs File')
|
||||
getDotEnvFile = dotEnvFile
|
||||
|
||||
setDotEnvFile :: Wasp -> Maybe (Path Abs File) -> Wasp
|
||||
setDotEnvFile :: Wasp -> Maybe (Path' Abs File') -> Wasp
|
||||
setDotEnvFile wasp file = wasp {dotEnvFile = file}
|
||||
|
||||
-- * Js imports
|
||||
|
@ -5,14 +5,14 @@ where
|
||||
|
||||
import Data.Aeson (ToJSON (..), object, (.=))
|
||||
import ExternalCode (SourceExternalCodeDir)
|
||||
import StrongPath (File, Path', Posix, Rel)
|
||||
import StrongPath (File', Path, Posix, Rel)
|
||||
import qualified StrongPath as SP
|
||||
|
||||
-- | Represents javascript import -> "import <what> from <from>".
|
||||
data JsImport = JsImport
|
||||
{ _defaultImport :: !(Maybe String),
|
||||
_namedImports :: ![String],
|
||||
_from :: Path' Posix (Rel SourceExternalCodeDir) File
|
||||
_from :: Path Posix (Rel SourceExternalCodeDir) File'
|
||||
}
|
||||
deriving (Show, Eq)
|
||||
|
||||
@ -21,5 +21,5 @@ instance ToJSON JsImport where
|
||||
object
|
||||
[ "defaultImport" .= _defaultImport jsImport,
|
||||
"namedImports" .= _namedImports jsImport,
|
||||
"from" .= SP.toFilePath (_from jsImport)
|
||||
"from" .= SP.fromRelFileP (_from jsImport)
|
||||
]
|
||||
|
@ -6,10 +6,10 @@ where
|
||||
import Data.Aeson (ToJSON (..))
|
||||
import Data.Text (Text)
|
||||
import ExternalCode (SourceExternalCodeDir)
|
||||
import StrongPath (File, Path', Posix, Rel, toFilePath)
|
||||
import StrongPath (File', Path, Posix, Rel, toFilePath)
|
||||
|
||||
data Style
|
||||
= ExtCodeCssFile !(Path' Posix (Rel SourceExternalCodeDir) File)
|
||||
= ExtCodeCssFile !(Path Posix (Rel SourceExternalCodeDir) File')
|
||||
| CssCode !Text
|
||||
deriving (Show, Eq)
|
||||
|
||||
|
@ -6,7 +6,8 @@ module WaspignoreFile
|
||||
)
|
||||
where
|
||||
|
||||
import StrongPath (Abs, File, Path, toFilePath)
|
||||
import StrongPath (Abs, File', Path')
|
||||
import qualified StrongPath as SP
|
||||
import System.FilePath.Glob (Pattern, compile, match)
|
||||
import System.IO.Error (isDoesNotExistError)
|
||||
import UnliftIO.Exception (catch, throwIO)
|
||||
@ -51,10 +52,10 @@ parseWaspignoreFile =
|
||||
-- the file format, but it is very similar to `.gitignore`'s format.
|
||||
--
|
||||
-- If the ignore file does not exist, it is interpreted as a blank file.
|
||||
readWaspignoreFile :: Path Abs File -> IO WaspignoreFile
|
||||
readWaspignoreFile :: Path' Abs File' -> IO WaspignoreFile
|
||||
readWaspignoreFile fp = do
|
||||
text <-
|
||||
readFile (toFilePath fp)
|
||||
readFile (SP.fromAbsFile fp)
|
||||
`catch` ( \e ->
|
||||
if isDoesNotExistError e
|
||||
then return ""
|
||||
|
@ -18,7 +18,7 @@
|
||||
#
|
||||
# resolver: ./custom-snapshot.yaml
|
||||
# resolver: https://example.com/snapshots/2018-01-01.yaml
|
||||
resolver: lts-16.14
|
||||
resolver: lts-18.0
|
||||
|
||||
# User packages to be built.
|
||||
# Various formats can be used as shown in the example below.
|
||||
@ -38,7 +38,10 @@ packages:
|
||||
# Dependency packages to be pulled from upstream that are not in the resolver
|
||||
# using the same syntax as the packages field.
|
||||
# (e.g., acme-missiles-0.3)
|
||||
# extra-deps: []
|
||||
extra-deps:
|
||||
- strong-path-1.0.0.0
|
||||
- path-0.9.0
|
||||
- path-io-1.6.3
|
||||
|
||||
# Override default flag values for local packages and extra-deps
|
||||
# flags:
|
||||
|
15
waspc/test/FilePath/ExtraTest.hs
Normal file
15
waspc/test/FilePath/ExtraTest.hs
Normal file
@ -0,0 +1,15 @@
|
||||
module FilePath.ExtraTest where
|
||||
|
||||
import qualified FilePath.Extra as PE
|
||||
import StrongPath (reldirP, toFilePath)
|
||||
import Test.Tasty.Hspec
|
||||
|
||||
spec_reversePosixPath :: Spec
|
||||
spec_reversePosixPath = do
|
||||
[reldirP|.|] ~> "."
|
||||
[reldirP|foo|] ~> ".."
|
||||
[reldirP|foo/bar|] ~> "../.."
|
||||
[reldirP|./foo/bar/./test|] ~> "../../.."
|
||||
where
|
||||
path ~> expectedReversedPath = it (show path ++ " -> " ++ expectedReversedPath) $ do
|
||||
PE.reversePosixPath (toFilePath path) `shouldBe` expectedReversedPath
|
@ -2,6 +2,7 @@ module Fixtures where
|
||||
|
||||
import Data.Maybe (fromJust)
|
||||
import qualified Path as P
|
||||
import qualified StrongPath as SP
|
||||
import qualified System.FilePath as FP
|
||||
import Wasp
|
||||
import qualified Wasp.Route as RouteAST
|
||||
@ -27,6 +28,9 @@ wasp =
|
||||
[ WaspElementApp app
|
||||
]
|
||||
|
||||
systemSPRoot :: SP.Path' SP.Abs (SP.Dir d)
|
||||
systemSPRoot = fromJust $ SP.parseAbsDir systemFpRoot
|
||||
|
||||
systemPathRoot :: P.Path P.Abs P.Dir
|
||||
systemPathRoot = fromJust $ P.parseAbsDir systemFpRoot
|
||||
|
||||
|
@ -2,17 +2,16 @@ module Generator.ExternalCodeGenerator.JsTest where
|
||||
|
||||
import Generator.ExternalCodeGenerator.Common (asGenExtFile)
|
||||
import Generator.ExternalCodeGenerator.Js as Js
|
||||
import qualified Path as P
|
||||
import qualified StrongPath as SP
|
||||
import Test.Tasty.Hspec
|
||||
|
||||
spec_resolveJsFileWaspImportsForExtCodeDir :: Spec
|
||||
spec_resolveJsFileWaspImportsForExtCodeDir = do
|
||||
(asGenExtFile [P.relfile|extFile.js|], "import foo from 'bar'") ~> "import foo from 'bar'"
|
||||
(asGenExtFile [P.relfile|extFile.js|], "import foo from '@wasp/bar'") ~> "import foo from '../bar'"
|
||||
(asGenExtFile [P.relfile|a/extFile.js|], "import foo from \"@wasp/bar/foo\"")
|
||||
(asGenExtFile [SP.relfile|extFile.js|], "import foo from 'bar'") ~> "import foo from 'bar'"
|
||||
(asGenExtFile [SP.relfile|extFile.js|], "import foo from '@wasp/bar'") ~> "import foo from '../bar'"
|
||||
(asGenExtFile [SP.relfile|a/extFile.js|], "import foo from \"@wasp/bar/foo\"")
|
||||
~> "import foo from \"../../bar/foo\""
|
||||
where
|
||||
(path, text) ~> expectedText =
|
||||
it (SP.toFilePath path ++ " " ++ show text ++ " -> " ++ show expectedText) $ do
|
||||
Js.resolveJsFileWaspImportsForExtCodeDir (SP.fromPathRelDir [P.reldir|src|]) path text `shouldBe` expectedText
|
||||
Js.resolveJsFileWaspImportsForExtCodeDir [SP.reldir|src|] path text `shouldBe` expectedText
|
||||
|
@ -1,9 +1,8 @@
|
||||
module Generator.FileDraft.CopyFileDraftTest where
|
||||
|
||||
import Fixtures (systemPathRoot)
|
||||
import Fixtures (systemSPRoot)
|
||||
import Generator.FileDraft
|
||||
import qualified Generator.MockWriteableMonad as Mock
|
||||
import qualified Path as P
|
||||
import qualified StrongPath as SP
|
||||
import Test.Tasty.Hspec
|
||||
|
||||
@ -19,9 +18,9 @@ spec_CopyFileDraft = do
|
||||
`shouldBe` [(SP.toFilePath expectedSrcPath, SP.toFilePath expectedDstPath)]
|
||||
where
|
||||
(dstDir, dstPath, srcPath) =
|
||||
( SP.fromPathAbsDir $ systemPathRoot P.</> [P.reldir|a/b|],
|
||||
SP.fromPathRelFile [P.relfile|c/d/dst.txt|],
|
||||
SP.fromPathAbsFile $ systemPathRoot P.</> [P.relfile|e/src.txt|]
|
||||
( systemSPRoot SP.</> [SP.reldir|a/b|],
|
||||
[SP.relfile|c/d/dst.txt|],
|
||||
systemSPRoot SP.</> [SP.relfile|e/src.txt|]
|
||||
)
|
||||
fileDraft = createCopyFileDraft dstPath srcPath
|
||||
expectedSrcPath = srcPath
|
||||
|
@ -2,10 +2,9 @@ module Generator.FileDraft.TemplateFileDraftTest where
|
||||
|
||||
import Data.Aeson (object, (.=))
|
||||
import Data.Text (Text)
|
||||
import Fixtures (systemPathRoot)
|
||||
import Fixtures (systemSPRoot)
|
||||
import Generator.FileDraft
|
||||
import qualified Generator.MockWriteableMonad as Mock
|
||||
import qualified Path as P
|
||||
import qualified StrongPath as SP
|
||||
import Test.Tasty.Hspec
|
||||
|
||||
@ -23,14 +22,14 @@ spec_TemplateFileDraft = do
|
||||
`shouldBe` [(SP.toFilePath expectedDstPath, mockTemplateContent)]
|
||||
where
|
||||
(dstDir, dstPath, templatePath) =
|
||||
( SP.fromPathAbsDir $ systemPathRoot P.</> [P.reldir|a/b|],
|
||||
SP.fromPathRelFile [P.relfile|c/d/dst.txt|],
|
||||
SP.fromPathRelFile [P.relfile|e/tmpl.txt|]
|
||||
( systemSPRoot SP.</> [SP.reldir|a/b|],
|
||||
[SP.relfile|c/d/dst.txt|],
|
||||
[SP.relfile|e/tmpl.txt|]
|
||||
)
|
||||
templateData = object ["foo" .= ("bar" :: String)]
|
||||
fileDraft = createTemplateFileDraft dstPath templatePath (Just templateData)
|
||||
expectedDstPath = dstDir SP.</> dstPath
|
||||
mockTemplatesDirAbsPath = SP.fromPathAbsDir $ systemPathRoot P.</> [P.reldir|mock/templates/dir|]
|
||||
mockTemplatesDirAbsPath = systemSPRoot SP.</> [SP.reldir|mock/templates/dir|]
|
||||
mockTemplateContent = "Mock template content" :: Text
|
||||
mockConfig =
|
||||
Mock.defaultMockConfig
|
||||
|
@ -13,12 +13,10 @@ where
|
||||
import Control.Monad.State
|
||||
import qualified Data.Aeson as Aeson
|
||||
import Data.Text (Text, pack)
|
||||
import Fixtures (systemPathRoot)
|
||||
import Fixtures (systemSPRoot)
|
||||
import Generator.FileDraft.WriteableMonad
|
||||
import Generator.Templates (TemplatesDir)
|
||||
import qualified Path as P
|
||||
import StrongPath (Abs, Dir, File, Path, Rel)
|
||||
import qualified StrongPath as SP
|
||||
import StrongPath (Abs, Dir, File', Path', Rel, reldir, (</>))
|
||||
|
||||
-- TODO: Instead of manually defining mock like this, consider using monad-mock package,
|
||||
-- it should do most of this automatically, now there is a lot of boilerplate.
|
||||
@ -27,8 +25,8 @@ import qualified StrongPath as SP
|
||||
defaultMockConfig :: MockWriteableMonadConfig
|
||||
defaultMockConfig =
|
||||
MockWriteableMonadConfig
|
||||
{ getTemplatesDirAbsPath_impl = SP.fromPathAbsDir $ systemPathRoot P.</> [P.reldir|mock/templates/dir|],
|
||||
getTemplateFileAbsPath_impl = \path -> SP.fromPathAbsDir (systemPathRoot P.</> [P.reldir|mock/templates/dir|]) SP.</> path,
|
||||
{ getTemplatesDirAbsPath_impl = systemSPRoot </> [reldir|mock/templates/dir|],
|
||||
getTemplateFileAbsPath_impl = \path -> systemSPRoot </> [reldir|mock/templates/dir|] </> path,
|
||||
compileAndRenderTemplate_impl = \_ _ -> pack "Mock template content",
|
||||
doesFileExist_impl = const True
|
||||
}
|
||||
@ -85,14 +83,14 @@ data MockWriteableMonadLogs = MockWriteableMonadLogs
|
||||
getTemplatesDirAbsPath_calls :: [()],
|
||||
createDirectoryIfMissing_calls :: [(Bool, FilePath)],
|
||||
copyFile_calls :: [(FilePath, FilePath)],
|
||||
getTemplateFileAbsPath_calls :: [(Path (Rel TemplatesDir) File)],
|
||||
compileAndRenderTemplate_calls :: [(Path (Rel TemplatesDir) File, Aeson.Value)]
|
||||
getTemplateFileAbsPath_calls :: [(Path' (Rel TemplatesDir) File')],
|
||||
compileAndRenderTemplate_calls :: [(Path' (Rel TemplatesDir) File', Aeson.Value)]
|
||||
}
|
||||
|
||||
data MockWriteableMonadConfig = MockWriteableMonadConfig
|
||||
{ getTemplatesDirAbsPath_impl :: Path Abs (Dir TemplatesDir),
|
||||
getTemplateFileAbsPath_impl :: Path (Rel TemplatesDir) File -> Path Abs File,
|
||||
compileAndRenderTemplate_impl :: Path (Rel TemplatesDir) File -> Aeson.Value -> Text,
|
||||
{ getTemplatesDirAbsPath_impl :: Path' Abs (Dir TemplatesDir),
|
||||
getTemplateFileAbsPath_impl :: Path' (Rel TemplatesDir) File' -> Path' Abs File',
|
||||
compileAndRenderTemplate_impl :: Path' (Rel TemplatesDir) File' -> Aeson.Value -> Text,
|
||||
doesFileExist_impl :: FilePath -> Bool
|
||||
}
|
||||
|
||||
@ -104,7 +102,7 @@ getTemplatesDirAbsPath_addCall :: MockWriteableMonadLogs -> MockWriteableMonadLo
|
||||
getTemplatesDirAbsPath_addCall logs =
|
||||
logs {getTemplatesDirAbsPath_calls = () : (getTemplatesDirAbsPath_calls logs)}
|
||||
|
||||
getTemplateFileAbsPath_addCall :: Path (Rel TemplatesDir) File -> MockWriteableMonadLogs -> MockWriteableMonadLogs
|
||||
getTemplateFileAbsPath_addCall :: Path' (Rel TemplatesDir) File' -> MockWriteableMonadLogs -> MockWriteableMonadLogs
|
||||
getTemplateFileAbsPath_addCall path logs =
|
||||
logs {getTemplateFileAbsPath_calls = (path) : (getTemplateFileAbsPath_calls logs)}
|
||||
|
||||
@ -120,7 +118,7 @@ createDirectoryIfMissing_addCall createParents path logs =
|
||||
}
|
||||
|
||||
compileAndRenderTemplate_addCall ::
|
||||
Path (Rel TemplatesDir) File ->
|
||||
Path' (Rel TemplatesDir) File' ->
|
||||
Aeson.Value ->
|
||||
MockWriteableMonadLogs ->
|
||||
MockWriteableMonadLogs
|
||||
|
@ -1,14 +1,13 @@
|
||||
module Generator.WebAppGeneratorTest where
|
||||
|
||||
import qualified CompileOptions
|
||||
import Fixtures (systemPathRoot)
|
||||
import Fixtures (systemSPRoot)
|
||||
import Generator.FileDraft
|
||||
import qualified Generator.FileDraft.CopyFileDraft as CopyFD
|
||||
import qualified Generator.FileDraft.TemplateFileDraft as TmplFD
|
||||
import qualified Generator.FileDraft.TextFileDraft as TextFD
|
||||
import Generator.WebAppGenerator
|
||||
import qualified Generator.WebAppGenerator.Common as Common
|
||||
import qualified Path as P
|
||||
import qualified StrongPath as SP
|
||||
import System.FilePath ((</>))
|
||||
import Test.Tasty.Hspec
|
||||
@ -23,7 +22,7 @@ spec_WebAppGenerator = do
|
||||
let testWasp = (fromApp testApp)
|
||||
let testCompileOptions =
|
||||
CompileOptions.CompileOptions
|
||||
{ CompileOptions.externalCodeDirPath = SP.fromPathAbsDir $ systemPathRoot P.</> [P.reldir|test/src|],
|
||||
{ CompileOptions.externalCodeDirPath = systemSPRoot SP.</> [SP.reldir|test/src|],
|
||||
CompileOptions.isBuild = False
|
||||
}
|
||||
|
||||
|
@ -4,7 +4,6 @@ import Data.Either (isLeft)
|
||||
import Data.Char (toLower)
|
||||
import Parser.Action (action)
|
||||
import Parser.Common (runWaspParser)
|
||||
import qualified Path.Posix as PPosix
|
||||
import qualified StrongPath as SP
|
||||
import Test.Tasty.Hspec
|
||||
import qualified Wasp.Action
|
||||
@ -19,7 +18,6 @@ spec_parseAction :: Spec
|
||||
spec_parseAction =
|
||||
describe "Parsing action declaration" $ do
|
||||
let parseAction = runWaspParser action
|
||||
|
||||
it "When given a valid action declaration, returns correct AST (no auth)" $ do
|
||||
let testAction = genActionAST Nothing
|
||||
let testActionInput = genActionInput Nothing
|
||||
@ -59,6 +57,6 @@ spec_parseAction =
|
||||
authStr :: Maybe Bool -> String
|
||||
authStr (Just useAuth) = ",\n auth: " ++ map toLower (show useAuth) ++ "\n"
|
||||
authStr _ = "\n"
|
||||
testActionJsFunctionFrom = SP.fromPathRelFileP [PPosix.relfile|some/path|]
|
||||
testActionJsFunctionFrom = [SP.relfileP|some/path|]
|
||||
testActionJsFunctionName = "myJsAction"
|
||||
testActionName = "myAction"
|
||||
|
@ -4,7 +4,7 @@ import Data.Either
|
||||
import Lexer
|
||||
import qualified Lexer as L
|
||||
import Parser.Common
|
||||
import Path (relfile)
|
||||
import qualified StrongPath as SP
|
||||
import Test.Tasty.Hspec
|
||||
import Text.Parsec
|
||||
|
||||
@ -99,7 +99,7 @@ spec_parseWaspCommon = do
|
||||
describe "Parsing relative file path string" $ do
|
||||
it "Correctly parses relative path in double quotes" $ do
|
||||
runWaspParser relFilePathString "\"foo/bar.txt\""
|
||||
`shouldBe` Right [relfile|foo/bar.txt|]
|
||||
`shouldBe` Right [SP.relfile|foo/bar.txt|]
|
||||
|
||||
-- TODO: It is not passing on Windows, due to Path differently parsing paths on Windows.
|
||||
-- Check out Path.Posix vs Path.Windows.
|
||||
|
@ -3,7 +3,6 @@ module Parser.ExternalCodeTest where
|
||||
import Data.Either (isLeft)
|
||||
import Parser.Common (runWaspParser)
|
||||
import Parser.ExternalCode (extCodeFilePathString)
|
||||
import qualified Path.Posix as PPosix
|
||||
import qualified StrongPath as SP
|
||||
import Test.Tasty.Hspec
|
||||
|
||||
@ -12,7 +11,7 @@ spec_ParserExternalCode = do
|
||||
describe "Parsing external code file path string" $ do
|
||||
it "Correctly parses external code path in double quotes" $ do
|
||||
runWaspParser extCodeFilePathString "\"@ext/foo/bar.txt\""
|
||||
`shouldBe` Right (SP.fromPathRelFileP [PPosix.relfile|foo/bar.txt|])
|
||||
`shouldBe` Right [SP.relfileP|foo/bar.txt|]
|
||||
|
||||
it "When path does not start with @ext/, returns Left" $ do
|
||||
isLeft (runWaspParser extCodeFilePathString "\"@ext2/foo/bar.txt\"") `shouldBe` True
|
||||
|
@ -3,14 +3,13 @@ module Parser.JsImportTest where
|
||||
import Data.Either (isLeft)
|
||||
import Parser.Common (runWaspParser)
|
||||
import Parser.JsImport (jsImport)
|
||||
import Path.Posix (relfile)
|
||||
import qualified StrongPath as SP
|
||||
import Test.Tasty.Hspec
|
||||
import qualified Wasp
|
||||
|
||||
spec_parseJsImport :: Spec
|
||||
spec_parseJsImport = do
|
||||
let someFilePath = SP.fromPathRelFileP [relfile|some/file.js|]
|
||||
let someFilePath = [SP.relfileP|some/file.js|]
|
||||
|
||||
it "Parses external code js import with default import correctly" $ do
|
||||
runWaspParser jsImport "import something from \"@ext/some/file.js\""
|
||||
|
@ -3,7 +3,6 @@ module Parser.OperationTest where
|
||||
import Data.List (intercalate)
|
||||
import Parser.Common (runWaspParser)
|
||||
import Parser.Operation
|
||||
import qualified Path.Posix as PPosix
|
||||
import qualified StrongPath as SP
|
||||
import Test.Tasty.Hspec
|
||||
import qualified Wasp.JsImport
|
||||
@ -15,7 +14,7 @@ spec_parseOperation =
|
||||
|
||||
it "When given a valid list of properties, correctly parses them" $ do
|
||||
let testJsFnName = "myJsFn"
|
||||
testJsFnFrom = SP.fromPathRelFileP [PPosix.relfile|some/path|]
|
||||
testJsFnFrom = [SP.relfileP|some/path|]
|
||||
let testProps =
|
||||
[ JsFunction $
|
||||
Wasp.JsImport.JsImport
|
||||
|
@ -3,7 +3,6 @@ module Parser.PageTest where
|
||||
import Data.Either (isLeft)
|
||||
import Parser.Common (runWaspParser)
|
||||
import Parser.Page (page)
|
||||
import qualified Path.Posix as PPosix
|
||||
import qualified StrongPath as SP
|
||||
import Test.Tasty.Hspec
|
||||
import qualified Wasp.JsImport
|
||||
@ -18,7 +17,7 @@ spec_parsePage =
|
||||
Wasp.JsImport.JsImport
|
||||
{ Wasp.JsImport._defaultImport = Just "Main",
|
||||
Wasp.JsImport._namedImports = [],
|
||||
Wasp.JsImport._from = (SP.fromPathRelFileP [PPosix.relfile|pages/Main|])
|
||||
Wasp.JsImport._from = [SP.relfileP|pages/Main|]
|
||||
}
|
||||
|
||||
it "When given a valid page declaration, returns correct AST" $ do
|
||||
|
@ -4,7 +4,6 @@ import Data.Either
|
||||
import NpmDependency as ND
|
||||
import Parser
|
||||
import Parser.Common (runWaspParser)
|
||||
import qualified Path.Posix as PPosix
|
||||
import qualified Psl.Parser.Model
|
||||
import qualified StrongPath as SP
|
||||
import Test.Tasty.Hspec
|
||||
@ -53,7 +52,7 @@ spec_parseWasp =
|
||||
Wasp.JsImport.JsImport
|
||||
{ Wasp.JsImport._defaultImport = Just "Landing",
|
||||
Wasp.JsImport._namedImports = [],
|
||||
Wasp.JsImport._from = SP.fromPathRelFileP [PPosix.relfile|pages/Landing|]
|
||||
Wasp.JsImport._from = [SP.relfileP|pages/Landing|]
|
||||
},
|
||||
Wasp.Page._authRequired = Just False
|
||||
},
|
||||
@ -69,7 +68,7 @@ spec_parseWasp =
|
||||
Wasp.JsImport.JsImport
|
||||
{ Wasp.JsImport._defaultImport = Just "Test",
|
||||
Wasp.JsImport._namedImports = [],
|
||||
Wasp.JsImport._from = SP.fromPathRelFileP [PPosix.relfile|pages/Test|]
|
||||
Wasp.JsImport._from = [SP.relfileP|pages/Test|]
|
||||
},
|
||||
Wasp.Page._authRequired = Nothing
|
||||
},
|
||||
@ -106,7 +105,7 @@ spec_parseWasp =
|
||||
Wasp.JsImport.JsImport
|
||||
{ Wasp.JsImport._defaultImport = Nothing,
|
||||
Wasp.JsImport._namedImports = ["myJsQuery"],
|
||||
Wasp.JsImport._from = SP.fromPathRelFileP [PPosix.relfile|some/path|]
|
||||
Wasp.JsImport._from = [SP.relfileP|some/path|]
|
||||
},
|
||||
Wasp.Query._entities = Nothing,
|
||||
Wasp.Query._auth = Nothing
|
||||
@ -121,5 +120,5 @@ spec_parseWasp =
|
||||
]
|
||||
}
|
||||
]
|
||||
`setJsImports` [JsImport (Just "something") [] (SP.fromPathRelFileP [PPosix.relfile|some/file|])]
|
||||
`setJsImports` [JsImport (Just "something") [] [SP.relfileP|some/file|]]
|
||||
)
|
||||
|
@ -3,7 +3,6 @@ module Parser.QueryTest where
|
||||
import Data.Either (isLeft)
|
||||
import Parser.Common (runWaspParser)
|
||||
import Parser.Query (query)
|
||||
import qualified Path.Posix as PPosix
|
||||
import qualified StrongPath as SP
|
||||
import Test.Tasty.Hspec
|
||||
import qualified Wasp.JsImport
|
||||
@ -14,7 +13,6 @@ spec_parseQuery :: Spec
|
||||
spec_parseQuery =
|
||||
describe "Parsing query declaration" $ do
|
||||
let parseQuery = runWaspParser query
|
||||
|
||||
it "When given a valid query declaration, returns correct AST(without auth)" $ do
|
||||
let testQuery = genQueryAST Nothing
|
||||
let testQueryInput = genQueryInput Nothing
|
||||
@ -57,5 +55,5 @@ spec_parseQuery =
|
||||
}
|
||||
testQueryName = "myQuery"
|
||||
testQueryJsFunctionName = "myJsQuery"
|
||||
testQueryJsFunctionFrom = SP.fromPathRelFileP [PPosix.relfile|some/path|]
|
||||
testQueryJsFunctionFrom = [SP.relfileP|some/path|]
|
||||
|
||||
|
@ -3,7 +3,6 @@ module Parser.StyleTest where
|
||||
import Data.Either (isLeft)
|
||||
import Parser.Common (runWaspParser)
|
||||
import Parser.Style (style)
|
||||
import qualified Path.Posix as PPosix
|
||||
import qualified StrongPath as SP
|
||||
import Test.Tasty.Hspec
|
||||
import qualified Wasp.Style
|
||||
@ -12,7 +11,7 @@ spec_parseStyle :: Spec
|
||||
spec_parseStyle = do
|
||||
it "Parses external code file path correctly" $ do
|
||||
runWaspParser style "\"@ext/some/file.css\""
|
||||
`shouldBe` Right (Wasp.Style.ExtCodeCssFile (SP.fromPathRelFileP [PPosix.relfile|some/file.css|]))
|
||||
`shouldBe` Right (Wasp.Style.ExtCodeCssFile [SP.relfileP|some/file.css|])
|
||||
|
||||
it "Parses css closure correctly" $ do
|
||||
runWaspParser style "{=css Some css code css=}"
|
||||
|
@ -1,15 +0,0 @@
|
||||
module Path.ExtraTest where
|
||||
|
||||
import Path (reldir)
|
||||
import qualified Path.Extra as PE
|
||||
import Test.Tasty.Hspec
|
||||
|
||||
spec_reversePosixPath :: Spec
|
||||
spec_reversePosixPath = do
|
||||
[reldir|.|] ~> "."
|
||||
[reldir|foo|] ~> ".."
|
||||
[reldir|foo/bar|] ~> "../.."
|
||||
[reldir|./foo/bar/./test|] ~> "../../.."
|
||||
where
|
||||
path ~> expectedReversedPath = it ((show path) ++ " -> " ++ expectedReversedPath) $ do
|
||||
PE.reversePosixPath (PE.toPosixFilePath path) `shouldBe` expectedReversedPath
|
@ -1,292 +0,0 @@
|
||||
module StrongPathTest where
|
||||
|
||||
import Data.Maybe (fromJust)
|
||||
import Fixtures (systemFpRoot, systemPathRoot)
|
||||
import qualified Path as P
|
||||
import qualified Path.Posix as PP
|
||||
import qualified Path.Windows as PW
|
||||
import StrongPath
|
||||
import StrongPath.Internal
|
||||
( RelPathPrefix (..),
|
||||
extractRelPathPrefix,
|
||||
relPathNumParentDirs,
|
||||
)
|
||||
import qualified System.FilePath as FP
|
||||
import qualified System.FilePath.Posix as FPP
|
||||
import qualified System.FilePath.Windows as FPW
|
||||
import Test.Tasty.Hspec
|
||||
import Test.Util (posixToSystemFp, posixToWindowsFp)
|
||||
|
||||
data Bar
|
||||
|
||||
data Fizz
|
||||
|
||||
-- TODO: I should look into using QuickCheck to simplify / enhcance StrongPath tests,
|
||||
-- it would probably be a good fit for some cases.
|
||||
|
||||
spec_StrongPath :: Spec
|
||||
spec_StrongPath = do
|
||||
describe "Example with Foo file and Bar, Fizz and Kokolo dirs" $ do
|
||||
let fooFileInBarDir = fromPathRelFile [P.relfile|foo.txt|] :: Path (Rel Bar) File
|
||||
let barDirInFizzDir = fromPathRelDir [P.reldir|kokolo/bar|] :: Path (Rel Fizz) (Dir Bar)
|
||||
let fizzDir = (fromPathAbsDir $ systemPathRoot P.</> [P.reldir|fizz|]) :: Path Abs (Dir Fizz)
|
||||
let fooFile = (fizzDir </> barDirInFizzDir </> fooFileInBarDir) :: Path Abs File
|
||||
let fooFileInFizzDir = (barDirInFizzDir </> fooFileInBarDir) :: Path (Rel Fizz) File
|
||||
|
||||
it "Paths are correctly concatenated" $ do
|
||||
P.toFilePath (toPathAbsFile fooFile) `shouldBe` posixToSystemFp "/fizz/kokolo/bar/foo.txt"
|
||||
P.toFilePath (toPathRelFile fooFileInFizzDir) `shouldBe` posixToSystemFp "kokolo/bar/foo.txt"
|
||||
|
||||
it "Paths are unchanged when packed from Path.Path and unpacked to Path.Path" $ do
|
||||
let test pack unpack path = unpack (pack path) == path `shouldBe` True
|
||||
test fromPathRelFile toPathRelFile [P.relfile|some/file.txt|]
|
||||
test fromPathRelDir toPathRelDir [P.reldir|some/dir/|]
|
||||
test fromPathAbsFile toPathAbsFile $ systemPathRoot P.</> [P.relfile|some/file.txt|]
|
||||
test fromPathAbsDir toPathAbsDir $ systemPathRoot P.</> [P.reldir|some/file.txt|]
|
||||
|
||||
describe "relDirToPosix/relFileToPosix correctly converts relative strong path to Posix" $ do
|
||||
describe "when strong path is relative dir" $ do
|
||||
let expectedPosixPath = fromPathRelDirP [PP.reldir|test/dir/|]
|
||||
it "from standard Win" $
|
||||
fromJust (relDirToPosix $ fromPathRelDirW [PW.reldir|test\dir\|])
|
||||
`shouldBe` expectedPosixPath
|
||||
it "from standard Posix" $
|
||||
fromJust (relDirToPosix $ fromPathRelDirP [PP.reldir|test/dir/|])
|
||||
`shouldBe` expectedPosixPath
|
||||
it "from standard System" $
|
||||
fromJust (relDirToPosix $ fromPathRelDir [P.reldir|test/dir/|])
|
||||
`shouldBe` expectedPosixPath
|
||||
describe "correctly when strong path is relative file" $ do
|
||||
let expectedPosixPath = fromPathRelFileP [PP.relfile|test/file|]
|
||||
it "from standard Win" $
|
||||
fromJust (relFileToPosix $ fromPathRelFileW [PW.relfile|test\file|])
|
||||
`shouldBe` expectedPosixPath
|
||||
it "from standard Posix" $
|
||||
fromJust (relFileToPosix $ fromPathRelFileP [PP.relfile|test/file|])
|
||||
`shouldBe` expectedPosixPath
|
||||
it "from standard System" $
|
||||
fromJust (relFileToPosix $ fromPathRelFile [P.relfile|test/file|])
|
||||
`shouldBe` expectedPosixPath
|
||||
|
||||
describe "extractRelPathPrefix correctly extracts prefix from rel FilePath." $ do
|
||||
it "when path starts with multiple ../" $ do
|
||||
extractRelPathPrefix [FPP.pathSeparator] "../../" `shouldBe` (ParentDir 2, "")
|
||||
extractRelPathPrefix [FPP.pathSeparator] "../.." `shouldBe` (ParentDir 2, "")
|
||||
extractRelPathPrefix [FP.pathSeparator] ".." `shouldBe` (ParentDir 1, "")
|
||||
extractRelPathPrefix [FP.pathSeparator, FPP.pathSeparator] "../../../a/b" `shouldBe` (ParentDir 3, "a/b")
|
||||
extractRelPathPrefix [FPW.pathSeparator] "..\\a\\b" `shouldBe` (ParentDir 1, "a\\b")
|
||||
it "when path does not start with ../" $ do
|
||||
extractRelPathPrefix [FPP.pathSeparator] "a/b" `shouldBe` (NoPrefix, "a/b")
|
||||
extractRelPathPrefix [FP.pathSeparator] "b" `shouldBe` (NoPrefix, "b")
|
||||
extractRelPathPrefix [FP.pathSeparator] "." `shouldBe` (NoPrefix, ".")
|
||||
|
||||
describe "Parsing from FilePath" $ do
|
||||
let runTest fpToParseIntoExpectedFp parser fpToParse =
|
||||
let expectedFp = fpToParseIntoExpectedFp fpToParse
|
||||
in it (fpToParse ++ " should parse into " ++ expectedFp) $ do
|
||||
let sp = fromJust $ parser fpToParse
|
||||
toFilePath sp `shouldBe` expectedFp
|
||||
let runTestRel fpToParseIntoExpectedFp parser fpToParse expectedNumParentDirs =
|
||||
let expectedFp = fpToParseIntoExpectedFp fpToParse
|
||||
in it (fpToParse ++ " should parse into " ++ expectedFp) $ do
|
||||
let sp = fromJust $ parser fpToParse
|
||||
toFilePath sp `shouldBe` expectedFp
|
||||
relPathNumParentDirs sp `shouldBe` expectedNumParentDirs
|
||||
|
||||
describe "into standard System" $ do
|
||||
describe "into base Rel" $ do
|
||||
describe "captures one or multiple ../ at start of relative path" $ do
|
||||
let test = runTestRel id
|
||||
test parseRelDir (posixToSystemFp "../../a/b/") 2
|
||||
test parseRelDir (posixToSystemFp "../") 1
|
||||
test parseRelDir (posixToSystemFp "../../") 2
|
||||
test parseRelDir (posixToSystemFp "./") 0
|
||||
test parseRelFile (posixToSystemFp "../a/b.txt") 1
|
||||
describe "can parse from system FilePath" $ do
|
||||
let test = runTestRel id
|
||||
test parseRelDir (posixToSystemFp "../a/b/") 1
|
||||
test parseRelDir (posixToSystemFp "a/b/") 0
|
||||
test parseRelFile (posixToSystemFp "../a/b.txt") 1
|
||||
test parseRelFile (posixToSystemFp "a/b.txt") 0
|
||||
describe "can parse from posix FilePath" $ do
|
||||
let test = runTestRel posixToSystemFp
|
||||
test parseRelDir "../a/b/" 1
|
||||
test parseRelDir "a/b/" 0
|
||||
test parseRelFile "../a/b.txt" 1
|
||||
test parseRelFile "a/b.txt" 0
|
||||
describe "into base Abs" $ do
|
||||
describe "can parse from system FilePath" $ do
|
||||
let test = runTest id
|
||||
test parseAbsDir (systemFpRoot FP.</> posixToSystemFp "a/b/")
|
||||
test parseAbsFile (systemFpRoot FP.</> posixToSystemFp "a/b.txt")
|
||||
describe "can parse from FilePath with system root and posix separators" $ do
|
||||
let test = runTest posixToSystemFp
|
||||
test parseAbsDir (systemFpRoot FP.</> "a/b/")
|
||||
test parseAbsFile (systemFpRoot FP.</> "a/b.txt")
|
||||
|
||||
describe "into standard Windows" $ do
|
||||
describe "into base Rel" $ do
|
||||
describe "captures one or multiple ../ at start of relative path" $ do
|
||||
let test = runTestRel posixToWindowsFp
|
||||
test parseRelDirW (posixToSystemFp "../../a/b/") 2
|
||||
test parseRelFileW (posixToSystemFp "../a/b.txt") 1
|
||||
describe "can parse from windows FilePath" $ do
|
||||
let test = runTestRel id
|
||||
test parseRelDirW "..\\a\\b\\" 1
|
||||
test parseRelDirW "a\\b\\" 0
|
||||
test parseRelFileW "..\\a\\b.txt" 1
|
||||
test parseRelFileW "..\\..\\a\\b.txt" 2
|
||||
test parseRelFileW "a\\b.txt" 0
|
||||
describe "can parse from posix FilePath" $ do
|
||||
let test = runTestRel posixToWindowsFp
|
||||
test parseRelDirW "../a/b/" 1
|
||||
test parseRelDirW "a/b/" 0
|
||||
test parseRelFileW "../a/b.txt" 1
|
||||
test parseRelFileW "a/b.txt" 0
|
||||
describe "into base Abs" $ do
|
||||
describe "can parse from windows FilePath" $ do
|
||||
let test = runTest id
|
||||
test parseAbsDirW "C:\\a\\b\\"
|
||||
test parseAbsFileW "C:\\a\\b.txt"
|
||||
describe "can parse from FilePath with windows root and Posix separators" $ do
|
||||
let test = runTest posixToWindowsFp
|
||||
test parseAbsDirW "C:\\a/b/"
|
||||
test parseAbsFileW "C:\\a/b.txt"
|
||||
|
||||
describe "into standard Posix" $ do
|
||||
describe "into base Rel" $ do
|
||||
describe "captures one or multiple ../ at start of relative path" $ do
|
||||
let test = runTestRel id
|
||||
test parseRelDirP "../../a/b/" 2
|
||||
test parseRelFileP "../a/b.txt" 1
|
||||
describe "can parse from posix FilePath" $ do
|
||||
let test = runTestRel id
|
||||
test parseRelDirP "../a/b/" 1
|
||||
test parseRelDirP "a/b/" 0
|
||||
test parseRelFileP "a/b.txt" 0
|
||||
describe "into base Abs" $ do
|
||||
describe "can parse from posix FilePath" $ do
|
||||
let test = runTest id
|
||||
test parseAbsDirP "/a/b/"
|
||||
test parseAbsFileP "/a/b.txt"
|
||||
|
||||
describe "toFilePath correctly transforms strong path into FilePath" $ do
|
||||
let test msp efp =
|
||||
it ("toFilePath (" ++ show msp ++ ") = " ++ efp) $
|
||||
toFilePath (fromJust msp) `shouldBe` efp
|
||||
test (parseRelDir $ posixToSystemFp "../") (posixToSystemFp "../")
|
||||
test (parseRelDir $ posixToSystemFp "a/b") (posixToSystemFp "a/b/")
|
||||
test (parseRelFile $ posixToSystemFp "../../foo.txt") (posixToSystemFp "../../foo.txt")
|
||||
test (parseRelDirW "../") "..\\"
|
||||
test (parseRelDirP "../") "../"
|
||||
-- TODO: Add more tests.
|
||||
|
||||
describe "`parent` correctly returns parent dir" $ do
|
||||
let test msp mexpectedSp =
|
||||
it ("parent (" ++ show msp ++ ") == " ++ show mexpectedSp) $ do
|
||||
let sp = fromJust msp
|
||||
let expectedSp = fromJust mexpectedSp
|
||||
parent sp `shouldBe` expectedSp
|
||||
let tests relDirParser relFileParser absDirParser absFileParser root = do
|
||||
test (relDirParser "a/b") (relDirParser "a")
|
||||
test (relDirParser "../a") (relDirParser "..")
|
||||
test (relDirParser "..") (relDirParser "../..")
|
||||
test (relDirParser ".") (relDirParser "..")
|
||||
test (relFileParser "a.txt") (relDirParser ".")
|
||||
test (relFileParser "../a.txt") (relDirParser "..")
|
||||
test (relFileParser "a/b.txt") (relDirParser "a")
|
||||
test (absDirParser $ root ++ "a/b") (absDirParser $ root ++ "a")
|
||||
test (absDirParser root) (absDirParser root)
|
||||
test (absFileParser $ root ++ "a/b.txt") (absDirParser $ root ++ "a")
|
||||
describe "when standard is System" $
|
||||
tests parseRelDir parseRelFile parseAbsDir parseAbsFile systemFpRoot
|
||||
describe "when standard is Windows" $
|
||||
tests parseRelDirW parseRelFileW parseAbsDirW parseAbsFileW "C:\\"
|
||||
describe "when standard is Posix" $
|
||||
tests parseRelDirP parseRelFileP parseAbsDirP parseAbsFileP "/"
|
||||
|
||||
describe "</> correctly concatenates two corresponding paths" $ do
|
||||
let test mlsp mrsp mexpectedSp =
|
||||
it (show mlsp ++ " </> " ++ show mrsp ++ " == " ++ show mexpectedSp) $ do
|
||||
let lsp = fromJust mlsp
|
||||
let rsp = fromJust mrsp
|
||||
let expectedSp = fromJust mexpectedSp
|
||||
(lsp </> rsp) `shouldBe` expectedSp
|
||||
let tests relDirParser relFileParser absDirParser absFileParser root = do
|
||||
test (relDirParser "a/b") (relFileParser "c.txt") (relFileParser "a/b/c.txt")
|
||||
test (relDirParser "a/b") (relFileParser "../c.txt") (relFileParser "a/c.txt")
|
||||
test (relDirParser "..") (relFileParser "../c.txt") (relFileParser "../../c.txt")
|
||||
test (relDirParser "..") (relDirParser "..") (relDirParser "../..")
|
||||
test (relDirParser ".") (relDirParser "../a") (relDirParser "../a")
|
||||
test (relDirParser ".") (relDirParser ".") (relDirParser ".")
|
||||
test (relDirParser "a/b") (relDirParser "c/d") (relDirParser "a/b/c/d")
|
||||
test (relDirParser "../a/b") (relDirParser "c/d") (relDirParser "../a/b/c/d")
|
||||
test (absDirParser $ root ++ "a/b") (relFileParser "c.txt") (absFileParser $ root ++ "a/b/c.txt")
|
||||
test (absDirParser $ root ++ "a/b") (relFileParser "../c.txt") (absFileParser $ root ++ "a/c.txt")
|
||||
test (absDirParser $ root ++ "a") (relDirParser "../b") (absDirParser $ root ++ "b")
|
||||
test (absDirParser $ root ++ "a/b") (relDirParser "../../../") (absDirParser root)
|
||||
describe "when standard is System" $
|
||||
tests parseRelDir parseRelFile parseAbsDir parseAbsFile systemFpRoot
|
||||
describe "when standard is Windows" $
|
||||
tests parseRelDirW parseRelFileW parseAbsDirW parseAbsFileW "C:\\"
|
||||
describe "when standard is Posix" $
|
||||
tests parseRelDirP parseRelFileP parseAbsDirP parseAbsFileP "/"
|
||||
|
||||
spec_Path :: Spec
|
||||
spec_Path = do
|
||||
-- Just checking that Path behaves in a way that we expect it to behave.
|
||||
it "Path.Windows.parseRelDir correctly parses Windows path" $ do
|
||||
fromJust (PW.parseRelDir ".\\") `shouldBe` fromJust (PW.parseRelDir "./")
|
||||
fromJust (PW.parseRelDir "a\\\\b\\") `shouldBe` fromJust (PW.parseRelDir "a/b/")
|
||||
fromJust (PW.parseRelDir "a\\b") `shouldBe` fromJust (PW.parseRelDir "a/b")
|
||||
PW.toFilePath (fromJust $ PW.parseRelDir "a\\b\\") `shouldBe` "a\\b\\"
|
||||
|
||||
describe "Concatenation of System . paths works as expected" $ do
|
||||
let test lp rp ep =
|
||||
it (show lp ++ " </> " ++ show rp ++ " == " ++ show ep) $
|
||||
(lp P.</> rp) `shouldBe` ep
|
||||
test [P.reldir|.|] [P.reldir|.|] [P.reldir|.|]
|
||||
test [P.reldir|a|] [P.reldir|.|] [P.reldir|a|]
|
||||
test [P.reldir|.|] [P.reldir|a|] [P.reldir|a|]
|
||||
test [P.reldir|.|] [P.relfile|c.txt|] [P.relfile|c.txt|]
|
||||
|
||||
-- NOTE: All of the failing Path tests are due to the badly implemented Include mechanism in Path.
|
||||
-- I made a PR for fix on Path, so when that gets in we can uncomment these tests and also remove
|
||||
-- workarounds in StrongPath / StrongPath.Internal.
|
||||
|
||||
-- describe "Concatenation of Win . paths works as expected" $ do
|
||||
-- let test lp rp ep =
|
||||
-- it (show lp ++ " </> " ++ show rp ++ " == " ++ show ep) $
|
||||
-- (lp PW.</> rp) `shouldBe` ep
|
||||
-- -- TODO: Fails on Linux/Mac: expected: ".\\" but got: ".\\.\\"
|
||||
-- test [PW.reldir|.|] [PW.reldir|.|] [PW.reldir|.|]
|
||||
-- -- TODO: Fails on Linux/Mac: expected: "a\\" but got: ".\\a\\"
|
||||
-- test [PW.reldir|.|] [PW.reldir|a|] [PW.reldir|a|]
|
||||
-- -- TODO: Fails on Linux/Mac: expected: "a\\" but got: "a\\.\\"
|
||||
-- test [PW.reldir|a|] [PW.reldir|.|] [PW.reldir|a|]
|
||||
|
||||
-- describe "Concatenation of Posix . paths works as expected" $ do
|
||||
-- let test lp rp ep =
|
||||
-- it (show lp ++ " </> " ++ show rp ++ " == " ++ show ep) $
|
||||
-- (lp PP.</> rp) `shouldBe` ep
|
||||
-- -- TODO: Fails on Win: expected: "./" but got: "././"
|
||||
-- test [PP.reldir|.|] [PP.reldir|.|] [PP.reldir|.|]
|
||||
-- -- TODO: Fails on Win: expected: "a/" but got: "./a/"
|
||||
-- test [PP.reldir|.|] [PP.reldir|a|] [PP.reldir|a|]
|
||||
-- -- TODO: Fails on Win: expected: "a/" but got: "a/./"
|
||||
-- test [PP.reldir|a|] [PP.reldir|.|] [PP.reldir|a|]
|
||||
|
||||
describe "Parsing rel path with .. at start should fail" $ do
|
||||
let test parser p =
|
||||
it (show p ++ " should successfully parse") $
|
||||
parser p `shouldBe` Nothing
|
||||
describe "for PW.parseRelDir" $ do
|
||||
test PW.parseRelDir "../a"
|
||||
-- -- TODO: This fails on Linux/Mac! Weird, I thought Path does not allow relative paths starting with ..?
|
||||
-- -- expected: Nothing but got: Just "..\\a\\"
|
||||
-- test PW.parseRelDir "..\\a"
|
||||
describe "for P.parseRelDir" $ do
|
||||
test P.parseRelDir "../a"
|
||||
test P.parseRelDir $ ".." FP.</> "a"
|
||||
describe "for PP.parseRelDir" $ do
|
||||
test PP.parseRelDir "../a"
|
Loading…
Reference in New Issue
Block a user