aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--bootstrap/package.yaml11
-rw-r--r--bootstrap/src/Build.hs379
-rw-r--r--bootstrap/src/BuildModel.hs403
-rw-r--r--bootstrap/src/Fpm.hs18
-rw-r--r--bootstrap/stack.yaml6
-rw-r--r--bootstrap/stack.yaml.lock23
l---------bootstrap/test1
-rw-r--r--bootstrap/test/Spec.hs (renamed from test/Spec.hs)38
l---------bootstrap/test/example_packages1
-rw-r--r--bootstrap/unit_test/ModuleSourceConstructionTest.hs83
-rw-r--r--bootstrap/unit_test/ModuleToCompileInfoTest.hs70
-rw-r--r--bootstrap/unit_test/ProgramSourceConstructionTest.hs69
-rw-r--r--bootstrap/unit_test/ProgramToCompileInfoTest.hs68
-rw-r--r--bootstrap/unit_test/SubmoduleSourceConstructionTest.hs79
-rw-r--r--bootstrap/unit_test/SubmoduleToCompileInfoTest.hs75
-rw-r--r--bootstrap/unit_test/Trimmer.hs1
-rwxr-xr-xci/run_tests.bat40
-rwxr-xr-xci/run_tests.sh26
-rw-r--r--example_packages/README.md (renamed from test/example_packages/README.md)6
-rw-r--r--example_packages/auto_discovery_off/app/main.f90 (renamed from test/example_packages/auto_discovery_off/app/main.f90)0
-rw-r--r--example_packages/auto_discovery_off/app/unused.f90 (renamed from test/example_packages/auto_discovery_off/app/unused.f90)0
-rw-r--r--example_packages/auto_discovery_off/fpm.toml (renamed from test/example_packages/auto_discovery_off/fpm.toml)0
-rw-r--r--example_packages/auto_discovery_off/test/my_test.f90 (renamed from test/example_packages/auto_discovery_off/test/my_test.f90)0
-rw-r--r--example_packages/auto_discovery_off/test/unused_test.f90 (renamed from test/example_packages/auto_discovery_off/test/unused_test.f90)0
-rw-r--r--example_packages/circular_example/.gitignore (renamed from test/example_packages/circular_example/.gitignore)0
-rw-r--r--example_packages/circular_example/fpm.toml (renamed from test/example_packages/circular_example/fpm.toml)0
-rw-r--r--example_packages/circular_example/src/greet_m.f90 (renamed from test/example_packages/circular_example/src/greet_m.f90)0
-rw-r--r--example_packages/circular_example/test/main.f90 (renamed from test/example_packages/circular_example/test/main.f90)0
-rw-r--r--example_packages/circular_test/.gitignore (renamed from test/example_packages/circular_test/.gitignore)0
-rw-r--r--example_packages/circular_test/fpm.toml (renamed from test/example_packages/circular_test/fpm.toml)0
-rw-r--r--example_packages/circular_test/src/hello_test.f90 (renamed from test/example_packages/circular_test/src/hello_test.f90)0
-rw-r--r--example_packages/hello_complex/.gitignore (renamed from test/example_packages/hello_complex/.gitignore)0
-rw-r--r--example_packages/hello_complex/apps/say_goodbye/say_goodbye.f90 (renamed from test/example_packages/hello_complex/apps/say_goodbye/say_goodbye.f90)0
-rw-r--r--example_packages/hello_complex/apps/say_hello/say_Hello.f90 (renamed from test/example_packages/hello_complex/apps/say_hello/say_Hello.f90)0
-rw-r--r--example_packages/hello_complex/fpm.toml (renamed from test/example_packages/hello_complex/fpm.toml)0
-rw-r--r--example_packages/hello_complex/source/farewell_m.f90 (renamed from test/example_packages/hello_complex/source/farewell_m.f90)0
-rw-r--r--example_packages/hello_complex/source/greet_m.f90 (renamed from test/example_packages/hello_complex/source/greet_m.f90)0
-rw-r--r--example_packages/hello_complex/source/subdir/constants.f90 (renamed from test/example_packages/hello_complex/source/subdir/constants.f90)0
-rw-r--r--example_packages/hello_complex/tests/farewell/farewell_test.f90 (renamed from test/example_packages/hello_complex/tests/farewell/farewell_test.f90)0
-rw-r--r--example_packages/hello_complex/tests/greet/greet_test.f90 (renamed from test/example_packages/hello_complex/tests/greet/greet_test.f90)0
-rw-r--r--example_packages/hello_complex_2/.gitignore (renamed from test/example_packages/hello_complex_2/.gitignore)0
-rw-r--r--example_packages/hello_complex_2/app/app_mod.f90 (renamed from test/example_packages/hello_complex_2/app/app_mod.f90)0
-rw-r--r--example_packages/hello_complex_2/app/say_goodbye.f90 (renamed from test/example_packages/hello_complex_2/app/say_goodbye.f90)0
-rw-r--r--example_packages/hello_complex_2/app/say_hello/app_hello_mod.f90 (renamed from test/example_packages/hello_complex_2/app/say_hello/app_hello_mod.f90)2
-rw-r--r--example_packages/hello_complex_2/app/say_hello/say_Hello.f90 (renamed from test/example_packages/hello_complex_2/app/say_hello/say_Hello.f90)0
-rw-r--r--example_packages/hello_complex_2/fpm.toml (renamed from test/example_packages/hello_complex_2/fpm.toml)0
-rw-r--r--example_packages/hello_complex_2/src/farewell_m.f90 (renamed from test/example_packages/hello_complex_2/src/farewell_m.f90)0
-rw-r--r--example_packages/hello_complex_2/src/greet_m.f90 (renamed from test/example_packages/hello_complex_2/src/greet_m.f90)0
-rw-r--r--example_packages/hello_complex_2/test/farewell_test.f90 (renamed from test/example_packages/hello_complex_2/test/farewell_test.f90)0
-rw-r--r--example_packages/hello_complex_2/test/greet_test.f90 (renamed from test/example_packages/hello_complex_2/test/greet_test.f90)0
-rw-r--r--example_packages/hello_complex_2/test/test_mod.f90 (renamed from test/example_packages/hello_complex_2/test/test_mod.f90)0
-rw-r--r--example_packages/hello_fpm/.gitignore (renamed from test/example_packages/hello_fpm/.gitignore)0
-rw-r--r--example_packages/hello_fpm/app/main.f90 (renamed from test/example_packages/hello_fpm/app/main.f90)0
-rw-r--r--example_packages/hello_fpm/fpm.toml (renamed from test/example_packages/hello_fpm/fpm.toml)0
-rw-r--r--example_packages/hello_world/.gitignore (renamed from test/example_packages/hello_world/.gitignore)0
-rw-r--r--example_packages/hello_world/app/main.f90 (renamed from test/example_packages/hello_world/app/main.f90)0
-rw-r--r--example_packages/hello_world/fpm.toml (renamed from test/example_packages/hello_world/fpm.toml)0
-rw-r--r--example_packages/makefile_complex/.gitignore (renamed from test/example_packages/makefile_complex/.gitignore)0
-rw-r--r--example_packages/makefile_complex/Makefile (renamed from test/example_packages/makefile_complex/Makefile)0
-rw-r--r--example_packages/makefile_complex/app/main.f90 (renamed from test/example_packages/makefile_complex/app/main.f90)0
-rw-r--r--example_packages/makefile_complex/fpm.toml (renamed from test/example_packages/makefile_complex/fpm.toml)0
-rw-r--r--example_packages/makefile_complex/src/wrapper_mod.f90 (renamed from test/example_packages/makefile_complex/src/wrapper_mod.f90)0
-rw-r--r--example_packages/program_with_module/app/main.f90 (renamed from test/example_packages/program_with_module/app/main.f90)0
-rw-r--r--example_packages/program_with_module/fpm.toml (renamed from test/example_packages/program_with_module/fpm.toml)0
-rw-r--r--example_packages/submodules/.gitignore (renamed from test/example_packages/with_makefile/.gitignore)0
-rw-r--r--example_packages/submodules/fpm.toml (renamed from test/example_packages/submodules/fpm.toml)0
-rw-r--r--example_packages/submodules/src/child1.f90 (renamed from test/example_packages/submodules/src/child1.f90)0
-rw-r--r--example_packages/submodules/src/child2.f90 (renamed from test/example_packages/submodules/src/child2.f90)0
-rw-r--r--example_packages/submodules/src/grandchild.f90 (renamed from test/example_packages/submodules/src/grandchild.f90)0
-rw-r--r--example_packages/submodules/src/parent.f90 (renamed from test/example_packages/submodules/src/parent.f90)0
-rw-r--r--example_packages/with_c/app/main.f90 (renamed from test/example_packages/with_c/app/main.f90)0
-rw-r--r--example_packages/with_c/fpm.toml (renamed from test/example_packages/with_c/fpm.toml)0
-rw-r--r--example_packages/with_c/src/c_code.c (renamed from test/example_packages/with_c/src/c_code.c)0
-rw-r--r--example_packages/with_c/src/with_c.f90 (renamed from test/example_packages/with_c/src/with_c.f90)0
-rw-r--r--example_packages/with_makefile/.gitignore1
-rw-r--r--example_packages/with_makefile/Makefile (renamed from test/example_packages/with_makefile/Makefile)0
-rw-r--r--example_packages/with_makefile/fpm.toml (renamed from test/example_packages/with_makefile/fpm.toml)0
-rw-r--r--example_packages/with_makefile/src/hello_makefile.f90 (renamed from test/example_packages/with_makefile/src/hello_makefile.f90)0
-rw-r--r--fpm/src/fpm.f90146
-rw-r--r--fpm/src/fpm/git.f9052
-rw-r--r--fpm/src/fpm_backend.f9013
-rw-r--r--fpm/src/fpm_filesystem.f9012
-rw-r--r--fpm/src/fpm_sources.f90138
-rw-r--r--fpm/test/fpm_test/test_source_parsing.f906
-rwxr-xr-xinstall.sh33
85 files changed, 1387 insertions, 413 deletions
diff --git a/bootstrap/package.yaml b/bootstrap/package.yaml
index ec5ecf2..26a7f74 100644
--- a/bootstrap/package.yaml
+++ b/bootstrap/package.yaml
@@ -58,3 +58,14 @@ tests:
- -with-rtsopts=-N
dependencies:
- fpm
+ fpm-unittest:
+ main: Trimmer.hs
+ source-dirs: unit_test
+ ghc-options:
+ - -threaded
+ - -rtsopts
+ - -with-rtsopts=-N
+ dependencies:
+ - fpm
+ - hedge
+ - hedge-trimmer
diff --git a/bootstrap/src/Build.hs b/bootstrap/src/Build.hs
index cdcbb02..083e646 100644
--- a/bootstrap/src/Build.hs
+++ b/bootstrap/src/Build.hs
@@ -6,20 +6,19 @@ module Build
)
where
-import Control.Applicative ( (<|>) )
-import Control.Monad ( filterM )
-import Data.Char ( isAsciiLower
- , isDigit
- , toLower
+import BuildModel ( CompileTimeInfo(..)
+ , RawSource(..)
+ , Source(..)
+ , constructCompileTimeInfo
+ , getAllObjectFiles
+ , getAvailableModules
+ , getSourceFileName
+ , processRawSource
)
import Data.List ( intercalate
, isSuffixOf
)
import Data.List.Utils ( replace )
-import qualified Data.Map as Map
-import Data.Maybe ( fromMaybe
- , mapMaybe
- )
import Development.Shake ( FilePattern
, Change(ChangeModtimeAndDigest)
, cmd
@@ -36,39 +35,20 @@ import Development.Shake ( FilePattern
, shakeThreads
, want
, (<//>)
- , (&%>)
, (%>)
- , (?>)
+ , (&?>)
)
-import Development.Shake.FilePath ( dropExtension
- , exe
- , makeRelative
+import Development.Shake.FilePath ( exe
+ , splitDirectories
, (</>)
, (<.>)
- , (-<.>)
)
+import System.Environment ( setEnv )
+import System.Process ( system )
import System.Directory ( createDirectoryIfMissing
, makeAbsolute
, withCurrentDirectory
)
-import System.Environment ( setEnv )
-import System.FilePath ( splitDirectories )
-import System.Process ( system )
-import Text.ParserCombinators.ReadP ( ReadP
- , char
- , eof
- , many
- , many1
- , option
- , readP_to_S
- , satisfy
- , skipSpaces
- , string
- )
-
-type ModuleName = String
-
-data LineContents = ModuleUsed ModuleName | Other
buildProgram
:: FilePath
@@ -81,29 +61,23 @@ buildProgram
-> FilePath
-> [FilePath]
-> IO ()
-buildProgram programDirectory libraryDirectories sourceExtensions buildDirectory compiler flags programName programSource archives
+buildProgram programDirectory' libraryDirectories sourceExtensions buildDirectory' compiler flags programName programSource archives
= do
- sourceFiles <- getDirectoriesFiles [programDirectory] sourceExtensions
- canonicalProgramSource <- makeAbsolute $ programDirectory </> programSource
- moduleSourceFiles <- filterM
- (\source -> do
- canonicalSource <- makeAbsolute source
- return $ canonicalProgramSource /= canonicalSource
- )
- sourceFiles
- let moduleObjectFiles = map
- (sourceFileToObjectFile buildDirectory programDirectory)
- moduleSourceFiles
- let sourceFileLookupMap = createSourceFileLookupMap buildDirectory
- programDirectory
- moduleSourceFiles
- let moduleLookupMap = createModuleLookupMap buildDirectory
- programDirectory
- moduleSourceFiles
- otherModuleMaps <- mapM getLibraryModuleMap libraryDirectories
- let allModuleMaps =
- moduleLookupMap `Map.union` foldl Map.union Map.empty otherModuleMaps
+ let programDirectory = foldl1 (</>) (splitDirectories programDirectory')
+ let buildDirectory = foldl1 (</>) (splitDirectories buildDirectory')
let includeFlags = map ("-I" ++) libraryDirectories
+ sourceFiles <- getDirectoriesFiles [programDirectory] sourceExtensions
+ rawSources <- mapM sourceFileToRawSource sourceFiles
+ let sources' = map processRawSource rawSources
+ let isThisProgramOrNotProgram p@(Program{}) =
+ programSourceFileName p == programDirectory </> programSource
+ isThisProgramOrNotProgram _ = True
+ let sources = filter isThisProgramOrNotProgram sources'
+ let availableModules = getAvailableModules sources
+ let compileTimeInfo = map
+ (\s -> constructCompileTimeInfo s availableModules buildDirectory)
+ sources
+ let objectFiles = getAllObjectFiles buildDirectory sources
shake shakeOptions { shakeFiles = buildDirectory
, shakeChange = ChangeModtimeAndDigest
, shakeColor = True
@@ -111,47 +85,28 @@ buildProgram programDirectory libraryDirectories sourceExtensions buildDirectory
, shakeProgress = progressSimple
}
$ do
+ let infoToRule cti =
+ let obj = compileTimeInfoObjectFileProduced cti
+ other = compileTimeInfoOtherFilesProduced cti
+ directDependencies = compileTimeInfoDirectDependencies cti
+ sourceFile = compileTimeInfoSourceFileName cti
+ fileMatcher f =
+ let realf = foldl1 (</>) (splitDirectories f)
+ in if realf == obj || realf `elem` other
+ then Just (obj : other)
+ else Nothing
+ in fileMatcher &?> \(objectFile : _) -> do
+ need (sourceFile : directDependencies)
+ cmd compiler
+ ["-c", "-J" ++ buildDirectory]
+ includeFlags
+ flags
+ ["-o", objectFile, sourceFile]
want [buildDirectory </> programName <.> exe]
buildDirectory </> programName <.> exe %> \executable -> do
- let objectFile = sourceFileToObjectFile buildDirectory
- programDirectory
- programSource
- let allObjectFiles = objectFile : moduleObjectFiles
- need allObjectFiles
- need archives
- cmd compiler allObjectFiles archives ["-o", executable] flags
- buildDirectory </> (map toLower programSource) -<.> "o" %> \objectFile -> do
- let realObjectFile = foldl (</>) "" $ splitDirectories objectFile
- let sourceFile = programDirectory </> programSource
- need [sourceFile]
- modulesUsed <- liftIO $ getModulesUsed sourceFile
- let moduleFilesNeeded =
- mapMaybe (`Map.lookup` allModuleMaps) modulesUsed
- let includeFlags = map ("-I" ++) libraryDirectories
- need moduleFilesNeeded
- cmd compiler
- ["-c", "-J" ++ buildDirectory]
- includeFlags
- flags
- ["-o", objectFile, sourceFile]
- map (\ext -> buildDirectory </> "*" <.> ext) ["o", "mod"]
- &%> \[objectFile, moduleFile] -> do
- let realObjectFile =
- foldl (</>) "" $ splitDirectories objectFile
- let sourceFile = fromMaybe
- undefined
- (Map.lookup realObjectFile sourceFileLookupMap)
- need [sourceFile]
- modulesUsed <- liftIO $ getModulesUsed sourceFile
- let moduleFilesNeeded =
- mapMaybe (`Map.lookup` allModuleMaps) modulesUsed
- let includeFlags = map ("-I" ++) libraryDirectories
- need moduleFilesNeeded
- cmd compiler
- ["-c", "-J" ++ buildDirectory]
- includeFlags
- flags
- ["-o", objectFile, sourceFile]
+ need objectFiles
+ cmd compiler objectFiles archives ["-o", executable] flags
+ mapM_ infoToRule compileTimeInfo
buildLibrary
:: FilePath
@@ -164,14 +119,15 @@ buildLibrary
-> IO (FilePath)
buildLibrary libraryDirectory sourceExtensions buildDirectory compiler flags libraryName otherLibraryDirectories
= do
+ let includeFlags = map ("-I" ++) otherLibraryDirectories
sourceFiles <- getDirectoriesFiles [libraryDirectory] sourceExtensions
- let sourceFileLookupMap =
- createSourceFileLookupMap buildDirectory libraryDirectory sourceFiles
- let moduleLookupMap =
- createModuleLookupMap buildDirectory libraryDirectory sourceFiles
- otherModuleMaps <- mapM getLibraryModuleMap otherLibraryDirectories
- let allModuleMaps =
- moduleLookupMap `Map.union` foldl Map.union Map.empty otherModuleMaps
+ rawSources <- mapM sourceFileToRawSource sourceFiles
+ let sources = map processRawSource rawSources
+ let availableModules = getAvailableModules sources
+ let compileTimeInfo = map
+ (\s -> constructCompileTimeInfo s availableModules buildDirectory)
+ sources
+ let objectFiles = getAllObjectFiles buildDirectory sources
let archiveFile = buildDirectory </> "lib" ++ libraryName <.> "a"
shake shakeOptions { shakeFiles = buildDirectory
, shakeChange = ChangeModtimeAndDigest
@@ -180,196 +136,30 @@ buildLibrary libraryDirectory sourceExtensions buildDirectory compiler flags lib
, shakeProgress = progressSimple
}
$ do
- map (\ext -> buildDirectory </> "*" <.> ext) ["o", "mod"]
- &%> \[objectFile, moduleFile] -> do
- let realObjectFile =
- foldl (</>) "" $ splitDirectories objectFile
- let sourceFile = fromMaybe
- undefined
- (Map.lookup realObjectFile sourceFileLookupMap)
- need [sourceFile]
- modulesUsed <- liftIO $ getModulesUsed sourceFile
- let moduleFilesNeeded =
- mapMaybe (`Map.lookup` allModuleMaps) modulesUsed
- let includeFlags = map ("-I" ++) otherLibraryDirectories
- need moduleFilesNeeded
- cmd compiler
- ["-c", "-J" ++ buildDirectory]
- includeFlags
- flags
- ["-o", objectFile, sourceFile]
+ let infoToRule cti =
+ let obj = compileTimeInfoObjectFileProduced cti
+ other = compileTimeInfoOtherFilesProduced cti
+ directDependencies = compileTimeInfoDirectDependencies cti
+ sourceFile = compileTimeInfoSourceFileName cti
+ fileMatcher f =
+ let realf = foldl1 (</>) (splitDirectories f)
+ in if realf == obj || realf `elem` other
+ then Just (obj : other)
+ else Nothing
+ in fileMatcher &?> \(objectFile : _) -> do
+ need (sourceFile : directDependencies)
+ cmd compiler
+ ["-c", "-J" ++ buildDirectory]
+ includeFlags
+ flags
+ ["-o", objectFile, sourceFile]
+ want [archiveFile]
archiveFile %> \a -> do
- let objectFiles = Map.keys sourceFileLookupMap
need objectFiles
cmd "ar" ["rs"] a objectFiles
- want [archiveFile]
+ mapM_ infoToRule compileTimeInfo
return archiveFile
--- A little wrapper around getDirectoryFiles so we can get files from multiple directories
-getDirectoriesFiles :: [FilePath] -> [FilePattern] -> IO [FilePath]
-getDirectoriesFiles dirs exts = getDirectoryFilesIO "" newPatterns
- where
- newPatterns = concatMap appendExts dirs
- appendExts dir = map ((dir <//> "*") ++) exts
-
-getLibraryModuleMap :: FilePath -> IO (Map.Map ModuleName FilePath)
-getLibraryModuleMap libraryDirectory = do
- moduleFiles <- getDirectoriesFiles [libraryDirectory] ["*.mod"]
- let moduleMap = foldl
- Map.union
- Map.empty
- (map (\m -> Map.singleton (moduleFileToModuleName m) m) moduleFiles)
- return moduleMap
- where
- moduleFileToModuleName moduleFile =
- map toLower $ dropExtension (makeRelative libraryDirectory moduleFile)
-
-createSourceFileLookupMap
- :: FilePath -> FilePath -> [FilePath] -> Map.Map FilePath FilePath
-createSourceFileLookupMap buildDirectory libraryDirectory sourceFiles = foldl
- Map.union
- Map.empty
- (map (createSourceToObjectMap buildDirectory libraryDirectory) sourceFiles)
-
-createModuleLookupMap
- :: FilePath -> FilePath -> [FilePath] -> Map.Map ModuleName FilePath
-createModuleLookupMap buildDirectory libraryDirectory sourceFiles = foldl
- Map.union
- Map.empty
- (map (createSourceToModuleMap buildDirectory libraryDirectory) sourceFiles)
-
-createSourceToModuleMap
- :: FilePath -> FilePath -> FilePath -> Map.Map ModuleName FilePath
-createSourceToModuleMap buildDirectory libraryDirectory sourceFile =
- Map.singleton
- (sourceFileToModuleName libraryDirectory sourceFile)
- (sourceFileToModFile buildDirectory libraryDirectory sourceFile)
-
-sourceFileToModuleName :: FilePath -> FilePath -> ModuleName
-sourceFileToModuleName libraryDirectory sourceFile =
- map toLower $ pathSeparatorsToUnderscores
- (dropExtension (makeRelative libraryDirectory sourceFile))
-
-createSourceToObjectMap
- :: FilePath -> FilePath -> FilePath -> Map.Map FilePath FilePath
-createSourceToObjectMap buildDirectory libraryDirectory sourceFile =
- Map.singleton
- (sourceFileToObjectFile buildDirectory libraryDirectory sourceFile)
- sourceFile
-
-sourceFileToObjectFile :: FilePath -> FilePath -> FilePath -> FilePath
-sourceFileToObjectFile buildDirectory libraryDirectory sourceFile =
- (foldl (</>) "" $ splitDirectories buildDirectory)
- </> map
- toLower
- (pathSeparatorsToUnderscores
- (makeRelative libraryDirectory sourceFile)
- )
- -<.> "o"
-
-sourceFileToExecutable :: FilePath -> FilePath -> FilePath -> FilePath
-sourceFileToExecutable buildDirectory appDirectory sourceFile =
- buildDirectory
- </> pathSeparatorsToUnderscores (makeRelative appDirectory sourceFile)
- -<.> exe
-
-sourceFileToModFile :: FilePath -> FilePath -> FilePath -> FilePath
-sourceFileToModFile buildDirectory libraryDirectory sourceFile =
- buildDirectory
- </> map
- toLower
- (pathSeparatorsToUnderscores
- (makeRelative libraryDirectory sourceFile)
- )
- -<.> "mod"
-
-pathSeparatorsToUnderscores :: FilePath -> FilePath
-pathSeparatorsToUnderscores fileName =
- intercalate "_" (splitDirectories fileName)
-
-getModulesUsed :: FilePath -> IO [ModuleName]
-getModulesUsed sourceFile = do
- fileLines <- readFileLinesIO sourceFile
- let lineContents = map parseFortranLine fileLines
- return $ contentsToModuleNames lineContents
-
-contentsToModuleNames :: [LineContents] -> [ModuleName]
-contentsToModuleNames = mapMaybe contentToMaybeModuleName
- where
- contentToMaybeModuleName content = case content of
- ModuleUsed moduleName -> Just moduleName
- _ -> Nothing
-
-readFileLinesIO :: FilePath -> IO [String]
-readFileLinesIO file = do
- contents <- readFile file
- return $ lines contents
-
-parseFortranLine :: String -> LineContents
-parseFortranLine line =
- let line' = map toLower line
- result = readP_to_S doFortranLineParse line'
- in getResult result
- where
- getResult (_ : (contents, _) : _) = contents
- getResult [(contents, _) ] = contents
- getResult [] = Other
-
-doFortranLineParse :: ReadP LineContents
-doFortranLineParse = option Other fortranUsefulContents
-
-fortranUsefulContents :: ReadP LineContents
-fortranUsefulContents = useStatement
-
-useStatement :: ReadP LineContents
-useStatement = do
- skipSpaces
- _ <- string "use"
- skipAtLeastOneWhiteSpace
- modName <- validIdentifier
- skipSpaceCommaOrEnd
- return $ ModuleUsed modName
-
-skipAtLeastOneWhiteSpace :: ReadP ()
-skipAtLeastOneWhiteSpace = do
- _ <- many1 whiteSpace
- return ()
-
-skipSpaceOrEnd :: ReadP ()
-skipSpaceOrEnd = eof <|> skipAtLeastOneWhiteSpace
-
-skipSpaceCommaOrEnd :: ReadP ()
-skipSpaceCommaOrEnd = eof <|> skipComma <|> skipAtLeastOneWhiteSpace
-
-skipComma :: ReadP ()
-skipComma = do
- _ <- char ','
- return ()
-
-whiteSpace :: ReadP Char
-whiteSpace = satisfy (`elem` " \t")
-
-validIdentifier :: ReadP String
-validIdentifier = do
- first <- validFirstCharacter
- rest <- many validIdentifierCharacter
- return $ first : rest
-
-validFirstCharacter :: ReadP Char
-validFirstCharacter = alphabet
-
-validIdentifierCharacter :: ReadP Char
-validIdentifierCharacter = alphabet <|> digit <|> underscore
-
-alphabet :: ReadP Char
-alphabet = satisfy isAsciiLower
-
-digit :: ReadP Char
-digit = satisfy isDigit
-
-underscore :: ReadP Char
-underscore = char '_'
-
buildWithScript
:: String
-> FilePath
@@ -387,12 +177,11 @@ buildWithScript script projectDirectory buildDirectory compiler flags libraryNam
setEnv "FC" compiler
setEnv "FFLAGS" (intercalate " " flags)
setEnv "BUILD_DIR" $ unWindowsPath absoluteBuildDirectory
- setEnv
- "INCLUDE_DIRS"
- (intercalate " " (map unWindowsPath absoluteLibraryDirectories))
+ setEnv "INCLUDE_DIRS"
+ (intercalate " " (map unWindowsPath absoluteLibraryDirectories))
let archiveFile =
(unWindowsPath absoluteBuildDirectory)
- ++ "/lib"
+ ++ "/lib"
++ libraryName
<.> "a"
withCurrentDirectory
@@ -403,6 +192,18 @@ buildWithScript script projectDirectory buildDirectory compiler flags libraryNam
| otherwise -> system (script ++ " " ++ archiveFile)
return archiveFile
+-- A little wrapper around getDirectoryFiles so we can get files from multiple directories
+getDirectoriesFiles :: [FilePath] -> [FilePattern] -> IO [FilePath]
+getDirectoriesFiles dirs exts = getDirectoryFilesIO "" newPatterns
+ where
+ newPatterns = concatMap appendExts dirs
+ appendExts dir = map ((dir <//> "*") ++) exts
+
+sourceFileToRawSource :: FilePath -> IO RawSource
+sourceFileToRawSource sourceFile = do
+ contents <- readFile sourceFile
+ return $ RawSource sourceFile contents
+
isMakefile :: String -> Bool
isMakefile script | script == "Makefile" = True
| script == "makefile" = True
diff --git a/bootstrap/src/BuildModel.hs b/bootstrap/src/BuildModel.hs
new file mode 100644
index 0000000..95d3cac
--- /dev/null
+++ b/bootstrap/src/BuildModel.hs
@@ -0,0 +1,403 @@
+module BuildModel where
+
+import Control.Applicative ( (<|>) )
+import Control.Monad ( when )
+import Data.Char ( isAsciiLower
+ , isDigit
+ , toLower
+ )
+import Data.Maybe ( fromMaybe
+ , mapMaybe
+ )
+import Data.List ( intercalate )
+import System.FilePath ( (</>)
+ , (<.>)
+ , splitDirectories
+ )
+import Text.ParserCombinators.ReadP ( ReadP
+ , char
+ , eof
+ , many
+ , many1
+ , option
+ , readP_to_S
+ , satisfy
+ , skipSpaces
+ , string
+ )
+
+data LineContents =
+ ProgramDeclaration
+ | ModuleDeclaration String
+ | ModuleUsed String
+ | ModuleSubprogramDeclaration
+ | SubmoduleDeclaration String String String
+ | Other
+
+data RawSource = RawSource {
+ rawSourceFilename :: FilePath
+ , rawSourceContents :: String
+}
+
+data Source =
+ Program
+ { programSourceFileName :: FilePath
+ , programObjectFileName :: FilePath -> FilePath
+ , programModulesUsed :: [String]
+ }
+ | Module
+ { moduleSourceFileName :: FilePath
+ , moduleObjectFileName :: FilePath -> FilePath
+ , moduleModulesUsed :: [String]
+ , moduleName :: String
+ , moduleProducesSmod :: Bool
+ }
+ | Submodule
+ { submoduleSourceFileName :: FilePath
+ , submoduleObjectFileName :: FilePath -> FilePath
+ , submoduleModulesUsed :: [String]
+ , submoduleBaseModuleName :: String
+ , submoduleParentName :: String
+ , submoduleName :: String
+ }
+
+data CompileTimeInfo = CompileTimeInfo {
+ compileTimeInfoSourceFileName :: FilePath
+ , compileTimeInfoObjectFileProduced :: FilePath
+ , compileTimeInfoOtherFilesProduced :: [FilePath]
+ , compileTimeInfoDirectDependencies :: [FilePath]
+}
+
+processRawSource :: RawSource -> Source
+processRawSource rawSource =
+ let
+ sourceFileName = rawSourceFilename rawSource
+ parsedContents = parseContents rawSource
+ objectFileName =
+ \bd -> bd </> (pathSeparatorsToUnderscores sourceFileName) <.> "o"
+ modulesUsed = getModulesUsed parsedContents
+ in
+ if hasProgramDeclaration parsedContents
+ then Program { programSourceFileName = sourceFileName
+ , programObjectFileName = objectFileName
+ , programModulesUsed = modulesUsed
+ }
+ else if hasModuleDeclaration parsedContents
+ then Module
+ { moduleSourceFileName = sourceFileName
+ , moduleObjectFileName = objectFileName
+ , moduleModulesUsed = modulesUsed
+ , moduleName = getModuleName parsedContents
+ , moduleProducesSmod = hasModuleSubprogramDeclaration parsedContents
+ }
+ else if hasSubmoduleDeclaration parsedContents
+ then Submodule
+ { submoduleSourceFileName = sourceFileName
+ , submoduleObjectFileName = objectFileName
+ , submoduleModulesUsed = modulesUsed
+ , submoduleBaseModuleName = getSubmoduleBaseModuleName
+ parsedContents
+ , submoduleParentName = getSubmoduleParentName parsedContents
+ , submoduleName = getSubmoduleName parsedContents
+ }
+ else undefined
+
+getAvailableModules :: [Source] -> [String]
+getAvailableModules = mapMaybe maybeModuleName
+ where
+ maybeModuleName m@(Module{}) = Just $ moduleName m
+ maybeModuleName _ = Nothing
+
+getAllObjectFiles :: FilePath -> [Source] -> [FilePath]
+getAllObjectFiles buildDirectory sources = map getObjectFile sources
+ where
+ getObjectFile p@(Program{} ) = (programObjectFileName p) buildDirectory
+ getObjectFile m@(Module{} ) = (moduleObjectFileName m) buildDirectory
+ getObjectFile s@(Submodule{}) = (submoduleObjectFileName s) buildDirectory
+
+getSourceFileName :: Source -> FilePath
+getSourceFileName p@(Program{} ) = programSourceFileName p
+getSourceFileName m@(Module{} ) = moduleSourceFileName m
+getSourceFileName s@(Submodule{}) = submoduleSourceFileName s
+
+constructCompileTimeInfo :: Source -> [String] -> FilePath -> CompileTimeInfo
+constructCompileTimeInfo p@(Program{}) availableModules buildDirectory =
+ CompileTimeInfo
+ { compileTimeInfoSourceFileName = programSourceFileName p
+ , compileTimeInfoObjectFileProduced = (programObjectFileName p)
+ buildDirectory
+ , compileTimeInfoOtherFilesProduced = []
+ , compileTimeInfoDirectDependencies = map
+ (\mName -> buildDirectory </> mName <.> "mod")
+ (filter (`elem` availableModules) (programModulesUsed p))
+ }
+constructCompileTimeInfo m@(Module{}) availableModules buildDirectory =
+ CompileTimeInfo
+ { compileTimeInfoSourceFileName = moduleSourceFileName m
+ , compileTimeInfoObjectFileProduced = (moduleObjectFileName m)
+ buildDirectory
+ , compileTimeInfoOtherFilesProduced =
+ (buildDirectory </> moduleName m <.> "mod") : if moduleProducesSmod m
+ then [buildDirectory </> moduleName m <.> "smod"]
+ else []
+ , compileTimeInfoDirectDependencies = map
+ (\mName -> buildDirectory </> mName <.> "mod")
+ (filter (`elem` availableModules) (moduleModulesUsed m))
+ }
+constructCompileTimeInfo s@(Submodule{}) availableModules buildDirectory =
+ CompileTimeInfo
+ { compileTimeInfoSourceFileName = submoduleSourceFileName s
+ , compileTimeInfoObjectFileProduced = (submoduleObjectFileName s)
+ buildDirectory
+ , compileTimeInfoOtherFilesProduced = [ buildDirectory
+ </> submoduleBaseModuleName s
+ ++ "@"
+ ++ submoduleName s
+ <.> "smod"
+ ]
+ , compileTimeInfoDirectDependencies =
+ (buildDirectory </> submoduleParentName s <.> "smod")
+ : (map (\mName -> buildDirectory </> mName <.> "mod")
+ (filter (`elem` availableModules) (submoduleModulesUsed s))
+ )
+ }
+
+pathSeparatorsToUnderscores :: FilePath -> FilePath
+pathSeparatorsToUnderscores fileName =
+ intercalate "_" (splitDirectories fileName)
+
+parseContents :: RawSource -> [LineContents]
+parseContents rawSource =
+ let fileLines = lines $ rawSourceContents rawSource
+ in map parseFortranLine fileLines
+
+hasProgramDeclaration :: [LineContents] -> Bool
+hasProgramDeclaration parsedContents = case filter f parsedContents of
+ x : _ -> True
+ _ -> False
+ where
+ f lc = case lc of
+ ProgramDeclaration -> True
+ _ -> False
+
+hasModuleDeclaration :: [LineContents] -> Bool
+hasModuleDeclaration parsedContents = case filter f parsedContents of
+ x : _ -> True
+ _ -> False
+ where
+ f lc = case lc of
+ ModuleDeclaration{} -> True
+ _ -> False
+
+hasSubmoduleDeclaration :: [LineContents] -> Bool
+hasSubmoduleDeclaration parsedContents = case filter f parsedContents of
+ x : _ -> True
+ _ -> False
+ where
+ f lc = case lc of
+ SubmoduleDeclaration{} -> True
+ _ -> False
+
+hasModuleSubprogramDeclaration :: [LineContents] -> Bool
+hasModuleSubprogramDeclaration parsedContents = case filter f parsedContents of
+ x : _ -> True
+ _ -> False
+ where
+ f lc = case lc of
+ ModuleSubprogramDeclaration -> True
+ _ -> False
+
+getModulesUsed :: [LineContents] -> [String]
+getModulesUsed = mapMaybe contentToMaybeModuleName
+ where
+ contentToMaybeModuleName content = case content of
+ ModuleUsed moduleName -> Just moduleName
+ _ -> Nothing
+
+getModuleName :: [LineContents] -> String
+getModuleName pc = head $ mapMaybe contentToMaybeModuleName pc
+ where
+ contentToMaybeModuleName content = case content of
+ ModuleDeclaration moduleName -> Just moduleName
+ _ -> Nothing
+
+getSubmoduleBaseModuleName :: [LineContents] -> String
+getSubmoduleBaseModuleName pc = head $ mapMaybe contentToMaybeModuleName pc
+ where
+ contentToMaybeModuleName content = case content of
+ SubmoduleDeclaration baseModuleName submoduleParentName submoduleName ->
+ Just baseModuleName
+ _ -> Nothing
+
+getSubmoduleParentName :: [LineContents] -> String
+getSubmoduleParentName pc = head $ mapMaybe contentToMaybeModuleName pc
+ where
+ contentToMaybeModuleName content = case content of
+ SubmoduleDeclaration baseModuleName submoduleParentName submoduleName ->
+ Just submoduleParentName
+ _ -> Nothing
+
+getSubmoduleName :: [LineContents] -> String
+getSubmoduleName pc = head $ mapMaybe contentToMaybeModuleName pc
+ where
+ contentToMaybeModuleName content = case content of
+ SubmoduleDeclaration baseModuleName submoduleParentName submoduleName ->
+ Just submoduleName
+ _ -> Nothing
+
+readFileLinesIO :: FilePath -> IO [String]
+readFileLinesIO file = do
+ contents <- readFile file
+ return $ lines contents
+
+parseFortranLine :: String -> LineContents
+parseFortranLine line =
+ let line' = map toLower line
+ result = readP_to_S doFortranLineParse line'
+ in getResult result
+ where
+ getResult (_ : (contents, _) : _) = contents
+ getResult [(contents, _) ] = contents
+ getResult [] = Other
+
+doFortranLineParse :: ReadP LineContents
+doFortranLineParse = option Other fortranUsefulContents
+
+fortranUsefulContents :: ReadP LineContents
+fortranUsefulContents =
+ programDeclaration
+ <|> moduleSubprogramDeclaration
+ <|> moduleDeclaration
+ <|> submoduleDeclaration
+ <|> useStatement
+
+programDeclaration :: ReadP LineContents
+programDeclaration = do
+ skipSpaces
+ _ <- string "program"
+ skipAtLeastOneWhiteSpace
+ _ <- validIdentifier
+ return ProgramDeclaration
+
+moduleDeclaration :: ReadP LineContents
+moduleDeclaration = do
+ skipSpaces
+ _ <- string "module"
+ skipAtLeastOneWhiteSpace
+ moduleName <- validIdentifier
+ when (moduleName == "procedure") (fail "")
+ skipSpaceCommentOrEnd
+ return $ ModuleDeclaration moduleName
+
+submoduleDeclaration :: ReadP LineContents
+submoduleDeclaration = do
+ skipSpaces
+ _ <- string "submodule"
+ parents <- submoduleParents
+ let parentName = case parents of
+ (baseModule : []) -> baseModule
+ (multiple ) -> (head multiple) ++ "@" ++ (last multiple)
+ skipSpaces
+ name <- validIdentifier
+ skipSpaceCommentOrEnd
+ return $ SubmoduleDeclaration (head parents) parentName name
+
+submoduleParents :: ReadP [String]
+submoduleParents = do
+ skipSpaces
+ _ <- char '('
+ skipSpaces
+ firstParent <- validIdentifier
+ remainingParents <- many
+ (do
+ skipSpaces
+ _ <- char ':'
+ skipSpaces
+ name <- validIdentifier
+ return name
+ )
+ skipSpaces
+ _ <- char ')'
+ return $ firstParent : remainingParents
+
+useStatement :: ReadP LineContents
+useStatement = do
+ skipSpaces
+ _ <- string "use"
+ skipAtLeastOneWhiteSpace
+ modName <- validIdentifier
+ skipSpaceCommaOrEnd
+ return $ ModuleUsed modName
+
+moduleSubprogramDeclaration :: ReadP LineContents
+moduleSubprogramDeclaration = do
+ skipSpaces
+ skipProcedureQualifiers
+ _ <- string "module"
+ skipAtLeastOneWhiteSpace
+ _ <- string "function" <|> string "subroutine"
+ skipAtLeastOneWhiteSpace
+ return $ ModuleSubprogramDeclaration
+
+skipProcedureQualifiers :: ReadP ()
+skipProcedureQualifiers = do
+ many skipPossibleQualifier
+ return ()
+
+skipPossibleQualifier :: ReadP ()
+skipPossibleQualifier = do
+ _ <- string "pure" <|> string "elemental" <|> string "impure"
+ skipAtLeastOneWhiteSpace
+
+skipAtLeastOneWhiteSpace :: ReadP ()
+skipAtLeastOneWhiteSpace = do
+ _ <- many1 whiteSpace
+ return ()
+
+skipSpaceOrEnd :: ReadP ()
+skipSpaceOrEnd = eof <|> skipAtLeastOneWhiteSpace
+
+skipSpaceCommaOrEnd :: ReadP ()
+skipSpaceCommaOrEnd = eof <|> skipComma <|> skipAtLeastOneWhiteSpace
+
+skipSpaceCommentOrEnd :: ReadP ()
+skipSpaceCommentOrEnd = eof <|> skipComment <|> skipAtLeastOneWhiteSpace
+
+skipComma :: ReadP ()
+skipComma = do
+ _ <- char ','
+ return ()
+
+skipComment :: ReadP ()
+skipComment = do
+ _ <- char '!'
+ return ()
+
+skipAnything :: ReadP ()
+skipAnything = do
+ _ <- many (satisfy (const True))
+ return ()
+
+whiteSpace :: ReadP Char
+whiteSpace = satisfy (`elem` " \t")
+
+validIdentifier :: ReadP String
+validIdentifier = do
+ first <- validFirstCharacter
+ rest <- many validIdentifierCharacter
+ return $ first : rest
+
+validFirstCharacter :: ReadP Char
+validFirstCharacter = alphabet
+
+validIdentifierCharacter :: ReadP Char
+validIdentifierCharacter = alphabet <|> digit <|> underscore
+
+alphabet :: ReadP Char
+alphabet = satisfy isAsciiLower
+
+digit :: ReadP Char
+digit = satisfy isDigit
+
+underscore :: ReadP Char
+underscore = char '_'
diff --git a/bootstrap/src/Fpm.hs b/bootstrap/src/Fpm.hs
index d9de668..115b63e 100644
--- a/bootstrap/src/Fpm.hs
+++ b/bootstrap/src/Fpm.hs
@@ -616,12 +616,15 @@ fetchDependency name version = do
putStrLn "Simple dependencies are not yet supported :("
undefined
GitVersion versionSpec -> do
- system
- ("git init " ++ clonePath)
+ system ("git init " ++ clonePath)
case gitVersionSpecRef versionSpec of
Just ref -> do
system
- ("git -C " ++ clonePath ++ " fetch " ++ gitVersionSpecUrl versionSpec ++ " "
+ ( "git -C "
+ ++ clonePath
+ ++ " fetch "
+ ++ gitVersionSpecUrl versionSpec
+ ++ " "
++ (case ref of
Tag tag -> tag
Branch branch -> branch
@@ -630,9 +633,12 @@ fetchDependency name version = do
)
Nothing -> do
system
- ("git -C " ++ clonePath ++ " fetch " ++ gitVersionSpecUrl versionSpec)
- system
- ("git -C " ++ clonePath ++ " checkout -qf FETCH_HEAD")
+ ( "git -C "
+ ++ clonePath
+ ++ " fetch "
+ ++ gitVersionSpecUrl versionSpec
+ )
+ system ("git -C " ++ clonePath ++ " checkout -qf FETCH_HEAD")
return (name, clonePath)
PathVersion versionSpec -> return (name, pathVersionSpecPath versionSpec)
diff --git a/bootstrap/stack.yaml b/bootstrap/stack.yaml
index 68dcaaa..7147c40 100644
--- a/bootstrap/stack.yaml
+++ b/bootstrap/stack.yaml
@@ -42,6 +42,12 @@ packages:
extra-deps:
- git: https://github.com/kowainik/tomland.git
commit: 536a5e6ffb148d0dd4e4c4b120913a6744097676
+- git: https://gitlab.com/everythingfunctional/hedge.git
+ commit: 1c6cba3b5f8e52cf317f2421aaca13a0ddab4e92
+ subdirs:
+ - .
+ - hedge-trimmer
+- quickcheck-with-counterexamples-1.2
# Override default flag values for local packages and extra-deps
# flags: {}
diff --git a/bootstrap/stack.yaml.lock b/bootstrap/stack.yaml.lock
index 15bfc22..0ca18ae 100644
--- a/bootstrap/stack.yaml.lock
+++ b/bootstrap/stack.yaml.lock
@@ -5,9 +5,6 @@
packages:
- completed:
- cabal-file:
- size: 6802
- sha256: 85568a0280115b6e9a9f263cf4cfc72ad5a6eaeb2412875816adb82ea6a405bc
name: tomland
version: 1.3.0.0
git: https://github.com/kowainik/tomland.git
@@ -18,6 +15,26 @@ packages:
original:
git: https://github.com/kowainik/tomland.git
commit: 536a5e6ffb148d0dd4e4c4b120913a6744097676
+- completed:
+ subdir: hedge-trimmer
+ name: hedge-trimmer
+ version: 1.0.0.0
+ git: https://gitlab.com/everythingfunctional/hedge.git
+ pantry-tree:
+ size: 226
+ sha256: 19972f5b81c7627d6b66c852dfb7e0e67b3931ed4f418663c152717ce4ea267e
+ commit: 1c6cba3b5f8e52cf317f2421aaca13a0ddab4e92
+ original:
+ subdir: hedge-trimmer
+ git: https://gitlab.com/everythingfunctional/hedge.git
+ commit: 1c6cba3b5f8e52cf317f2421aaca13a0ddab4e92
+- completed:
+ hackage: quickcheck-with-counterexamples-1.2@sha256:d322d79008602df26f5eb4e1379e5b58bf1a92604df8601e71e200cfc3e847a3,1688
+ pantry-tree:
+ size: 724
+ sha256: 0046517e3cc2adebfce19d4aad05a06dcf55ec9e572fa1c661ba9abe81386484
+ original:
+ hackage: quickcheck-with-counterexamples-1.2
snapshots:
- completed:
size: 524996
diff --git a/bootstrap/test b/bootstrap/test
deleted file mode 120000
index 419df4f..0000000
--- a/bootstrap/test
+++ /dev/null
@@ -1 +0,0 @@
-../test \ No newline at end of file
diff --git a/test/Spec.hs b/bootstrap/test/Spec.hs
index 6fb4006..4e660e7 100644
--- a/test/Spec.hs
+++ b/bootstrap/test/Spec.hs
@@ -15,27 +15,53 @@ main = do
testCircular
testWithMakefile
testMakefileComplex
+ testSubmodule
testHelloWorld :: IO ()
testHelloWorld =
- withCurrentDirectory (example_path </> "hello_world") $ start $ Arguments (Run "") False ""
+ withCurrentDirectory (example_path </> "hello_world") $ start $ Arguments
+ (Run "")
+ False
+ ""
testHelloComplex :: IO ()
testHelloComplex =
- withCurrentDirectory (example_path </> "hello_complex") $ start $ Arguments (Test "") False ""
+ withCurrentDirectory (example_path </> "hello_complex") $ start $ Arguments
+ (Test "")
+ False
+ ""
testHelloFpm :: IO ()
testHelloFpm =
- withCurrentDirectory (example_path </> "hello_fpm") $ start $ Arguments (Run "") False ""
+ withCurrentDirectory (example_path </> "hello_fpm") $ start $ Arguments
+ (Run "")
+ False
+ ""
testCircular :: IO ()
testCircular =
- withCurrentDirectory (example_path </> "circular_example") $ start $ Arguments (Test "") False ""
+ withCurrentDirectory (example_path </> "circular_example") $ start $ Arguments
+ (Test "")
+ False
+ ""
testWithMakefile :: IO ()
testWithMakefile =
- withCurrentDirectory (example_path </> "with_makefile") $ start $ Arguments (Build) False ""
+ withCurrentDirectory (example_path </> "with_makefile") $ start $ Arguments
+ (Build)
+ False
+ ""
testMakefileComplex :: IO ()
testMakefileComplex =
- withCurrentDirectory (example_path </> "makefile_complex") $ start $ Arguments (Run "") False ""
+ withCurrentDirectory (example_path </> "makefile_complex") $ start $ Arguments
+ (Run "")
+ False
+ ""
+
+testSubmodule :: IO ()
+testSubmodule =
+ withCurrentDirectory (example_path </> "submodules") $ start $ Arguments
+ (Build)
+ False
+ ""
diff --git a/bootstrap/test/example_packages b/bootstrap/test/example_packages
new file mode 120000
index 0000000..b7c12dc
--- /dev/null
+++ b/bootstrap/test/example_packages
@@ -0,0 +1 @@
+../../example_packages \ No newline at end of file
diff --git a/bootstrap/unit_test/ModuleSourceConstructionTest.hs b/bootstrap/unit_test/ModuleSourceConstructionTest.hs
new file mode 100644
index 0000000..b98e9d3
--- /dev/null
+++ b/bootstrap/unit_test/ModuleSourceConstructionTest.hs
@@ -0,0 +1,83 @@
+module ModuleSourceConstructionTest
+ ( test
+ )
+where
+
+import BuildModel ( RawSource(..)
+ , Source(..)
+ , processRawSource
+ )
+import Hedge ( Result
+ , Test
+ , assertEquals
+ , assertThat
+ , fail'
+ , givenInput
+ , then'
+ , whenTransformed
+ )
+import System.FilePath ( (</>) )
+
+test :: IO (Test ())
+test = return $ givenInput
+ "a module"
+ exampleModule
+ [ whenTransformed
+ "processed to a source"
+ processRawSource
+ [ then' "it is a Module" checkIsModule
+ , then' "its source file name is the same as the original"
+ checkModuleSourceFileName
+ , then'
+ "its object file name is the 'flattened' path of the source file with '.o' appeneded"
+ checkModuleObjectFileName
+ , then' "it knows what modules it uses directly" checkModuleModulesUsed
+ , then' "it knows its name" checkModuleName
+ , then' "it can tell that it will produce a '.smod' file" checkSmod
+ ]
+ ]
+
+exampleModule :: RawSource
+exampleModule = RawSource moduleSourceFileName' $ unlines
+ [ "module some_module"
+ , " use module1"
+ , " USE MODULE2"
+ , " implicit none"
+ , " interface"
+ , " pure module function some_func()"
+ , " integer :: some_func"
+ , " end function"
+ , " end interface"
+ , "end module"
+ ]
+
+moduleSourceFileName' :: String
+moduleSourceFileName' = "some" </> "file" </> "somewhere.f90"
+
+checkIsModule :: Source -> Result
+checkIsModule Module{} = assertThat True
+checkIsModule _ = assertThat False
+
+checkModuleSourceFileName :: Source -> Result
+checkModuleSourceFileName m@(Module{}) =
+ assertEquals moduleSourceFileName' $ moduleSourceFileName m
+checkModuleSourceFileName _ = fail' "wasn't a Module"
+
+checkModuleObjectFileName :: Source -> Result
+checkModuleObjectFileName m@(Module{}) =
+ assertEquals ("." </> "some_file_somewhere.f90.o")
+ $ (moduleObjectFileName m) "."
+checkModuleObjectFileName _ = fail' "wasn't a Module"
+
+checkModuleModulesUsed :: Source -> Result
+checkModuleModulesUsed m@(Module{}) =
+ assertEquals ["module1", "module2"] $ moduleModulesUsed m
+checkModuleModulesUsed _ = fail' "wasn't a Module"
+
+checkModuleName :: Source -> Result
+checkModuleName m@(Module{}) = assertEquals "some_module" $ moduleName m
+checkModuleName _ = fail' "wasn't a Module"
+
+checkSmod :: Source -> Result
+checkSmod m@(Module{}) = assertThat $ moduleProducesSmod m
+checkSmod _ = fail' "wasn't a Module"
diff --git a/bootstrap/unit_test/ModuleToCompileInfoTest.hs b/bootstrap/unit_test/ModuleToCompileInfoTest.hs
new file mode 100644
index 0000000..5a1f0a8
--- /dev/null
+++ b/bootstrap/unit_test/ModuleToCompileInfoTest.hs
@@ -0,0 +1,70 @@
+module ModuleToCompileInfoTest
+ ( test
+ )
+where
+
+import BuildModel ( CompileTimeInfo(..)
+ , Source(..)
+ , constructCompileTimeInfo
+ )
+import Hedge ( Result
+ , Test
+ , assertEquals
+ , givenInput
+ , then'
+ , whenTransformed
+ )
+import System.FilePath ( (</>) )
+
+test :: IO (Test ())
+test = return $ givenInput
+ "a module and available modules"
+ (exampleModule, availableModules)
+ [ whenTransformed
+ "its compileTimeInfo is determined"
+ doCompileTimeTransformation
+ [ then' "it stil knows the original source file" checkSourceFileName
+ , then' "it knows what object file will be produced" checkObjectFileName
+ , then' "the mod and smod files are also produced" checkOtherFilesProduced
+ , then' "the direct dependencies are only the available modules used"
+ checkDirectDependencies
+ ]
+ ]
+
+exampleModule :: Source
+exampleModule = Module
+ { moduleSourceFileName = moduleSourceFileName'
+ , moduleObjectFileName = \bd -> bd </> "some_file_somewhere.f90.o"
+ , moduleModulesUsed = ["module1", "module2", "module3"]
+ , moduleName = "some_module"
+ , moduleProducesSmod = True
+ }
+
+moduleSourceFileName' :: FilePath
+moduleSourceFileName' = "some" </> "file" </> "somewhere.f90"
+
+availableModules :: [String]
+availableModules = ["module1", "module3"]
+
+doCompileTimeTransformation :: (Source, [String]) -> CompileTimeInfo
+doCompileTimeTransformation (programSource, otherSources) =
+ constructCompileTimeInfo programSource otherSources "build_dir"
+
+checkSourceFileName :: CompileTimeInfo -> Result
+checkSourceFileName cti =
+ assertEquals moduleSourceFileName' (compileTimeInfoSourceFileName cti)
+
+checkObjectFileName :: CompileTimeInfo -> Result
+checkObjectFileName cti = assertEquals
+ ("build_dir" </> "some_file_somewhere.f90.o")
+ (compileTimeInfoObjectFileProduced cti)
+
+checkOtherFilesProduced :: CompileTimeInfo -> Result
+checkOtherFilesProduced cti = assertEquals
+ ["build_dir" </> "some_module.mod", "build_dir" </> "some_module.smod"]
+ (compileTimeInfoOtherFilesProduced cti)
+
+checkDirectDependencies :: CompileTimeInfo -> Result
+checkDirectDependencies cti = assertEquals
+ ["build_dir" </> "module1.mod", "build_dir" </> "module3.mod"]
+ (compileTimeInfoDirectDependencies cti)
diff --git a/bootstrap/unit_test/ProgramSourceConstructionTest.hs b/bootstrap/unit_test/ProgramSourceConstructionTest.hs
new file mode 100644
index 0000000..6369965
--- /dev/null
+++ b/bootstrap/unit_test/ProgramSourceConstructionTest.hs
@@ -0,0 +1,69 @@
+module ProgramSourceConstructionTest
+ ( test
+ )
+where
+
+import BuildModel ( RawSource(..)
+ , Source(..)
+ , processRawSource
+ )
+import Hedge ( Result
+ , Test
+ , assertEquals
+ , assertThat
+ , fail'
+ , givenInput
+ , then'
+ , whenTransformed
+ )
+import System.FilePath ( (</>) )
+
+test :: IO (Test ())
+test = return $ givenInput
+ "a program"
+ exampleProgram
+ [ whenTransformed
+ "processed to a source"
+ processRawSource
+ [ then' "it is a Program" checkIsProgram
+ , then' "its source file name is the same as the original"
+ checkProgramSourceFileName
+ , then'
+ "its object file name is the 'flattened' path of the source file with '.o' appended"
+ checkProgramObjectFileName
+ , then' "it knows what modules it uses directly" checkProgramModulesUsed
+ ]
+ ]
+
+exampleProgram :: RawSource
+exampleProgram = RawSource programSourceFileName' $ unlines
+ [ "program some_program"
+ , " use module1"
+ , " USE MODULE2"
+ , " implicit none"
+ , " print *, \"Hello, World!\""
+ , "end program"
+ ]
+
+programSourceFileName' :: String
+programSourceFileName' = "some" </> "file" </> "somewhere.f90"
+
+checkIsProgram :: Source -> Result
+checkIsProgram Program{} = assertThat True
+checkIsProgram _ = assertThat False
+
+checkProgramSourceFileName :: Source -> Result
+checkProgramSourceFileName p@(Program{}) =
+ assertEquals programSourceFileName' $ programSourceFileName p
+checkProgramSourceFileName _ = fail' "wasn't a Program"
+
+checkProgramObjectFileName :: Source -> Result
+checkProgramObjectFileName p@(Program{}) =
+ assertEquals ("." </> "some_file_somewhere.f90.o")
+ $ (programObjectFileName p) "."
+checkProgramObjectFileName _ = fail' "wasn't a Program"
+
+checkProgramModulesUsed :: Source -> Result
+checkProgramModulesUsed p@(Program{}) =
+ assertEquals ["module1", "module2"] $ programModulesUsed p
+checkProgramModulesUsed _ = fail' "wasn't a Program"
diff --git a/bootstrap/unit_test/ProgramToCompileInfoTest.hs b/bootstrap/unit_test/ProgramToCompileInfoTest.hs
new file mode 100644
index 0000000..f17a3df
--- /dev/null
+++ b/bootstrap/unit_test/ProgramToCompileInfoTest.hs
@@ -0,0 +1,68 @@
+module ProgramToCompileInfoTest
+ ( test
+ )
+where
+
+import BuildModel ( CompileTimeInfo(..)
+ , Source(..)
+ , constructCompileTimeInfo
+ )
+import Hedge ( Result
+ , Test
+ , assertEmpty
+ , assertEquals
+ , givenInput
+ , then'
+ , whenTransformed
+ )
+import System.FilePath ( (</>) )
+
+test :: IO (Test ())
+test = return $ givenInput
+ "a program and available modules"
+ (exampleProgram, availableModules)
+ [ whenTransformed
+ "its compileTimeInfo is determined"
+ doCompileTimeTransformation
+ [ then' "it still knows the original source file" checkSourceFileName
+ , then' "it knows what object file will be produced" checkObjectFileName
+ , then' "there are no other files produced" checkOtherFilesProduced
+ , then' "the direct dependencies are only the available modules used"
+ checkDirectDependencies
+ ]
+ ]
+
+exampleProgram :: Source
+exampleProgram = Program
+ { programSourceFileName = programSourceFileName'
+ , programObjectFileName = \bd -> bd </> "some_file_somewhere.f90.o"
+ , programModulesUsed = ["module1", "module2", "module3"]
+ }
+
+programSourceFileName' :: FilePath
+programSourceFileName' = "some" </> "file" </> "somewhere.f90"
+
+availableModules :: [String]
+availableModules = ["module1", "module3"]
+
+doCompileTimeTransformation :: (Source, [String]) -> CompileTimeInfo
+doCompileTimeTransformation (programSource, otherSources) =
+ constructCompileTimeInfo programSource otherSources "build_dir"
+
+checkSourceFileName :: CompileTimeInfo -> Result
+checkSourceFileName cti =
+ assertEquals programSourceFileName' (compileTimeInfoSourceFileName cti)
+
+checkObjectFileName :: CompileTimeInfo -> Result
+checkObjectFileName cti = assertEquals
+ ("build_dir" </> "some_file_somewhere.f90.o")
+ (compileTimeInfoObjectFileProduced cti)
+
+checkOtherFilesProduced :: CompileTimeInfo -> Result
+checkOtherFilesProduced cti =
+ assertEmpty (compileTimeInfoOtherFilesProduced cti)
+
+checkDirectDependencies :: CompileTimeInfo -> Result
+checkDirectDependencies cti = assertEquals
+ ["build_dir" </> "module1.mod", "build_dir" </> "module3.mod"]
+ (compileTimeInfoDirectDependencies cti)
diff --git a/bootstrap/unit_test/SubmoduleSourceConstructionTest.hs b/bootstrap/unit_test/SubmoduleSourceConstructionTest.hs
new file mode 100644
index 0000000..d07a6ed
--- /dev/null
+++ b/bootstrap/unit_test/SubmoduleSourceConstructionTest.hs
@@ -0,0 +1,79 @@
+module SubmoduleSourceConstructionTest
+ ( test
+ )
+where
+
+import BuildModel ( RawSource(..)
+ , Source(..)
+ , processRawSource
+ )
+import Hedge ( Result
+ , Test
+ , assertEquals
+ , assertThat
+ , fail'
+ , givenInput
+ , then'
+ , whenTransformed
+ )
+import System.FilePath ( (</>) )
+
+test :: IO (Test ())
+test = return $ givenInput
+ "a submodule"
+ exampleSubmodule
+ [ whenTransformed
+ "processed to a source"
+ processRawSource
+ [ then' "it is a Submodule" checkIsSubmodule
+ , then' "its source file name is the same as the original"
+ checkSubmoduleSourceFileName
+ , then'
+ "its object file name is the 'flattened' path of the source file with '.o' appeneded"
+ checkSubmoduleObjectFileName
+ , then' "it knows what modules it uses directly" checkSubmoduleModulesUsed
+ , then' "it knows its parent's name" checkSubmoduleParentName
+ , then' "it knows its name" checkSubmoduleName
+ ]
+ ]
+
+exampleSubmodule :: RawSource
+exampleSubmodule = RawSource submoduleSourceFileName' $ unlines
+ [ "submodule (some_module:parent) child"
+ , " use module1"
+ , " USE MODULE2"
+ , " implicit none"
+ , "end submodule"
+ ]
+
+submoduleSourceFileName' :: String
+submoduleSourceFileName' = "some" </> "file" </> "somewhere.f90"
+
+checkIsSubmodule :: Source -> Result
+checkIsSubmodule Submodule{} = assertThat True
+checkIsSubmodule _ = assertThat False
+
+checkSubmoduleSourceFileName :: Source -> Result
+checkSubmoduleSourceFileName s@(Submodule{}) =
+ assertEquals submoduleSourceFileName' $ submoduleSourceFileName s
+checkSubmoduleSourceFileName _ = fail' "wasn't a Submodule"
+
+checkSubmoduleObjectFileName :: Source -> Result
+checkSubmoduleObjectFileName s@(Submodule{}) =
+ assertEquals ("." </> "some_file_somewhere.f90.o")
+ $ (submoduleObjectFileName s) "."
+checkSubmoduleObjectFileName _ = fail' "wasn't a Submodule"
+
+checkSubmoduleModulesUsed :: Source -> Result
+checkSubmoduleModulesUsed s@(Submodule{}) =
+ assertEquals ["module1", "module2"] $ submoduleModulesUsed s
+checkSubmoduleModulesUsed _ = fail' "wasn't a Submodule"
+
+checkSubmoduleParentName :: Source -> Result
+checkSubmoduleParentName s@(Submodule{}) =
+ assertEquals "some_module@parent" (submoduleParentName s)
+checkSubmoduleParentName _ = fail' "wasn't a Submodule"
+
+checkSubmoduleName :: Source -> Result
+checkSubmoduleName s@(Submodule{}) = assertEquals "child" $ submoduleName s
+checkSubmoduleName _ = fail' "wasn't a Submodule"
diff --git a/bootstrap/unit_test/SubmoduleToCompileInfoTest.hs b/bootstrap/unit_test/SubmoduleToCompileInfoTest.hs
new file mode 100644
index 0000000..d5d3ad8
--- /dev/null
+++ b/bootstrap/unit_test/SubmoduleToCompileInfoTest.hs
@@ -0,0 +1,75 @@
+module SubmoduleToCompileInfoTest
+ ( test
+ )
+where
+
+import BuildModel ( CompileTimeInfo(..)
+ , Source(..)
+ , constructCompileTimeInfo
+ )
+import Hedge ( Result
+ , Test
+ , assertEquals
+ , givenInput
+ , then'
+ , whenTransformed
+ )
+import System.FilePath ( (</>) )
+
+test :: IO (Test ())
+test = return $ givenInput
+ "a submodule and available modules"
+ (exampleSubmodule, availableModules)
+ [ whenTransformed
+ "its compileTimeInfo is determined"
+ doCompileTimeTransformation
+ [ then' "it still knows the original source file" checkSourceFileName
+ , then' "it knows what object file will be produced" checkObjectFileName
+ , then' "the smod file is also produced" checkOtherFilesProduced
+ , then'
+ "the direct dependencies are the parent smod and the available modules used"
+ checkDirectDependencies
+ ]
+ ]
+
+exampleSubmodule :: Source
+exampleSubmodule = Submodule
+ { submoduleSourceFileName = submoduleSourceFileName'
+ , submoduleObjectFileName = \bd -> bd </> "some_file_somewhere.f90.o"
+ , submoduleModulesUsed = ["module1", "module2", "module3"]
+ , submoduleBaseModuleName = "base_module"
+ , submoduleParentName = "base_module@parent"
+ , submoduleName = "some_submodule"
+ }
+
+submoduleSourceFileName' :: FilePath
+submoduleSourceFileName' = "some" </> "file" </> "somewhere.f90"
+
+availableModules :: [String]
+availableModules = ["module1", "module3"]
+
+doCompileTimeTransformation :: (Source, [String]) -> CompileTimeInfo
+doCompileTimeTransformation (programSource, otherSources) =
+ constructCompileTimeInfo programSource otherSources "build_dir"
+
+checkSourceFileName :: CompileTimeInfo -> Result
+checkSourceFileName cti =
+ assertEquals submoduleSourceFileName' (compileTimeInfoSourceFileName cti)
+
+checkObjectFileName :: CompileTimeInfo -> Result
+checkObjectFileName cti = assertEquals
+ ("build_dir" </> "some_file_somewhere.f90.o")
+ (compileTimeInfoObjectFileProduced cti)
+
+checkOtherFilesProduced :: CompileTimeInfo -> Result
+checkOtherFilesProduced cti = assertEquals
+ ["build_dir" </> "base_module@some_submodule.smod"]
+ (compileTimeInfoOtherFilesProduced cti)
+
+checkDirectDependencies :: CompileTimeInfo -> Result
+checkDirectDependencies cti = assertEquals
+ [ "build_dir" </> "base_module@parent.smod"
+ , "build_dir" </> "module1.mod"
+ , "build_dir" </> "module3.mod"
+ ]
+ (compileTimeInfoDirectDependencies cti)
diff --git a/bootstrap/unit_test/Trimmer.hs b/bootstrap/unit_test/Trimmer.hs
new file mode 100644
index 0000000..4e0f91d
--- /dev/null
+++ b/bootstrap/unit_test/Trimmer.hs
@@ -0,0 +1 @@
+{-# OPTIONS_GHC -F -pgmF hedge-trimmer #-}
diff --git a/ci/run_tests.bat b/ci/run_tests.bat
index 5f455b3..de45f24 100755
--- a/ci/run_tests.bat
+++ b/ci/run_tests.bat
@@ -17,20 +17,44 @@ rmdir fpm_scratch_* /s /q
build\gfortran_debug\app\fpm
if errorlevel 1 exit 1
-cd ..\test\example_packages\hello_world
+cd ..\example_packages\hello_world
if errorlevel 1 exit 1
-..\..\..\fpm\build\gfortran_debug\app\fpm build
+..\..\fpm\build\gfortran_debug\app\fpm build
if errorlevel 1 exit 1
.\build\gfortran_debug\app\hello_world
if errorlevel 1 exit 1
+cd ..\hello_fpm
+if errorlevel 1 exit 1
+
+..\..\fpm\build\gfortran_debug\app\fpm build
+if errorlevel 1 exit 1
+
+.\build\gfortran_debug\app\hello_fpm
+if errorlevel 1 exit 1
+
+
+cd ..\circular_test
+if errorlevel 1 exit 1
+
+..\..\fpm\build\gfortran_debug\app\fpm build
+if errorlevel 1 exit 1
+
+
+cd ..\circular_example
+if errorlevel 1 exit 1
+
+..\..\fpm\build\gfortran_debug\app\fpm build
+if errorlevel 1 exit 1
+
+
cd ..\hello_complex
if errorlevel 1 exit 1
-..\..\..\fpm\build\gfortran_debug\app\fpm build
+..\..\fpm\build\gfortran_debug\app\fpm build
if errorlevel 1 exit 1
.\build\gfortran_debug\app\say_Hello
@@ -49,7 +73,7 @@ if errorlevel 1 exit 1
cd ..\hello_complex_2
if errorlevel 1 exit 1
-..\..\..\fpm\build\gfortran_debug\app\fpm build
+..\..\fpm\build\gfortran_debug\app\fpm build
if errorlevel 1 exit 1
.\build\gfortran_debug\app\say_hello_world
@@ -67,7 +91,7 @@ if errorlevel 1 exit 1
cd ..\auto_discovery_off
if errorlevel 1 exit 1
-..\..\..\fpm\build\gfortran_debug\app\fpm build
+..\..\fpm\build\gfortran_debug\app\fpm build
if errorlevel 1 exit 1
.\build\gfortran_debug\app\auto_discovery_off
@@ -84,7 +108,7 @@ if exist .\build\gfortran_debug\test\unused_test exit /B 1
cd ..\with_c
if errorlevel 1 exit 1
-..\..\..\fpm\build\gfortran_debug\app\fpm build
+..\..\fpm\build\gfortran_debug\app\fpm build
if errorlevel 1 exit 1
.\build\gfortran_debug\app\with_c
@@ -94,14 +118,14 @@ if errorlevel 1 exit 1
cd ..\submodules
if errorlevel 1 exit 1
-..\..\..\fpm\build\gfortran_debug\app\fpm build
+..\..\fpm\build\gfortran_debug\app\fpm build
if errorlevel 1 exit 1
cd ..\program_with_module
if errorlevel 1 exit 1
-..\..\..\fpm\build\gfortran_debug\app\fpm build
+..\..\fpm\build\gfortran_debug\app\fpm build
if errorlevel 1 exit 1
.\build\gfortran_debug\app\Program_with_module
diff --git a/ci/run_tests.sh b/ci/run_tests.sh
index 7568b46..4f293e2 100755
--- a/ci/run_tests.sh
+++ b/ci/run_tests.sh
@@ -10,38 +10,48 @@ fpm test
rm -rf fpm_scratch_*/
build/gfortran_debug/app/fpm
-cd ../test/example_packages/hello_world
-../../../fpm/build/gfortran_debug/app/fpm build
+cd ../example_packages/hello_world
+../../fpm/build/gfortran_debug/app/fpm build
./build/gfortran_debug/app/hello_world
+cd ../hello_fpm
+../../fpm/build/gfortran_debug/app/fpm build
+./build/gfortran_debug/app/hello_fpm
+
+cd ../circular_test
+../../fpm/build/gfortran_debug/app/fpm build
+
+cd ../circular_example
+../../fpm/build/gfortran_debug/app/fpm build
+
cd ../hello_complex
-../../../fpm/build/gfortran_debug/app/fpm build
+../../fpm/build/gfortran_debug/app/fpm build
./build/gfortran_debug/app/say_Hello
./build/gfortran_debug/app/say_goodbye
./build/gfortran_debug/test/greet_test
./build/gfortran_debug/test/farewell_test
cd ../hello_complex_2
-../../../fpm/build/gfortran_debug/app/fpm build
+../../fpm/build/gfortran_debug/app/fpm build
./build/gfortran_debug/app/say_hello_world
./build/gfortran_debug/app/say_goodbye
./build/gfortran_debug/test/greet_test
./build/gfortran_debug/test/farewell_test
cd ../auto_discovery_off
-../../../fpm/build/gfortran_debug/app/fpm build
+../../fpm/build/gfortran_debug/app/fpm build
./build/gfortran_debug/app/auto_discovery_off
./build/gfortran_debug/test/my_test
test ! -x ./build/gfortran_debug/app/unused
test ! -x ./build/gfortran_debug/test/unused_test
cd ../with_c
-../../../fpm/build/gfortran_debug/app/fpm build
+../../fpm/build/gfortran_debug/app/fpm build
./build/gfortran_debug/app/with_c
cd ../submodules
-../../../fpm/build/gfortran_debug/app/fpm build
+../../fpm/build/gfortran_debug/app/fpm build
cd ../program_with_module
-../../../fpm/build/gfortran_debug/app/fpm build
+../../fpm/build/gfortran_debug/app/fpm build
./build/gfortran_debug/app/Program_with_module
diff --git a/test/example_packages/README.md b/example_packages/README.md
index 79fadb1..65f4109 100644
--- a/test/example_packages/README.md
+++ b/example_packages/README.md
@@ -7,11 +7,11 @@ the features demonstrated in each package and which versions of fpm are supporte
| Name | Features | Bootstrap (Haskell) fpm | fpm |
|---------------------|---------------------------------------------------------------|:-----------------------:|:---:|
| auto_discovery_off | Default layout with auto-discovery disabled | N | Y |
-| circular_example | Local path dependency; circular dependency | Y | N |
-| circular_test | Local path dependency; circular dependency | Y | N |
+| circular_example | Local path dependency; circular dependency | Y | Y |
+| circular_test | Local path dependency; circular dependency | Y | Y |
| hello_complex | Non-standard directory layout; multiple tests and executables | Y | Y |
| hello_complex_2 | Auto-discovery of tests and executables with modules | N | Y |
-| hello_fpm | App-only; local path dependency | Y | N |
+| hello_fpm | App-only; local path dependency | Y | Y |
| hello_world | App-only | Y | Y |
| makefile_complex | External build command (makefile); local path dependency | Y | N |
| program_with_module | App-only; module+program in single source file | Y | Y |
diff --git a/test/example_packages/auto_discovery_off/app/main.f90 b/example_packages/auto_discovery_off/app/main.f90
index 8902dc6..8902dc6 100644
--- a/test/example_packages/auto_discovery_off/app/main.f90
+++ b/example_packages/auto_discovery_off/app/main.f90
diff --git a/test/example_packages/auto_discovery_off/app/unused.f90 b/example_packages/auto_discovery_off/app/unused.f90
index 57d8153..57d8153 100644
--- a/test/example_packages/auto_discovery_off/app/unused.f90
+++ b/example_packages/auto_discovery_off/app/unused.f90
diff --git a/test/example_packages/auto_discovery_off/fpm.toml b/example_packages/auto_discovery_off/fpm.toml
index 9a852df..9a852df 100644
--- a/test/example_packages/auto_discovery_off/fpm.toml
+++ b/example_packages/auto_discovery_off/fpm.toml
diff --git a/test/example_packages/auto_discovery_off/test/my_test.f90 b/example_packages/auto_discovery_off/test/my_test.f90
index fd59f9f..fd59f9f 100644
--- a/test/example_packages/auto_discovery_off/test/my_test.f90
+++ b/example_packages/auto_discovery_off/test/my_test.f90
diff --git a/test/example_packages/auto_discovery_off/test/unused_test.f90 b/example_packages/auto_discovery_off/test/unused_test.f90
index 5c42611..5c42611 100644
--- a/test/example_packages/auto_discovery_off/test/unused_test.f90
+++ b/example_packages/auto_discovery_off/test/unused_test.f90
diff --git a/test/example_packages/circular_example/.gitignore b/example_packages/circular_example/.gitignore
index a007fea..a007fea 100644
--- a/test/example_packages/circular_example/.gitignore
+++ b/example_packages/circular_example/.gitignore
diff --git a/test/example_packages/circular_example/fpm.toml b/example_packages/circular_example/fpm.toml
index c524ce5..c524ce5 100644
--- a/test/example_packages/circular_example/fpm.toml
+++ b/example_packages/circular_example/fpm.toml
diff --git a/test/example_packages/circular_example/src/greet_m.f90 b/example_packages/circular_example/src/greet_m.f90
index 2372f9a..2372f9a 100644
--- a/test/example_packages/circular_example/src/greet_m.f90
+++ b/example_packages/circular_example/src/greet_m.f90
diff --git a/test/example_packages/circular_example/test/main.f90 b/example_packages/circular_example/test/main.f90
index 5b7d803..5b7d803 100644
--- a/test/example_packages/circular_example/test/main.f90
+++ b/example_packages/circular_example/test/main.f90
diff --git a/test/example_packages/circular_test/.gitignore b/example_packages/circular_test/.gitignore
index a007fea..a007fea 100644
--- a/test/example_packages/circular_test/.gitignore
+++ b/example_packages/circular_test/.gitignore
diff --git a/test/example_packages/circular_test/fpm.toml b/example_packages/circular_test/fpm.toml
index 56cfa2e..56cfa2e 100644
--- a/test/example_packages/circular_test/fpm.toml
+++ b/example_packages/circular_test/fpm.toml
diff --git a/test/example_packages/circular_test/src/hello_test.f90 b/example_packages/circular_test/src/hello_test.f90
index 5a591c6..5a591c6 100644
--- a/test/example_packages/circular_test/src/hello_test.f90
+++ b/example_packages/circular_test/src/hello_test.f90
diff --git a/test/example_packages/hello_complex/.gitignore b/example_packages/hello_complex/.gitignore
index a007fea..a007fea 100644
--- a/test/example_packages/hello_complex/.gitignore
+++ b/example_packages/hello_complex/.gitignore
diff --git a/test/example_packages/hello_complex/apps/say_goodbye/say_goodbye.f90 b/example_packages/hello_complex/apps/say_goodbye/say_goodbye.f90
index 6966e79..6966e79 100644
--- a/test/example_packages/hello_complex/apps/say_goodbye/say_goodbye.f90
+++ b/example_packages/hello_complex/apps/say_goodbye/say_goodbye.f90
diff --git a/test/example_packages/hello_complex/apps/say_hello/say_Hello.f90 b/example_packages/hello_complex/apps/say_hello/say_Hello.f90
index cf4a742..cf4a742 100644
--- a/test/example_packages/hello_complex/apps/say_hello/say_Hello.f90
+++ b/example_packages/hello_complex/apps/say_hello/say_Hello.f90
diff --git a/test/example_packages/hello_complex/fpm.toml b/example_packages/hello_complex/fpm.toml
index 30ed293..30ed293 100644
--- a/test/example_packages/hello_complex/fpm.toml
+++ b/example_packages/hello_complex/fpm.toml
diff --git a/test/example_packages/hello_complex/source/farewell_m.f90 b/example_packages/hello_complex/source/farewell_m.f90
index fbc45ed..fbc45ed 100644
--- a/test/example_packages/hello_complex/source/farewell_m.f90
+++ b/example_packages/hello_complex/source/farewell_m.f90
diff --git a/test/example_packages/hello_complex/source/greet_m.f90 b/example_packages/hello_complex/source/greet_m.f90
index 38afd08..38afd08 100644
--- a/test/example_packages/hello_complex/source/greet_m.f90
+++ b/example_packages/hello_complex/source/greet_m.f90
diff --git a/test/example_packages/hello_complex/source/subdir/constants.f90 b/example_packages/hello_complex/source/subdir/constants.f90
index 59d6e5f..59d6e5f 100644
--- a/test/example_packages/hello_complex/source/subdir/constants.f90
+++ b/example_packages/hello_complex/source/subdir/constants.f90
diff --git a/test/example_packages/hello_complex/tests/farewell/farewell_test.f90 b/example_packages/hello_complex/tests/farewell/farewell_test.f90
index 0f21b18..0f21b18 100644
--- a/test/example_packages/hello_complex/tests/farewell/farewell_test.f90
+++ b/example_packages/hello_complex/tests/farewell/farewell_test.f90
diff --git a/test/example_packages/hello_complex/tests/greet/greet_test.f90 b/example_packages/hello_complex/tests/greet/greet_test.f90
index 41fa508..41fa508 100644
--- a/test/example_packages/hello_complex/tests/greet/greet_test.f90
+++ b/example_packages/hello_complex/tests/greet/greet_test.f90
diff --git a/test/example_packages/hello_complex_2/.gitignore b/example_packages/hello_complex_2/.gitignore
index a007fea..a007fea 100644
--- a/test/example_packages/hello_complex_2/.gitignore
+++ b/example_packages/hello_complex_2/.gitignore
diff --git a/test/example_packages/hello_complex_2/app/app_mod.f90 b/example_packages/hello_complex_2/app/app_mod.f90
index d69a228..d69a228 100644
--- a/test/example_packages/hello_complex_2/app/app_mod.f90
+++ b/example_packages/hello_complex_2/app/app_mod.f90
diff --git a/test/example_packages/hello_complex_2/app/say_goodbye.f90 b/example_packages/hello_complex_2/app/say_goodbye.f90
index db12cbf..db12cbf 100644
--- a/test/example_packages/hello_complex_2/app/say_goodbye.f90
+++ b/example_packages/hello_complex_2/app/say_goodbye.f90
diff --git a/test/example_packages/hello_complex_2/app/say_hello/app_hello_mod.f90 b/example_packages/hello_complex_2/app/say_hello/app_hello_mod.f90
index 5c426c8..c5795cb 100644
--- a/test/example_packages/hello_complex_2/app/say_hello/app_hello_mod.f90
+++ b/example_packages/hello_complex_2/app/say_hello/app_hello_mod.f90
@@ -1,4 +1,6 @@
module app_hello_mod
implicit none
+integer :: hello_int = 42
+
end module app_hello_mod
diff --git a/test/example_packages/hello_complex_2/app/say_hello/say_Hello.f90 b/example_packages/hello_complex_2/app/say_hello/say_Hello.f90
index 3b69ba7..3b69ba7 100644
--- a/test/example_packages/hello_complex_2/app/say_hello/say_Hello.f90
+++ b/example_packages/hello_complex_2/app/say_hello/say_Hello.f90
diff --git a/test/example_packages/hello_complex_2/fpm.toml b/example_packages/hello_complex_2/fpm.toml
index 28c91d8..28c91d8 100644
--- a/test/example_packages/hello_complex_2/fpm.toml
+++ b/example_packages/hello_complex_2/fpm.toml
diff --git a/test/example_packages/hello_complex_2/src/farewell_m.f90 b/example_packages/hello_complex_2/src/farewell_m.f90
index 9fc75b9..9fc75b9 100644
--- a/test/example_packages/hello_complex_2/src/farewell_m.f90
+++ b/example_packages/hello_complex_2/src/farewell_m.f90
diff --git a/test/example_packages/hello_complex_2/src/greet_m.f90 b/example_packages/hello_complex_2/src/greet_m.f90
index 2372f9a..2372f9a 100644
--- a/test/example_packages/hello_complex_2/src/greet_m.f90
+++ b/example_packages/hello_complex_2/src/greet_m.f90
diff --git a/test/example_packages/hello_complex_2/test/farewell_test.f90 b/example_packages/hello_complex_2/test/farewell_test.f90
index dbe98d6..dbe98d6 100644
--- a/test/example_packages/hello_complex_2/test/farewell_test.f90
+++ b/example_packages/hello_complex_2/test/farewell_test.f90
diff --git a/test/example_packages/hello_complex_2/test/greet_test.f90 b/example_packages/hello_complex_2/test/greet_test.f90
index 38e9be0..38e9be0 100644
--- a/test/example_packages/hello_complex_2/test/greet_test.f90
+++ b/example_packages/hello_complex_2/test/greet_test.f90
diff --git a/test/example_packages/hello_complex_2/test/test_mod.f90 b/example_packages/hello_complex_2/test/test_mod.f90
index edb2626..edb2626 100644
--- a/test/example_packages/hello_complex_2/test/test_mod.f90
+++ b/example_packages/hello_complex_2/test/test_mod.f90
diff --git a/test/example_packages/hello_fpm/.gitignore b/example_packages/hello_fpm/.gitignore
index a007fea..a007fea 100644
--- a/test/example_packages/hello_fpm/.gitignore
+++ b/example_packages/hello_fpm/.gitignore
diff --git a/test/example_packages/hello_fpm/app/main.f90 b/example_packages/hello_fpm/app/main.f90
index 5df6d64..5df6d64 100644
--- a/test/example_packages/hello_fpm/app/main.f90
+++ b/example_packages/hello_fpm/app/main.f90
diff --git a/test/example_packages/hello_fpm/fpm.toml b/example_packages/hello_fpm/fpm.toml
index d94d904..d94d904 100644
--- a/test/example_packages/hello_fpm/fpm.toml
+++ b/example_packages/hello_fpm/fpm.toml
diff --git a/test/example_packages/hello_world/.gitignore b/example_packages/hello_world/.gitignore
index a007fea..a007fea 100644
--- a/test/example_packages/hello_world/.gitignore
+++ b/example_packages/hello_world/.gitignore
diff --git a/test/example_packages/hello_world/app/main.f90 b/example_packages/hello_world/app/main.f90
index d16022b..d16022b 100644
--- a/test/example_packages/hello_world/app/main.f90
+++ b/example_packages/hello_world/app/main.f90
diff --git a/test/example_packages/hello_world/fpm.toml b/example_packages/hello_world/fpm.toml
index b80e8d1..b80e8d1 100644
--- a/test/example_packages/hello_world/fpm.toml
+++ b/example_packages/hello_world/fpm.toml
diff --git a/test/example_packages/makefile_complex/.gitignore b/example_packages/makefile_complex/.gitignore
index a007fea..a007fea 100644
--- a/test/example_packages/makefile_complex/.gitignore
+++ b/example_packages/makefile_complex/.gitignore
diff --git a/test/example_packages/makefile_complex/Makefile b/example_packages/makefile_complex/Makefile
index 497c6b2..497c6b2 100644
--- a/test/example_packages/makefile_complex/Makefile
+++ b/example_packages/makefile_complex/Makefile
diff --git a/test/example_packages/makefile_complex/app/main.f90 b/example_packages/makefile_complex/app/main.f90
index ac9ed51..ac9ed51 100644
--- a/test/example_packages/makefile_complex/app/main.f90
+++ b/example_packages/makefile_complex/app/main.f90
diff --git a/test/example_packages/makefile_complex/fpm.toml b/example_packages/makefile_complex/fpm.toml
index 3282cbe..3282cbe 100644
--- a/test/example_packages/makefile_complex/fpm.toml
+++ b/example_packages/makefile_complex/fpm.toml
diff --git a/test/example_packages/makefile_complex/src/wrapper_mod.f90 b/example_packages/makefile_complex/src/wrapper_mod.f90
index e8028b5..e8028b5 100644
--- a/test/example_packages/makefile_complex/src/wrapper_mod.f90
+++ b/example_packages/makefile_complex/src/wrapper_mod.f90
diff --git a/test/example_packages/program_with_module/app/main.f90 b/example_packages/program_with_module/app/main.f90
index 59441f0..59441f0 100644
--- a/test/example_packages/program_with_module/app/main.f90
+++ b/example_packages/program_with_module/app/main.f90
diff --git a/test/example_packages/program_with_module/fpm.toml b/example_packages/program_with_module/fpm.toml
index bce6aa2..bce6aa2 100644
--- a/test/example_packages/program_with_module/fpm.toml
+++ b/example_packages/program_with_module/fpm.toml
diff --git a/test/example_packages/with_makefile/.gitignore b/example_packages/submodules/.gitignore
index a007fea..a007fea 100644
--- a/test/example_packages/with_makefile/.gitignore
+++ b/example_packages/submodules/.gitignore
diff --git a/test/example_packages/submodules/fpm.toml b/example_packages/submodules/fpm.toml
index cfc3d61..cfc3d61 100644
--- a/test/example_packages/submodules/fpm.toml
+++ b/example_packages/submodules/fpm.toml
diff --git a/test/example_packages/submodules/src/child1.f90 b/example_packages/submodules/src/child1.f90
index dbd0fa5..dbd0fa5 100644
--- a/test/example_packages/submodules/src/child1.f90
+++ b/example_packages/submodules/src/child1.f90
diff --git a/test/example_packages/submodules/src/child2.f90 b/example_packages/submodules/src/child2.f90
index 179cc32..179cc32 100644
--- a/test/example_packages/submodules/src/child2.f90
+++ b/example_packages/submodules/src/child2.f90
diff --git a/test/example_packages/submodules/src/grandchild.f90 b/example_packages/submodules/src/grandchild.f90
index 8c5aa17..8c5aa17 100644
--- a/test/example_packages/submodules/src/grandchild.f90
+++ b/example_packages/submodules/src/grandchild.f90
diff --git a/test/example_packages/submodules/src/parent.f90 b/example_packages/submodules/src/parent.f90
index 570827c..570827c 100644
--- a/test/example_packages/submodules/src/parent.f90
+++ b/example_packages/submodules/src/parent.f90
diff --git a/test/example_packages/with_c/app/main.f90 b/example_packages/with_c/app/main.f90
index 4d3174b..4d3174b 100644
--- a/test/example_packages/with_c/app/main.f90
+++ b/example_packages/with_c/app/main.f90
diff --git a/test/example_packages/with_c/fpm.toml b/example_packages/with_c/fpm.toml
index 97e3110..97e3110 100644
--- a/test/example_packages/with_c/fpm.toml
+++ b/example_packages/with_c/fpm.toml
diff --git a/test/example_packages/with_c/src/c_code.c b/example_packages/with_c/src/c_code.c
index 44604f0..44604f0 100644
--- a/test/example_packages/with_c/src/c_code.c
+++ b/example_packages/with_c/src/c_code.c
diff --git a/test/example_packages/with_c/src/with_c.f90 b/example_packages/with_c/src/with_c.f90
index edd839e..edd839e 100644
--- a/test/example_packages/with_c/src/with_c.f90
+++ b/example_packages/with_c/src/with_c.f90
diff --git a/example_packages/with_makefile/.gitignore b/example_packages/with_makefile/.gitignore
new file mode 100644
index 0000000..a007fea
--- /dev/null
+++ b/example_packages/with_makefile/.gitignore
@@ -0,0 +1 @@
+build/*
diff --git a/test/example_packages/with_makefile/Makefile b/example_packages/with_makefile/Makefile
index 51e72d4..51e72d4 100644
--- a/test/example_packages/with_makefile/Makefile
+++ b/example_packages/with_makefile/Makefile
diff --git a/test/example_packages/with_makefile/fpm.toml b/example_packages/with_makefile/fpm.toml
index 81dd02a..81dd02a 100644
--- a/test/example_packages/with_makefile/fpm.toml
+++ b/example_packages/with_makefile/fpm.toml
diff --git a/test/example_packages/with_makefile/src/hello_makefile.f90 b/example_packages/with_makefile/src/hello_makefile.f90
index 2d4d1a2..2d4d1a2 100644
--- a/test/example_packages/with_makefile/src/hello_makefile.f90
+++ b/example_packages/with_makefile/src/hello_makefile.f90
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90
index 7ab28df..575b654 100644
--- a/fpm/src/fpm.f90
+++ b/fpm/src/fpm.f90
@@ -1,6 +1,5 @@
module fpm
-
-use fpm_strings, only: string_t, str_ends_with
+use fpm_strings, only: string_t, str_ends_with, operator(.in.)
use fpm_backend, only: build_package
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
fpm_run_settings, fpm_install_settings, fpm_test_settings
@@ -14,9 +13,12 @@ use fpm_sources, only: add_executable_sources, add_sources_from_dir, &
resolve_module_dependencies
use fpm_manifest, only : get_package_data, default_executable, &
default_library, package_t, default_test
-use fpm_error, only : error_t
+use fpm_error, only : error_t, fatal_error
use fpm_manifest_test, only : test_t
-use,intrinsic :: iso_fortran_env, only : stderr=>error_unit
+use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
+ & stdout=>output_unit, &
+ & stderr=>error_unit
+use fpm_manifest_dependency, only: dependency_t
implicit none
private
public :: cmd_build, cmd_install, cmd_run, cmd_test
@@ -24,6 +26,121 @@ public :: cmd_build, cmd_install, cmd_run, cmd_test
contains
+recursive subroutine add_libsources_from_package(sources,package_list,package, &
+ package_root,dev_depends,error)
+ ! Discover library sources in a package, recursively including dependencies
+ !
+ type(srcfile_t), allocatable, intent(inout), target :: sources(:)
+ type(string_t), allocatable, intent(inout) :: package_list(:)
+ type(package_t), intent(in) :: package
+ character(*), intent(in) :: package_root
+ logical, intent(in) :: dev_depends
+ type(error_t), allocatable, intent(out) :: error
+
+ ! Add package library sources
+ if (allocated(package%library)) then
+
+ call add_sources_from_dir(sources, join_path(package_root,package%library%source_dir), &
+ FPM_SCOPE_LIB, error=error)
+
+ if (allocated(error)) then
+ return
+ end if
+
+ end if
+
+ ! Add library sources from dependencies
+ if (allocated(package%dependency)) then
+
+ call add_dependencies(package%dependency)
+
+ if (allocated(error)) then
+ return
+ end if
+
+ end if
+
+ ! Add library sources from dev-dependencies
+ if (dev_depends .and. allocated(package%dev_dependency)) then
+
+ call add_dependencies(package%dev_dependency)
+
+ if (allocated(error)) then
+ return
+ end if
+
+ end if
+
+ contains
+
+ subroutine add_dependencies(dependency_list)
+ type(dependency_t), intent(in) :: dependency_list(:)
+
+ integer :: i
+ type(string_t) :: dep_name
+ type(package_t) :: dependency
+
+ character(:), allocatable :: dependency_path
+
+ do i=1,size(dependency_list)
+
+ if (dependency_list(i)%name .in. package_list) then
+ cycle
+ end if
+
+ if (allocated(dependency_list(i)%git)) then
+
+ dependency_path = join_path('build','dependencies',dependency_list(i)%name)
+
+ if (.not.exists(join_path(dependency_path,'fpm.toml'))) then
+ call dependency_list(i)%git%checkout(dependency_path, error)
+ if (allocated(error)) return
+ end if
+
+ else if (allocated(dependency_list(i)%path)) then
+
+ dependency_path = join_path(package_root,dependency_list(i)%path)
+
+ end if
+
+ call get_package_data(dependency, &
+ join_path(dependency_path,"fpm.toml"), error)
+
+ if (allocated(error)) then
+ error%message = 'Error while parsing manifest for dependency package at:'//&
+ new_line('a')//join_path(dependency_path,"fpm.toml")//&
+ new_line('a')//error%message
+ return
+ end if
+
+ if (.not.allocated(dependency%library) .and. &
+ exists(join_path(dependency_path,"src"))) then
+ allocate(dependency%library)
+ dependency%library%source_dir = "src"
+ end if
+
+
+ call add_libsources_from_package(sources,package_list,dependency, &
+ package_root=dependency_path, &
+ dev_depends=.false., error=error)
+
+ if (allocated(error)) then
+ error%message = 'Error while processing sources for dependency package "'//&
+ new_line('a')//dependency%name//'"'//&
+ new_line('a')//error%message
+ return
+ end if
+
+ dep_name%s = dependency_list(i)%name
+ package_list = [package_list, dep_name]
+
+ end do
+
+ end subroutine add_dependencies
+
+end subroutine add_libsources_from_package
+
+
subroutine build_model(model, settings, package, error)
! Constructs a valid fpm model from command line settings and toml manifest
!
@@ -33,8 +150,13 @@ subroutine build_model(model, settings, package, error)
type(error_t), allocatable, intent(out) :: error
integer :: i
+ type(string_t), allocatable :: package_list(:)
+
model%package_name = package%name
+ allocate(package_list(1))
+ package_list(1)%s = package%name
+
! #TODO: Choose flags and output directory based on cli settings & manifest inputs
model%fortran_compiler = 'gfortran'
@@ -96,17 +218,13 @@ subroutine build_model(model, settings, package, error)
endif
- if (allocated(package%library)) then
-
- call add_sources_from_dir(model%sources, package%library%source_dir, &
- FPM_SCOPE_LIB, error=error)
-
- if (allocated(error)) then
- return
- endif
-
+ ! Add library sources, including local dependencies
+ call add_libsources_from_package(model%sources,package_list,package, &
+ package_root='.',dev_depends=.true.,error=error)
+ if (allocated(error)) then
+ return
+ end if
- endif
if(settings%list)then
do i=1,size(model%sources)
write(stderr,'(*(g0,1x))')'fpm::build<INFO>:file expected at',model%sources(i)%file_name, &
diff --git a/fpm/src/fpm/git.f90 b/fpm/src/fpm/git.f90
index 28ae867..187b551 100644
--- a/fpm/src/fpm/git.f90
+++ b/fpm/src/fpm/git.f90
@@ -1,5 +1,6 @@
!> Implementation for interacting with git repositories.
module fpm_git
+ use fpm_error, only: error_t, fatal_error
implicit none
public :: git_target_t
@@ -43,6 +44,9 @@ module fpm_git
contains
+ !> Fetch and checkout in local directory
+ procedure :: checkout
+
!> Show information on instance
procedure :: info
@@ -124,6 +128,54 @@ contains
end function git_target_tag
+ subroutine checkout(self,local_path, error)
+
+ !> Instance of the git target
+ class(git_target_t), intent(in) :: self
+
+ !> Local path to checkout in
+ character(*), intent(in) :: local_path
+
+ !> Error
+ type(error_t), allocatable, intent(out) :: error
+
+ !> git object ref
+ character(:), allocatable :: object
+
+ !> Stat for execute_command_line
+ integer :: stat
+
+ if (allocated(self%object)) then
+ object = self%object
+ else
+ object = 'HEAD'
+ end if
+
+ call execute_command_line("git init "//local_path, exitstat=stat)
+
+ if (stat /= 0) then
+ call fatal_error(error,'Error while initiating git repository for remote dependency')
+ return
+ end if
+
+ call execute_command_line("git -C "//local_path//" fetch "//self%url//&
+ " "//object, exitstat=stat)
+
+ if (stat /= 0) then
+ call fatal_error(error,'Error while fetching git repository for remote dependency')
+ return
+ end if
+
+ call execute_command_line("git -C "//local_path//" checkout -qf FETCH_HEAD", exitstat=stat)
+
+ if (stat /= 0) then
+ call fatal_error(error,'Error while checking out git repository for remote dependency')
+ return
+ end if
+
+ end subroutine checkout
+
+
!> Show information on git target
subroutine info(self, unit, verbosity)
diff --git a/fpm/src/fpm_backend.f90 b/fpm/src/fpm_backend.f90
index 40460d7..d7005bf 100644
--- a/fpm/src/fpm_backend.f90
+++ b/fpm/src/fpm_backend.f90
@@ -3,7 +3,7 @@ module fpm_backend
! Implements the native fpm build backend
use fpm_environment, only: run, get_os_type, OS_WINDOWS
-use fpm_filesystem, only: basename, join_path, exists, mkdir
+use fpm_filesystem, only: basename, dirname, join_path, exists, mkdir
use fpm_model, only: fpm_model_t, srcfile_t, FPM_UNIT_MODULE, &
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
FPM_UNIT_CSOURCE, FPM_UNIT_PROGRAM, &
@@ -113,6 +113,10 @@ recursive subroutine build_source(model,source_file,linking)
object_file = get_object_name(model,source_file%file_name)
+ if (.not.exists(dirname(object_file))) then
+ call mkdir(dirname(object_file))
+ end if
+
call run("gfortran -c " // source_file%file_name // model%fortran_compile_flags &
// " -o " // object_file)
linking = linking // " " // object_file
@@ -145,13 +149,6 @@ function get_object_name(model,source_file_name) result(object_file)
! Exclude first directory level from path
object_file = source_file_name(index(source_file_name,filesep)+1:)
- ! Convert remaining directory separators to underscores
- i = index(object_file,filesep)
- do while(i > 0)
- object_file(i:i) = '_'
- i = index(object_file,filesep)
- end do
-
! Construct full target path
object_file = join_path(model%output_directory, model%package_name, &
object_file//'.o')
diff --git a/fpm/src/fpm_filesystem.f90 b/fpm/src/fpm_filesystem.f90
index d2096f1..4c12314 100644
--- a/fpm/src/fpm_filesystem.f90
+++ b/fpm/src/fpm_filesystem.f90
@@ -215,6 +215,8 @@ subroutine mkdir(dir)
character(len=*), intent(in) :: dir
integer :: stat
+ if (is_dir(dir)) return
+
select case (get_os_type())
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
call execute_command_line('mkdir -p ' // dir, exitstat=stat)
@@ -233,6 +235,11 @@ end subroutine mkdir
recursive subroutine list_files(dir, files, recurse)
+ ! Get file & directory names in directory `dir`.
+ !
+ ! - File/directory names return are relative to cwd, ie. preprended with `dir`
+ ! - Includes files starting with `.` except current directory and parent directory
+ !
character(len=*), intent(in) :: dir
type(string_t), allocatable, intent(out) :: files(:)
logical, intent(in), optional :: recurse
@@ -242,8 +249,7 @@ recursive subroutine list_files(dir, files, recurse)
type(string_t), allocatable :: dir_files(:)
type(string_t), allocatable :: sub_dir_files(:)
- ! Using `inquire` / exists on directories works with gfortran, but not ifort
- if (.not. exists(dir)) then
+ if (.not. is_dir(dir)) then
allocate (files(0))
return
end if
@@ -252,7 +258,7 @@ recursive subroutine list_files(dir, files, recurse)
select case (get_os_type())
case (OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_CYGWIN, OS_SOLARIS, OS_FREEBSD)
- call execute_command_line('ls ' // dir // ' > ' // temp_file, &
+ call execute_command_line('ls -A ' // dir // ' > ' // temp_file, &
exitstat=stat)
case (OS_WINDOWS)
call execute_command_line('dir /b ' // windows_path(dir) // ' > ' // temp_file, &
diff --git a/fpm/src/fpm_sources.f90 b/fpm/src/fpm_sources.f90
index f798276..393c799 100644
--- a/fpm/src/fpm_sources.f90
+++ b/fpm/src/fpm_sources.f90
@@ -6,7 +6,7 @@ use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t, &
FPM_UNIT_CSOURCE, FPM_UNIT_CHEADER, FPM_SCOPE_UNKNOWN, &
FPM_SCOPE_LIB, FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST
-use fpm_filesystem, only: basename, canon_path, dirname, read_lines, list_files
+use fpm_filesystem, only: basename, canon_path, dirname, join_path, read_lines, list_files
use fpm_strings, only: lower, split, str_ends_with, string_t, operator(.in.)
use fpm_manifest_executable, only: executable_t
implicit none
@@ -24,6 +24,33 @@ character(15), parameter :: INTRINSIC_MODULE_NAMES(*) = &
contains
+function parse_source(source_file_path,error) result(source)
+ character(*), intent(in) :: source_file_path
+ type(error_t), allocatable, intent(out) :: error
+ type(srcfile_t) :: source
+
+ if (str_ends_with(lower(source_file_path), ".f90")) then
+
+ source = parse_f_source(source_file_path, error)
+
+ if (source%unit_type == FPM_UNIT_PROGRAM) then
+ source%exe_name = basename(source_file_path,suffix=.false.)
+ end if
+
+ else if (str_ends_with(lower(source_file_path), ".c") .or. &
+ str_ends_with(lower(source_file_path), ".h")) then
+
+ source = parse_c_source(source_file_path,error)
+
+ end if
+
+ if (allocated(error)) then
+ return
+ end if
+
+end function parse_source
+
+
subroutine add_sources_from_dir(sources,directory,scope,with_executables,error)
! Enumerate sources in a directory
!
@@ -33,7 +60,7 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,error)
logical, intent(in), optional :: with_executables
type(error_t), allocatable, intent(out) :: error
- integer :: i, j
+ integer :: i
logical, allocatable :: is_source(:), exclude_source(:)
type(string_t), allocatable :: file_names(:)
type(string_t), allocatable :: src_file_names(:)
@@ -46,13 +73,13 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,error)
if (allocated(sources)) then
allocate(existing_src_files(size(sources)))
do i=1,size(sources)
- existing_src_files(i)%s = sources(i)%file_name
+ existing_src_files(i)%s = canon_path(sources(i)%file_name)
end do
else
allocate(existing_src_files(0))
end if
- is_source = [(.not.(file_names(i)%s .in. existing_src_files) .and. &
+ is_source = [(.not.(canon_path(file_names(i)%s) .in. existing_src_files) .and. &
(str_ends_with(lower(file_names(i)%s), ".f90") .or. &
str_ends_with(lower(file_names(i)%s), ".c") .or. &
str_ends_with(lower(file_names(i)%s), ".h") ),i=1,size(file_names))]
@@ -63,26 +90,8 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,error)
do i = 1, size(src_file_names)
- if (str_ends_with(lower(src_file_names(i)%s), ".f90")) then
-
- dir_sources(i) = parse_f_source(src_file_names(i)%s, error)
-
- if (allocated(error)) then
- return
- end if
-
- end if
-
- if (str_ends_with(lower(src_file_names(i)%s), ".c") .or. &
- str_ends_with(lower(src_file_names(i)%s), ".h")) then
-
- dir_sources(i) = parse_c_source(src_file_names(i)%s,error)
-
- if (allocated(error)) then
- return
- end if
-
- end if
+ dir_sources(i) = parse_source(src_file_names(i)%s,error)
+ if (allocated(error)) return
dir_sources(i)%unit_scope = scope
@@ -93,7 +102,6 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,error)
if (with_executables) then
exclude_source(i) = .false.
- dir_sources(i)%exe_name = basename(src_file_names(i)%s,suffix=.false.)
end if
end if
@@ -122,49 +130,50 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,error)
integer :: i, j
type(string_t), allocatable :: exe_dirs(:)
- logical, allocatable :: include_source(:)
- type(srcfile_t), allocatable :: dir_sources(:)
+ type(srcfile_t) :: exe_source
call get_executable_source_dirs(exe_dirs,executables)
do i=1,size(exe_dirs)
- call add_sources_from_dir(dir_sources,exe_dirs(i)%s, &
- scope, with_executables=.true.,error=error)
+ call add_sources_from_dir(sources,exe_dirs(i)%s, &
+ scope, with_executables=auto_discover,error=error)
if (allocated(error)) then
return
end if
end do
- allocate(include_source(size(dir_sources)))
+ exe_loop: do i=1,size(executables)
- do i = 1, size(dir_sources)
-
- ! Include source by default if not a program or if auto_discover is enabled
- include_source(i) = (dir_sources(i)%unit_type /= FPM_UNIT_PROGRAM) .or. &
- auto_discover
+ ! Check if executable already discovered automatically
+ ! and apply any overrides
+ do j=1,size(sources)
- ! Always include sources specified in fpm.toml
- do j=1,size(executables)
-
- if (basename(dir_sources(i)%file_name,suffix=.true.) == executables(j)%main .and.&
- canon_path(dirname(dir_sources(i)%file_name)) == &
- canon_path(executables(j)%source_dir) ) then
+ if (basename(sources(j)%file_name,suffix=.true.) == executables(i)%main .and.&
+ canon_path(dirname(sources(j)%file_name)) == &
+ canon_path(executables(i)%source_dir) ) then
- include_source(i) = .true.
- dir_sources(i)%exe_name = executables(j)%name
- exit
+ sources(j)%exe_name = executables(i)%name
+ cycle exe_loop
end if
+
end do
- end do
+ ! Add if not already discovered (auto_discovery off)
+ exe_source = parse_source(join_path(executables(i)%source_dir,executables(i)%main),error)
+ exe_source%exe_name = executables(i)%name
+ exe_source%unit_scope = scope
+
+ if (allocated(error)) return
- if (.not.allocated(sources)) then
- sources = pack(dir_sources,include_source)
- else
- sources = [sources, pack(dir_sources,include_source)]
- end if
+ if (.not.allocated(sources)) then
+ sources = [exe_source]
+ else
+ sources = [sources, exe_source]
+ end if
+
+ end do exe_loop
end subroutine add_executable_sources
@@ -291,21 +300,26 @@ function parse_f_source(f_filename,error) result(f_source)
end if
! Process 'INCLUDE' statements
- if (index(adjustl(lower(file_lines(i)%s)),'include') == 1) then
-
- n_include = n_include + 1
+ ic = index(adjustl(lower(file_lines(i)%s)),'include')
+ if ( ic == 1 ) then
+ ic = index(lower(file_lines(i)%s),'include')
+ if (index(adjustl(file_lines(i)%s(ic+7:)),'"') == 1 .or. &
+ index(adjustl(file_lines(i)%s(ic+7:)),"'") == 1 ) then
- if (pass == 2) then
- f_source%include_dependencies(n_include)%s = &
- & split_n(file_lines(i)%s,n=2,delims="'"//'"',stat=stat)
- if (stat /= 0) then
- call file_parse_error(error,f_filename, &
- 'unable to find include file name',i, &
- file_lines(i)%s)
- return
+
+ n_include = n_include + 1
+
+ if (pass == 2) then
+ f_source%include_dependencies(n_include)%s = &
+ & split_n(file_lines(i)%s,n=2,delims="'"//'"',stat=stat)
+ if (stat /= 0) then
+ call file_parse_error(error,f_filename, &
+ 'unable to find include file name',i, &
+ file_lines(i)%s)
+ return
+ end if
end if
end if
-
end if
! Extract name of module if is module
diff --git a/fpm/test/fpm_test/test_source_parsing.f90 b/fpm/test/fpm_test/test_source_parsing.f90
index 0b92bef..d1d3e12 100644
--- a/fpm/test/fpm_test/test_source_parsing.f90
+++ b/fpm/test/fpm_test/test_source_parsing.f90
@@ -198,9 +198,11 @@ contains
write(unit, '(a)') &
& 'program test', &
& ' implicit none', &
- & ' include "included_file.f90"', &
+ & ' include "included_file.f90"', &
+ & ' character(*) :: include_comments', &
+ & ' include_comments = "some comments"', &
& ' contains ', &
- & ' include "second_include.f90"', &
+ & ' include"second_include.f90"', &
& 'end program test'
close(unit)
diff --git a/install.sh b/install.sh
new file mode 100755
index 0000000..862de25
--- /dev/null
+++ b/install.sh
@@ -0,0 +1,33 @@
+#!/bin/sh
+
+set -u # error on use of undefined variable
+set -e # exit on error
+
+install_path="$HOME/.local/bin"
+
+if command -v stack &> /dev/null ; then
+ echo "found stack"
+else
+ echo "Haskell stack not found."
+ echo "Installing Haskell stack to."
+ curl -sSL https://get.haskellstack.org/ | sh
+ if command -v stack &> /dev/null ; then
+ echo "Haskell stack installation successful."
+ else
+ echo "Haskell stack installation unsuccessful."
+ exit 1
+ fi
+fi
+
+if [[ -x "$install_path/fpm" ]]; then
+ echo "Overwriting existing fpm installation in $install_path"
+fi
+
+cd bootstrap
+stack install
+
+if [[ -x "$install_path/fpm" ]]; then
+ echo "fpm installed successfully to $install_path"
+else
+ echo "fpm installation unsuccessful: fpm not found in $install_path"
+fi