Skip to content
Merged
Show file tree
Hide file tree
Changes from 3 commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
31 changes: 31 additions & 0 deletions PACKAGING.md
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,8 @@ for it to successfully build with the Fortran Package Manager (FPM).
- [Multi-level library](#multi-level-library)
- [Be more explicit](#be-more-explicit)
- [Add some tests](#add-some-tests)
- [Adding dependencies](#adding-dependencies)
- [Custom build scripts](#custom-build-scripts)

## What kind of package can FPM build?

Expand Down Expand Up @@ -662,3 +664,32 @@ You can even specify the path to another folder, if for example you've got anoth
fpm package in the same repository. Like this: `helloff = { path = "helloff" }`.
Note that you should *not* specify paths outside of your repository, or things
won't work for your users.

### Custom Build Scripts

If there is something special about your library that makes fpm unable to build
it, you can provide your own build script. fpm will then simply call your
build script to build the library.

To specify a build script to be used, put it in the library section of your
`fpm.toml` file, like:

```toml
[library]
source-dir="src"
build-script="my_build_script"
```

fpm will set the following environment variables to specify some parameters to
the build script.

* `FC` - The Fortran compiler to be used
* `FFLAGS` - The flags that should be passed to the Fortran compiler
* `BUILD_DIR` - Where the compiled files should be placed
* `INCLUDE_DIRS` - The folders where any dependencies can be found
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

The trailing 'S' implies multiple folders can be specified - is this done in a system-dependent manner using colon/semicolon separators? If so, it's worth mentioning that here. (I had thought multiple include paths had to be specified with multiple -I flags.)

Copy link
Member Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

They are space separated. So yes, that should be mentioned here, and it is then necessary for your build script to turn this list into the appropriate flags for the compiler(s). I'll add this info.


Additionally, script will be called with the name of the archive (`*.a` file)
that should be produced as the command line argument.
Comment on lines +693 to +694
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Is this a full path to the archive file including BUILD_DIR or just the filename?
Perhaps worth mentioning explicitly that this is only for scripts not Makefiles to avoid confusion.

Copy link
Member Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Yes, it is the full path. And it actually is also for Makefiles. This is the target specified, so your Makefile doesn't necessarily have to have the library as the default target.

Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Ah I see, that makes a lot of sense. I would suggest also stating that explicitly in the following section about invoking make.


> Note: If the name of the build script is `Makefile` or ends with `.mk`, then
> the make program will be used to run it.
1 change: 1 addition & 0 deletions package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,7 @@ dependencies:
- directory
- extra
- filepath
- MissingH
- optparse-applicative
- process
- shake
Expand Down
50 changes: 48 additions & 2 deletions src/Build.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
{-# LANGUAGE MultiWayIf #-}
module Build
( buildLibrary
, buildProgram
, buildWithScript
)
where

Expand All @@ -10,7 +12,10 @@ import Data.Char ( isAsciiLower
, isDigit
, toLower
)
import Data.List ( intercalate )
import Data.List ( intercalate
, isSuffixOf
)
import Data.List.Utils (replace)
import qualified Data.Map as Map
import Data.Maybe ( fromMaybe
, mapMaybe
Expand Down Expand Up @@ -42,8 +47,13 @@ import Development.Shake.FilePath ( dropExtension
, (<.>)
, (-<.>)
)
import System.Directory ( makeAbsolute )
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
Expand Down Expand Up @@ -359,3 +369,39 @@ digit = satisfy isDigit

underscore :: ReadP Char
underscore = char '_'

buildWithScript
:: String
-> FilePath
-> FilePath
-> FilePath
-> [String]
-> String
-> [FilePath]
-> IO (FilePath)
buildWithScript script projectDirectory buildDirectory compiler flags libraryName otherLibraryDirectories
= do
absoluteBuildDirectory <- makeAbsolute buildDirectory
createDirectoryIfMissing True absoluteBuildDirectory
absoluteLibraryDirectories <- mapM makeAbsolute otherLibraryDirectories
setEnv "FC" compiler
setEnv "FFLAGS" (intercalate " " flags)
setEnv "BUILD_DIR" (escapeColon absoluteBuildDirectory)
setEnv "INCLUDE_DIRS" (intercalate " " absoluteLibraryDirectories)
let archiveFile = absoluteBuildDirectory </> "lib" ++ libraryName <.> "a"
withCurrentDirectory
projectDirectory
if
| isMakefile script -> system
("make -f " ++ script ++ " " ++ archiveFile)
| otherwise -> system (script ++ " " ++ archiveFile)
return archiveFile

isMakefile :: String -> Bool
isMakefile script | script == "Makefile" = True
| script == "makefile" = True
| ".mk" `isSuffixOf` script = True
| otherwise = False

escapeColon :: String -> String
escapeColon = replace ":" "\\:"
115 changes: 78 additions & 37 deletions src/Fpm.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,9 +11,13 @@ where

import Build ( buildLibrary
, buildProgram
, buildWithScript
)
import Control.Monad.Extra ( concatMapM )
import Data.List (isSuffixOf, find, nub )
import Data.List ( isSuffixOf
, find
, nub
)
import qualified Data.Map as Map
import qualified Data.Text.IO as TIO
import Development.Shake ( FilePattern
Expand Down Expand Up @@ -79,7 +83,7 @@ data AppSettings = AppSettings {
, appSettingsDevDependencies :: (Map.Map String Version)
}

data Library = Library { librarySourceDir :: String }
data Library = Library { librarySourceDir :: String, libraryBuildScript :: Maybe String }

data Executable = Executable {
executableSourceDir :: String
Expand All @@ -102,6 +106,7 @@ data DependencyTree = Dependency {
dependencyName :: String
, dependencyPath :: FilePath
, dependencySourcePath :: FilePath
, dependencyBuildScript :: Maybe String
, dependencyDependencies :: [DependencyTree]
}

Expand All @@ -117,8 +122,8 @@ start args = do

app :: Arguments -> AppSettings -> IO ()
app args settings = case command' args of
Build -> build settings
Run whichOne -> do
Build -> build settings
Run whichOne -> do
build settings
let buildPrefix = appSettingsBuildPrefix settings
let
Expand All @@ -133,13 +138,15 @@ app args settings = case command' args of
case canonicalExecutables of
[] -> putStrLn "No Executables Found"
_ -> case whichOne of
"" -> mapM_ system (map (++ " " ++ commandArguments args) canonicalExecutables)
"" -> mapM_
system
(map (++ " " ++ commandArguments args) canonicalExecutables)
name -> do
case find (name `isSuffixOf`) canonicalExecutables of
Nothing -> putStrLn "Executable Not Found"
Just specified -> do
system (specified ++ " " ++ (commandArguments args))
return ()
case find (name `isSuffixOf`) canonicalExecutables of
Nothing -> putStrLn "Executable Not Found"
Just specified -> do
system (specified ++ " " ++ (commandArguments args))
return ()
Test whichOne -> do
build settings
let buildPrefix = appSettingsBuildPrefix settings
Expand All @@ -155,13 +162,15 @@ app args settings = case command' args of
case canonicalExecutables of
[] -> putStrLn "No Tests Found"
_ -> case whichOne of
"" -> mapM_ system (map (++ " " ++ commandArguments args) canonicalExecutables)
"" -> mapM_
system
(map (++ " " ++ commandArguments args) canonicalExecutables)
name -> do
case find (name `isSuffixOf`) canonicalExecutables of
Nothing -> putStrLn "Test Not Found"
Just specified -> do
system (specified ++ " " ++ (commandArguments args))
return ()
case find (name `isSuffixOf`) canonicalExecutables of
Nothing -> putStrLn "Test Not Found"
Just specified -> do
system (specified ++ " " ++ (commandArguments args))
return ()

build :: AppSettings -> IO ()
build settings = do
Expand All @@ -183,15 +192,24 @@ build settings = do
{ dependencyName = projectName
, dependencyPath = "."
, dependencySourcePath = librarySourceDir'
, dependencyBuildScript = libraryBuildScript librarySettings
, dependencyDependencies = mainDependencyTrees
}
thisArchive <- buildLibrary librarySourceDir'
[".f90", ".f", ".F", ".F90", ".f95", ".f03"]
(buildPrefix </> projectName)
compiler
flags
projectName
(map fst builtDependencies)
thisArchive <- case libraryBuildScript librarySettings of
Just script -> buildWithScript script
"."
(buildPrefix </> projectName)
compiler
flags
projectName
(map fst builtDependencies)
Nothing -> buildLibrary librarySourceDir'
[".f90", ".f", ".F", ".F90", ".f95", ".f03"]
(buildPrefix </> projectName)
compiler
flags
projectName
(map fst builtDependencies)
return
$ ( (buildPrefix </> projectName, thisArchive) : builtDependencies
, Just thisDependencyTree
Expand Down Expand Up @@ -263,13 +281,18 @@ arguments =
(info buildArguments (progDesc "Build the executable"))
)
<*> switch (long "release" <> help "Build in release mode")
<*> strOption (long "args" <> metavar "ARGS" <> value "" <> help "Arguments to pass to executables/tests")
<*> strOption
(long "args" <> metavar "ARGS" <> value "" <> help
"Arguments to pass to executables/tests"
)

runArguments :: Parser Command
runArguments = Run <$> strArgument (metavar "EXE" <> value "" <> help "Which executable to run")
runArguments = Run <$> strArgument
(metavar "EXE" <> value "" <> help "Which executable to run")

testArguments :: Parser Command
testArguments = Test <$> strArgument (metavar "TEST" <> value "" <> help "Which test to run")
testArguments =
Test <$> strArgument (metavar "TEST" <> value "" <> help "Which test to run")

buildArguments :: Parser Command
buildArguments = pure Build
Expand Down Expand Up @@ -297,7 +320,12 @@ settingsCodec =
.= tomlSettingsDevDependencies

libraryCodec :: TomlCodec Library
libraryCodec = Library <$> Toml.string "source-dir" .= librarySourceDir
libraryCodec =
Library
<$> Toml.string "source-dir"
.= librarySourceDir
<*> Toml.dioptional (Toml.string "build-script")
.= libraryBuildScript

executableCodec :: TomlCodec Executable
executableCodec =
Expand Down Expand Up @@ -419,7 +447,10 @@ getLibrarySettings maybeSettings = case maybeSettings of
Nothing -> do
defaultExists <- doesDirectoryExist "src"
if defaultExists
then return (Just (Library { librarySourceDir = "src" }))
then return
(Just
(Library { librarySourceDir = "src", libraryBuildScript = Nothing })
)
else return Nothing

getExecutableSettings :: [Executable] -> String -> IO [Executable]
Expand Down Expand Up @@ -490,6 +521,7 @@ fetchDependencies dependencies = do
{ dependencyName = name
, dependencyPath = path
, dependencySourcePath = path </> (librarySourceDir librarySettings)
, dependencyBuildScript = libraryBuildScript librarySettings
, dependencyDependencies = newDependencies
}
Nothing -> do
Expand All @@ -500,7 +532,7 @@ fetchExecutableDependencies
:: (Maybe DependencyTree) -> Map.Map String Version -> IO [DependencyTree]
fetchExecutableDependencies maybeProjectTree dependencies =
case maybeProjectTree of
Just projectTree@(Dependency name _ _ _) ->
Just projectTree@(Dependency name _ _ _ _) ->
if name `Map.member` dependencies {- map contains this project-}
then fmap (projectTree :)
(fetchDependencies (Map.delete name dependencies)) {- fetch the other dependencies and include the project tree in the result -}
Expand All @@ -524,6 +556,7 @@ fetchExecutableDependencies maybeProjectTree dependencies =
{ dependencyName = name
, dependencyPath = path
, dependencySourcePath = path </> (librarySourceDir librarySettings)
, dependencyBuildScript = libraryBuildScript librarySettings
, dependencyDependencies = newDependencies
}
Nothing -> do
Expand Down Expand Up @@ -573,18 +606,26 @@ buildDependencies buildPrefix compiler flags dependencies = do

buildDependency
:: String -> String -> [String] -> DependencyTree -> IO [(FilePath, FilePath)]
buildDependency buildPrefix compiler flags (Dependency name path sourcePath dependencies)
buildDependency buildPrefix compiler flags (Dependency name path sourcePath mBuildScript dependencies)
= do
transitiveDependencies <- buildDependencies buildPrefix
compiler
flags
dependencies
let buildPath = buildPrefix </> name
thisArchive <- buildLibrary sourcePath
[".f90", ".f", ".F", ".F90", ".f95", ".f03"]
buildPath
compiler
flags
name
(map fst transitiveDependencies)
thisArchive <- case mBuildScript of
Just script -> buildWithScript script
path
buildPath
compiler
flags
name
(map fst transitiveDependencies)
Nothing -> buildLibrary sourcePath
[".f90", ".f", ".F", ".F90", ".f95", ".f03"]
buildPath
compiler
flags
name
(map fst transitiveDependencies)
return $ (buildPath, thisArchive) : transitiveDependencies
10 changes: 10 additions & 0 deletions test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,8 @@ main = do
testHelloComplex
testHelloFpm
testCircular
testWithMakefile
testMakefileComplex

testHelloWorld :: IO ()
testHelloWorld =
Expand All @@ -29,3 +31,11 @@ testHelloFpm =
testCircular :: IO ()
testCircular =
withCurrentDirectory (example_path </> "circular_example") $ start $ Arguments (Test "") False ""

testWithMakefile :: IO ()
testWithMakefile =
withCurrentDirectory (example_path </> "with_makefile") $ start $ Arguments (Build) False ""

testMakefileComplex :: IO ()
testMakefileComplex =
withCurrentDirectory (example_path </> "makefile_complex") $ start $ Arguments (Run "") False ""
1 change: 1 addition & 0 deletions test/example_packages/makefile_complex/.gitignore
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
build/*
9 changes: 9 additions & 0 deletions test/example_packages/makefile_complex/Makefile
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
INCLUDE_FLAGS = $(addprefix -I,$(INCLUDE_DIRS))

$(BUILD_DIR)/libmakefile_complex.a: $(BUILD_DIR)/wrapper_mod.o
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I think we need to prefix all the environment variables with FPM_, so:

  • FPM_INCLUDE_FLAGS
  • FPM_BUILD_DIR

etc.

Copy link
Member Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

The ones I used are actually the standard environment variables for Makefiles. You (almost) can use an empty Makefile and these would actually work. We can use prefixed variables, but it's one extra difference from what a lot of people will already have and be used to.

Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

This seems fine to me - FC and FFLAGS are standard Makefile variables - and I think we should be minimising the amount of changes people have to do to their Makefiles for compatibility.

ar rs $(@) $(^)

$(BUILD_DIR)/wrapper_mod.mod: src/wrapper_mod.f90

$(BUILD_DIR)/wrapper_mod.o: src/wrapper_mod.f90
$(FC) -c -J$(BUILD_DIR) $(INCLUDE_FLAGS) $(FFLAGS) -o $(@) $(<)
7 changes: 7 additions & 0 deletions test/example_packages/makefile_complex/app/main.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
program makefile_complex
use wrapper_mod, only: do_stuff

implicit none

call do_stuff
end program makefile_complex
Loading