@@ -13,7 +13,9 @@ import Build ( buildLibrary
1313 , buildProgram
1414 , buildWithScript
1515 )
16- import Control.Monad.Extra ( concatMapM )
16+ import Control.Monad.Extra ( concatMapM
17+ , when
18+ )
1719import Data.List ( isSuffixOf
1820 , find
1921 , nub
@@ -47,7 +49,8 @@ import Options.Applicative ( Parser
4749 , switch
4850 , value
4951 )
50- import System.Directory ( doesDirectoryExist
52+ import System.Directory ( createDirectory
53+ , doesDirectoryExist
5154 , doesFileExist
5255 , makeAbsolute
5356 , withCurrentDirectory
@@ -100,7 +103,7 @@ data GitRef = Tag String | Branch String | Commit String deriving Show
100103
101104data PathVersionSpec = PathVersionSpec { pathVersionSpecPath :: String } deriving Show
102105
103- data Command = Run String | Test String | Build
106+ data Command = Run String | Test String | Build | New String Bool Bool
104107
105108data DependencyTree = Dependency {
106109 dependencyName :: String
@@ -111,14 +114,17 @@ data DependencyTree = Dependency {
111114}
112115
113116start :: Arguments -> IO ()
114- start args = do
115- fpmContents <- TIO. readFile " fpm.toml"
116- let tomlSettings = Toml. decode settingsCodec fpmContents
117- case tomlSettings of
118- Left err -> print err
119- Right tomlSettings' -> do
120- appSettings <- toml2AppSettings tomlSettings' (release args)
121- app args appSettings
117+ start args = case command' args of
118+ New projectName withExecutable withTest ->
119+ createNewProject projectName withExecutable withTest
120+ _ -> do
121+ fpmContents <- TIO. readFile " fpm.toml"
122+ let tomlSettings = Toml. decode settingsCodec fpmContents
123+ case tomlSettings of
124+ Left err -> print err
125+ Right tomlSettings' -> do
126+ appSettings <- toml2AppSettings tomlSettings' (release args)
127+ app args appSettings
122128
123129app :: Arguments -> AppSettings -> IO ()
124130app args settings = case command' args of
@@ -279,6 +285,8 @@ arguments =
279285 <> command " test" (info testArguments (progDesc " Run the tests" ))
280286 <> command " build"
281287 (info buildArguments (progDesc " Build the executable" ))
288+ <> command " new"
289+ (info newArguments (progDesc " Create a new project in a new directory" ))
282290 )
283291 <*> switch (long " release" <> help " Build in release mode" )
284292 <*> strOption
@@ -297,6 +305,13 @@ testArguments =
297305buildArguments :: Parser Command
298306buildArguments = pure Build
299307
308+ newArguments :: Parser Command
309+ newArguments =
310+ New
311+ <$> strArgument (metavar " NAME" <> help " Name of new project" )
312+ <*> switch (long " with-executable" <> help " Include an executable" )
313+ <*> switch (long " with-test" <> help " Include a test" )
314+
300315getDirectoriesFiles :: [FilePath ] -> [FilePattern ] -> IO [FilePath ]
301316getDirectoriesFiles dirs exts = getDirectoryFilesIO " " newPatterns
302317 where
@@ -629,3 +644,77 @@ buildDependency buildPrefix compiler flags (Dependency name path sourcePath mBui
629644 name
630645 (map fst transitiveDependencies)
631646 return $ (buildPath, thisArchive) : transitiveDependencies
647+
648+ createNewProject :: String -> Bool -> Bool -> IO ()
649+ createNewProject projectName withExecutable withTest = do
650+ createDirectory projectName
651+ writeFile (projectName </> " fpm.toml" ) (templateFpmToml projectName)
652+ writeFile (projectName </> " README.md" ) (templateReadme projectName)
653+ writeFile (projectName </> " .gitignore" ) " build/*\n "
654+ createDirectory (projectName </> " src" )
655+ writeFile (projectName </> " src" </> projectName <.> " f90" )
656+ (templateModule projectName)
657+ when withExecutable $ do
658+ createDirectory (projectName </> " app" )
659+ writeFile (projectName </> " app" </> " main.f90" )
660+ (templateProgram projectName)
661+ when withTest $ do
662+ createDirectory (projectName </> " test" )
663+ writeFile (projectName </> " test" </> " main.f90" ) templateTest
664+ withCurrentDirectory projectName $ do
665+ system " git init"
666+ return ()
667+
668+ templateFpmToml :: String -> String
669+ templateFpmToml projectName =
670+ " name = \" "
671+ ++ projectName
672+ ++ " \"\n "
673+ ++ " version = \" 0.1.0\"\n "
674+ ++ " license = \" license\"\n "
675+ ++ " author = \" Jane Doe\"\n "
676+ ++ " maintainer = \" [email protected] \"\n " 677+ ++ " copyright = \" 2020 Jane Doe\"\n "
678+
679+ templateModule :: String -> String
680+ templateModule projectName =
681+ " module "
682+ ++ projectName
683+ ++ " \n "
684+ ++ " implicit none\n "
685+ ++ " private\n "
686+ ++ " \n "
687+ ++ " public :: say_hello\n "
688+ ++ " contains\n "
689+ ++ " subroutine say_hello\n "
690+ ++ " print *, \" Hello, "
691+ ++ projectName
692+ ++ " !\"\n "
693+ ++ " end subroutine say_hello\n "
694+ ++ " end module "
695+ ++ projectName
696+ ++ " \n "
697+
698+ templateReadme :: String -> String
699+ templateReadme projectName =
700+ " # " ++ projectName ++ " \n " ++ " \n " ++ " My cool new project!\n "
701+
702+ templateProgram :: String -> String
703+ templateProgram projectName =
704+ " program main\n "
705+ ++ " use "
706+ ++ projectName
707+ ++ " , only: say_hello\n "
708+ ++ " \n "
709+ ++ " implicit none\n "
710+ ++ " \n "
711+ ++ " call say_hello\n "
712+ ++ " end program main\n "
713+
714+ templateTest :: String
715+ templateTest =
716+ " program main\n "
717+ ++ " implicit none\n "
718+ ++ " \n "
719+ ++ " print *, \" Put some tests in here!\"\n "
720+ ++ " end program main\n "
0 commit comments