summaryrefslogtreecommitdiff
path: root/hadrian/src/Rules/Libffi.hs
blob: 44d6154fc2aad7405ddd3f88560b4e2c46bb8ecb (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
{-# LANGUAGE TypeFamilies #-}

module Rules.Libffi (
    LibffiDynLibs(..),
    needLibffi, askLibffilDynLibs, libffiRules, libffiLibrary, libffiHeaderFiles,
    libffiHeaders, libffiSystemHeaders, libffiName
    ) where

import Hadrian.Utilities

import Packages
import Settings.Builders.Common
import Target
import Utilities

-- | Oracle question type. The oracle returns the list of dynamic
-- libffi library file paths (all but one of which should be symlinks).
newtype LibffiDynLibs = LibffiDynLibs Stage
        deriving (Eq, Show, Hashable, Binary, NFData)
type instance RuleResult LibffiDynLibs = [FilePath]

askLibffilDynLibs :: Stage -> Action [FilePath]
askLibffilDynLibs stage = askOracle (LibffiDynLibs stage)

-- | The path to the dynamic library manifest file. The file contains all file
-- paths to libffi dynamic library file paths.
-- The path is calculated but not `need`ed.
dynLibManifest' :: Monad m => m FilePath -> Stage -> m FilePath
dynLibManifest' getRoot stage = do
    root <- getRoot
    return $ root -/- stageString stage -/- pkgName libffi -/- ".dynamiclibs"

dynLibManifestRules :: Stage -> Rules FilePath
dynLibManifestRules = dynLibManifest' buildRootRules

dynLibManifest :: Stage -> Action FilePath
dynLibManifest = dynLibManifest' buildRoot

-- | Need the (locally built) libffi library.
needLibffi :: Stage -> Action ()
needLibffi stage = do
    manifest <- dynLibManifest stage
    need [manifest]

-- | Context for @libffi@.
libffiContext :: Stage -> Action Context
libffiContext stage = do
    ways <- interpretInContext
            (Context stage libffi (error "libffiContext: way not set"))
            getLibraryWays
    return . Context stage libffi $ if any (wayUnit Dynamic) ways
        then dynamic
        else vanilla

-- | The name of the (locally built) library
libffiName :: Expr String
libffiName = do
    windows <- expr windowsHost
    way <- getWay
    return $ libffiName' windows (Dynamic `wayUnit` way)

-- | The name of the (locally built) library
libffiName' :: Bool -> Bool -> String
libffiName' windows dynamic
    = (if dynamic then "" else "C")
    ++ (if windows then "ffi-6" else "ffi")

libffiLibrary :: FilePath
libffiLibrary = "inst/lib/libffi.a"

libffiHeaderFiles :: [FilePath]
libffiHeaderFiles = ["ffi.h", "ffitarget.h"]

libffiHeaders :: Stage -> Action [FilePath]
libffiHeaders stage = do
    path <- libffiBuildPath stage
    return $ fmap ((path -/- "inst/include") -/-) libffiHeaderFiles

libffiSystemHeaders :: Action [FilePath]
libffiSystemHeaders = do
    ffiIncludeDir <- setting FfiIncludeDir
    return $ fmap (ffiIncludeDir -/-) libffiHeaderFiles

fixLibffiMakefile :: FilePath -> String -> String
fixLibffiMakefile top =
      replace "-MD" "-MMD"
    . replace "@toolexeclibdir@" "$(libdir)"
    . replace "@INSTALL@" ("$(subst ../install-sh," ++ top ++ "/install-sh,@INSTALL@)")

-- TODO: check code duplication w.r.t. ConfCcArgs
configureEnvironment :: Stage -> Action [CmdOption]
configureEnvironment stage = do
    context <- libffiContext stage
    cFlags  <- interpretInContext context $ mconcat
               [ cArgs
               , getStagedSettingList ConfCcArgs ]
    ldFlags <- interpretInContext context ldArgs
    sequence [ builderEnvironment "CC" $ Cc CompileC stage
             , builderEnvironment "CXX" $ Cc CompileC stage
             , builderEnvironment "LD" (Ld stage)
             , builderEnvironment "AR" (Ar Unpack stage)
             , builderEnvironment "NM" Nm
             , builderEnvironment "RANLIB" Ranlib
             , return . AddEnv  "CFLAGS" $ unwords  cFlags ++ " -w"
             , return . AddEnv "LDFLAGS" $ unwords ldFlags ++ " -w" ]

-- Need the libffi archive and `trackAllow` all files in the build directory.
-- As all libffi build files are derived from this archive, we can safely
-- `trackAllow` the libffi build dir. I.e the archive file can be seen as a
-- shallow dependency of the libffi build. This is much simpler than working out
-- the dependencies of each rule (within the build dir).
-- This means changing the archive file forces a clean build of libffi. This
-- seems like a performance issue, but is justified as building libffi is fast
-- and the archive file is rarely changed.
needLibfffiArchive :: FilePath -> Action FilePath
needLibfffiArchive buildPath = do
    top <- topDirectory
    tarball <- unifyPath
                . fromSingleton "Exactly one LibFFI tarball is expected"
                <$> getDirectoryFiles top ["libffi-tarballs/libffi*.tar.gz"]
    need [top -/- tarball]
    trackAllow [buildPath -/- "//*"]
    return tarball

libffiRules :: Rules ()
libffiRules = do
  _ <- addOracleCache $ \ (LibffiDynLibs stage)
                         -> readFileLines =<< dynLibManifest stage
  forM_ [Stage1 ..] $ \stage -> do
    root <- buildRootRules
    let path       = root -/- stageString stage
        libffiPath = path -/- pkgName libffi -/- "build"

    -- We set a higher priority because this rule overlaps with the build rule
    -- for static libraries 'Rules.Library.libraryRules'.
    dynLibMan <- dynLibManifestRules stage
    let topLevelTargets =  [ libffiPath -/- libffiLibrary
                           , dynLibMan
                           ]
    priority 2 $ topLevelTargets &%> \_ -> do
        _ <- needLibfffiArchive libffiPath
        context <- libffiContext stage

        -- Note this build needs the Makefile, triggering the rules bellow.
        build $ target context (Make libffiPath) [] []

        -- Find dynamic libraries.
        dynLibFiles <- do
            windows <- windowsHost
            osx     <- osxHost
            let libffiName'' = libffiName' windows True
            if windows
                then
                    let libffiDll = "lib" ++ libffiName'' ++ ".dll"
                    in return [libffiPath -/- "inst/bin" -/- libffiDll]
                else do
                    let libffiLibPath = libffiPath -/- "inst/lib"
                    dynLibsRelative <- liftIO $ getDirectoryFilesIO
                        libffiLibPath
                        (if osx
                            then ["lib" ++ libffiName'' ++ ".dylib*"]
                            else ["lib" ++ libffiName'' ++ ".so*"])
                    return (fmap (libffiLibPath -/-) dynLibsRelative)

        writeFileLines dynLibMan dynLibFiles
        putSuccess "| Successfully build libffi."

    fmap (libffiPath -/-) ["Makefile.in", "configure" ] &%> \[mkIn, _] -> do
        -- Extract libffi tar file
        context <- libffiContext stage
        removeDirectory libffiPath
        tarball <- needLibfffiArchive libffiPath
        -- Go from 'libffi-3.99999+git20171002+77e130c.tar.gz' to 'libffi-3.99999'
        let libname = takeWhile (/= '+') $ takeFileName tarball

        -- Move extracted directory to libffiPath.
        root <- buildRoot
        removeDirectory (root -/- libname)
        actionFinally (do
            build $ target context (Tar Extract) [tarball] [path]
            moveDirectory (path -/- libname) libffiPath) $
            -- And finally:
            removeFiles (path) [libname <//> "*"]

        top <- topDirectory
        fixFile mkIn (fixLibffiMakefile top)

        files <- liftIO $ getDirectoryFilesIO "." [libffiPath <//> "*"]
        produces files

    fmap (libffiPath -/-) ["Makefile", "config.guess", "config.sub"] &%> \[mk, _, _] -> do
        _ <- needLibfffiArchive libffiPath
        context <- libffiContext stage

        -- This need rule extracts the libffi tar file to libffiPath.
        need [mk <.> "in"]

        -- Configure.
        forM_ ["config.guess", "config.sub"] $ \file -> do
            copyFile file (libffiPath -/- file)
        env <- configureEnvironment stage
        buildWithCmdOptions env $
            target context (Configure libffiPath) [mk <.> "in"] [mk]

        dir   <- setting BuildPlatform
        files <- liftIO $ getDirectoryFilesIO "." [libffiPath -/- dir <//> "*"]
        produces files