Skip to content

Commit 410537b

Browse files
Merge pull request #99 from everythingfunctional/MakefileSupport
Add support for Makefiles and generic build scripts
2 parents f97260e + df531fc commit 410537b

File tree

14 files changed

+249
-39
lines changed

14 files changed

+249
-39
lines changed

PACKAGING.md

Lines changed: 37 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,8 @@ for it to successfully build with the Fortran Package Manager (FPM).
1212
- [Multi-level library](#multi-level-library)
1313
- [Be more explicit](#be-more-explicit)
1414
- [Add some tests](#add-some-tests)
15+
- [Adding dependencies](#adding-dependencies)
16+
- [Custom build scripts](#custom-build-scripts)
1517

1618
## What kind of package can FPM build?
1719

@@ -662,3 +664,38 @@ You can even specify the path to another folder, if for example you've got anoth
662664
fpm package in the same repository. Like this: `helloff = { path = "helloff" }`.
663665
Note that you should *not* specify paths outside of your repository, or things
664666
won't work for your users.
667+
668+
### Custom Build Scripts
669+
670+
If there is something special about your library that makes fpm unable to build
671+
it, you can provide your own build script. fpm will then simply call your
672+
build script to build the library.
673+
674+
To specify a build script to be used, put it in the library section of your
675+
`fpm.toml` file, like:
676+
677+
```toml
678+
[library]
679+
source-dir="src"
680+
build-script="my_build_script"
681+
```
682+
683+
fpm will set the following environment variables to specify some parameters to
684+
the build script.
685+
686+
* `FC` - The Fortran compiler to be used
687+
* `FFLAGS` - The flags that should be passed to the Fortran compiler
688+
* `BUILD_DIR` - Where the compiled files should be placed
689+
* `INCLUDE_DIRS` - The folders where any dependencies can be found, space seperated.
690+
It is then the responsibility of the build script to generate the appropriate
691+
include flags.
692+
693+
Additionally, script will be called with the name of the archive (`*.a` file)
694+
that should be produced as the command line argument.
695+
696+
> Note: If the name of the build script is `Makefile` or ends with `.mk`, then
697+
> the make program will be used to run it. Not the the archive file is explicitly
698+
> specified as the target to be built
699+
700+
> Note: All file and directory names are specified with their full canonical
701+
> path.

package.yaml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,7 @@ dependencies:
2525
- directory
2626
- extra
2727
- filepath
28+
- MissingH
2829
- optparse-applicative
2930
- process
3031
- shake

src/Build.hs

Lines changed: 61 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,8 @@
1+
{-# LANGUAGE MultiWayIf #-}
12
module Build
23
( buildLibrary
34
, buildProgram
5+
, buildWithScript
46
)
57
where
68

@@ -10,7 +12,10 @@ import Data.Char ( isAsciiLower
1012
, isDigit
1113
, toLower
1214
)
13-
import Data.List ( intercalate )
15+
import Data.List ( intercalate
16+
, isSuffixOf
17+
)
18+
import Data.List.Utils ( replace )
1419
import qualified Data.Map as Map
1520
import Data.Maybe ( fromMaybe
1621
, mapMaybe
@@ -42,8 +47,13 @@ import Development.Shake.FilePath ( dropExtension
4247
, (<.>)
4348
, (-<.>)
4449
)
45-
import System.Directory ( makeAbsolute )
50+
import System.Directory ( createDirectoryIfMissing
51+
, makeAbsolute
52+
, withCurrentDirectory
53+
)
54+
import System.Environment ( setEnv )
4655
import System.FilePath ( splitDirectories )
56+
import System.Process ( system )
4757
import Text.ParserCombinators.ReadP ( ReadP
4858
, char
4959
, eof
@@ -359,3 +369,52 @@ digit = satisfy isDigit
359369

360370
underscore :: ReadP Char
361371
underscore = char '_'
372+
373+
buildWithScript
374+
:: String
375+
-> FilePath
376+
-> FilePath
377+
-> FilePath
378+
-> [String]
379+
-> String
380+
-> [FilePath]
381+
-> IO (FilePath)
382+
buildWithScript script projectDirectory buildDirectory compiler flags libraryName otherLibraryDirectories
383+
= do
384+
absoluteBuildDirectory <- makeAbsolute buildDirectory
385+
createDirectoryIfMissing True absoluteBuildDirectory
386+
absoluteLibraryDirectories <- mapM makeAbsolute otherLibraryDirectories
387+
setEnv "FC" compiler
388+
setEnv "FFLAGS" (intercalate " " flags)
389+
setEnv "BUILD_DIR" $ unWindowsPath absoluteBuildDirectory
390+
setEnv
391+
"INCLUDE_DIRS"
392+
(intercalate " " (map unWindowsPath absoluteLibraryDirectories))
393+
let archiveFile =
394+
(unWindowsPath absoluteBuildDirectory)
395+
++ "/lib"
396+
++ libraryName
397+
<.> "a"
398+
withCurrentDirectory
399+
projectDirectory
400+
if
401+
| isMakefile script -> system
402+
("make -f " ++ script ++ " " ++ archiveFile)
403+
| otherwise -> system (script ++ " " ++ archiveFile)
404+
return archiveFile
405+
406+
isMakefile :: String -> Bool
407+
isMakefile script | script == "Makefile" = True
408+
| script == "makefile" = True
409+
| ".mk" `isSuffixOf` script = True
410+
| otherwise = False
411+
412+
unWindowsPath :: String -> String
413+
unWindowsPath = changeSeparators . removeDriveLetter
414+
415+
removeDriveLetter :: String -> String
416+
removeDriveLetter path | ':' `elem` path = (tail . dropWhile (/= ':')) path
417+
| otherwise = path
418+
419+
changeSeparators :: String -> String
420+
changeSeparators = replace "\\" "/"

src/Fpm.hs

Lines changed: 78 additions & 37 deletions
Original file line numberDiff line numberDiff line change
@@ -11,9 +11,13 @@ where
1111

1212
import Build ( buildLibrary
1313
, buildProgram
14+
, buildWithScript
1415
)
1516
import Control.Monad.Extra ( concatMapM )
16-
import Data.List (isSuffixOf, find, nub )
17+
import Data.List ( isSuffixOf
18+
, find
19+
, nub
20+
)
1721
import qualified Data.Map as Map
1822
import qualified Data.Text.IO as TIO
1923
import Development.Shake ( FilePattern
@@ -79,7 +83,7 @@ data AppSettings = AppSettings {
7983
, appSettingsDevDependencies :: (Map.Map String Version)
8084
}
8185

82-
data Library = Library { librarySourceDir :: String }
86+
data Library = Library { librarySourceDir :: String, libraryBuildScript :: Maybe String }
8387

8488
data Executable = Executable {
8589
executableSourceDir :: String
@@ -102,6 +106,7 @@ data DependencyTree = Dependency {
102106
dependencyName :: String
103107
, dependencyPath :: FilePath
104108
, dependencySourcePath :: FilePath
109+
, dependencyBuildScript :: Maybe String
105110
, dependencyDependencies :: [DependencyTree]
106111
}
107112

@@ -117,8 +122,8 @@ start args = do
117122

118123
app :: Arguments -> AppSettings -> IO ()
119124
app args settings = case command' args of
120-
Build -> build settings
121-
Run whichOne -> do
125+
Build -> build settings
126+
Run whichOne -> do
122127
build settings
123128
let buildPrefix = appSettingsBuildPrefix settings
124129
let
@@ -133,13 +138,15 @@ app args settings = case command' args of
133138
case canonicalExecutables of
134139
[] -> putStrLn "No Executables Found"
135140
_ -> case whichOne of
136-
"" -> mapM_ system (map (++ " " ++ commandArguments args) canonicalExecutables)
141+
"" -> mapM_
142+
system
143+
(map (++ " " ++ commandArguments args) canonicalExecutables)
137144
name -> do
138-
case find (name `isSuffixOf`) canonicalExecutables of
139-
Nothing -> putStrLn "Executable Not Found"
140-
Just specified -> do
141-
system (specified ++ " " ++ (commandArguments args))
142-
return ()
145+
case find (name `isSuffixOf`) canonicalExecutables of
146+
Nothing -> putStrLn "Executable Not Found"
147+
Just specified -> do
148+
system (specified ++ " " ++ (commandArguments args))
149+
return ()
143150
Test whichOne -> do
144151
build settings
145152
let buildPrefix = appSettingsBuildPrefix settings
@@ -155,13 +162,15 @@ app args settings = case command' args of
155162
case canonicalExecutables of
156163
[] -> putStrLn "No Tests Found"
157164
_ -> case whichOne of
158-
"" -> mapM_ system (map (++ " " ++ commandArguments args) canonicalExecutables)
165+
"" -> mapM_
166+
system
167+
(map (++ " " ++ commandArguments args) canonicalExecutables)
159168
name -> do
160-
case find (name `isSuffixOf`) canonicalExecutables of
161-
Nothing -> putStrLn "Test Not Found"
162-
Just specified -> do
163-
system (specified ++ " " ++ (commandArguments args))
164-
return ()
169+
case find (name `isSuffixOf`) canonicalExecutables of
170+
Nothing -> putStrLn "Test Not Found"
171+
Just specified -> do
172+
system (specified ++ " " ++ (commandArguments args))
173+
return ()
165174

166175
build :: AppSettings -> IO ()
167176
build settings = do
@@ -183,15 +192,24 @@ build settings = do
183192
{ dependencyName = projectName
184193
, dependencyPath = "."
185194
, dependencySourcePath = librarySourceDir'
195+
, dependencyBuildScript = libraryBuildScript librarySettings
186196
, dependencyDependencies = mainDependencyTrees
187197
}
188-
thisArchive <- buildLibrary librarySourceDir'
189-
[".f90", ".f", ".F", ".F90", ".f95", ".f03"]
190-
(buildPrefix </> projectName)
191-
compiler
192-
flags
193-
projectName
194-
(map fst builtDependencies)
198+
thisArchive <- case libraryBuildScript librarySettings of
199+
Just script -> buildWithScript script
200+
"."
201+
(buildPrefix </> projectName)
202+
compiler
203+
flags
204+
projectName
205+
(map fst builtDependencies)
206+
Nothing -> buildLibrary librarySourceDir'
207+
[".f90", ".f", ".F", ".F90", ".f95", ".f03"]
208+
(buildPrefix </> projectName)
209+
compiler
210+
flags
211+
projectName
212+
(map fst builtDependencies)
195213
return
196214
$ ( (buildPrefix </> projectName, thisArchive) : builtDependencies
197215
, Just thisDependencyTree
@@ -263,13 +281,18 @@ arguments =
263281
(info buildArguments (progDesc "Build the executable"))
264282
)
265283
<*> switch (long "release" <> help "Build in release mode")
266-
<*> strOption (long "args" <> metavar "ARGS" <> value "" <> help "Arguments to pass to executables/tests")
284+
<*> strOption
285+
(long "args" <> metavar "ARGS" <> value "" <> help
286+
"Arguments to pass to executables/tests"
287+
)
267288

268289
runArguments :: Parser Command
269-
runArguments = Run <$> strArgument (metavar "EXE" <> value "" <> help "Which executable to run")
290+
runArguments = Run <$> strArgument
291+
(metavar "EXE" <> value "" <> help "Which executable to run")
270292

271293
testArguments :: Parser Command
272-
testArguments = Test <$> strArgument (metavar "TEST" <> value "" <> help "Which test to run")
294+
testArguments =
295+
Test <$> strArgument (metavar "TEST" <> value "" <> help "Which test to run")
273296

274297
buildArguments :: Parser Command
275298
buildArguments = pure Build
@@ -297,7 +320,12 @@ settingsCodec =
297320
.= tomlSettingsDevDependencies
298321

299322
libraryCodec :: TomlCodec Library
300-
libraryCodec = Library <$> Toml.string "source-dir" .= librarySourceDir
323+
libraryCodec =
324+
Library
325+
<$> Toml.string "source-dir"
326+
.= librarySourceDir
327+
<*> Toml.dioptional (Toml.string "build-script")
328+
.= libraryBuildScript
301329

302330
executableCodec :: TomlCodec Executable
303331
executableCodec =
@@ -419,7 +447,10 @@ getLibrarySettings maybeSettings = case maybeSettings of
419447
Nothing -> do
420448
defaultExists <- doesDirectoryExist "src"
421449
if defaultExists
422-
then return (Just (Library { librarySourceDir = "src" }))
450+
then return
451+
(Just
452+
(Library { librarySourceDir = "src", libraryBuildScript = Nothing })
453+
)
423454
else return Nothing
424455

425456
getExecutableSettings :: [Executable] -> String -> IO [Executable]
@@ -490,6 +521,7 @@ fetchDependencies dependencies = do
490521
{ dependencyName = name
491522
, dependencyPath = path
492523
, dependencySourcePath = path </> (librarySourceDir librarySettings)
524+
, dependencyBuildScript = libraryBuildScript librarySettings
493525
, dependencyDependencies = newDependencies
494526
}
495527
Nothing -> do
@@ -500,7 +532,7 @@ fetchExecutableDependencies
500532
:: (Maybe DependencyTree) -> Map.Map String Version -> IO [DependencyTree]
501533
fetchExecutableDependencies maybeProjectTree dependencies =
502534
case maybeProjectTree of
503-
Just projectTree@(Dependency name _ _ _) ->
535+
Just projectTree@(Dependency name _ _ _ _) ->
504536
if name `Map.member` dependencies {- map contains this project-}
505537
then fmap (projectTree :)
506538
(fetchDependencies (Map.delete name dependencies)) {- fetch the other dependencies and include the project tree in the result -}
@@ -524,6 +556,7 @@ fetchExecutableDependencies maybeProjectTree dependencies =
524556
{ dependencyName = name
525557
, dependencyPath = path
526558
, dependencySourcePath = path </> (librarySourceDir librarySettings)
559+
, dependencyBuildScript = libraryBuildScript librarySettings
527560
, dependencyDependencies = newDependencies
528561
}
529562
Nothing -> do
@@ -573,18 +606,26 @@ buildDependencies buildPrefix compiler flags dependencies = do
573606

574607
buildDependency
575608
:: String -> String -> [String] -> DependencyTree -> IO [(FilePath, FilePath)]
576-
buildDependency buildPrefix compiler flags (Dependency name path sourcePath dependencies)
609+
buildDependency buildPrefix compiler flags (Dependency name path sourcePath mBuildScript dependencies)
577610
= do
578611
transitiveDependencies <- buildDependencies buildPrefix
579612
compiler
580613
flags
581614
dependencies
582615
let buildPath = buildPrefix </> name
583-
thisArchive <- buildLibrary sourcePath
584-
[".f90", ".f", ".F", ".F90", ".f95", ".f03"]
585-
buildPath
586-
compiler
587-
flags
588-
name
589-
(map fst transitiveDependencies)
616+
thisArchive <- case mBuildScript of
617+
Just script -> buildWithScript script
618+
path
619+
buildPath
620+
compiler
621+
flags
622+
name
623+
(map fst transitiveDependencies)
624+
Nothing -> buildLibrary sourcePath
625+
[".f90", ".f", ".F", ".F90", ".f95", ".f03"]
626+
buildPath
627+
compiler
628+
flags
629+
name
630+
(map fst transitiveDependencies)
590631
return $ (buildPath, thisArchive) : transitiveDependencies

test/Spec.hs

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,8 @@ main = do
1313
testHelloComplex
1414
testHelloFpm
1515
testCircular
16+
testWithMakefile
17+
testMakefileComplex
1618

1719
testHelloWorld :: IO ()
1820
testHelloWorld =
@@ -29,3 +31,11 @@ testHelloFpm =
2931
testCircular :: IO ()
3032
testCircular =
3133
withCurrentDirectory (example_path </> "circular_example") $ start $ Arguments (Test "") False ""
34+
35+
testWithMakefile :: IO ()
36+
testWithMakefile =
37+
withCurrentDirectory (example_path </> "with_makefile") $ start $ Arguments (Build) False ""
38+
39+
testMakefileComplex :: IO ()
40+
testMakefileComplex =
41+
withCurrentDirectory (example_path </> "makefile_complex") $ start $ Arguments (Run "") False ""
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
build/*

0 commit comments

Comments
 (0)