1-------------------------------------------------------------------------
2-- Copyright (c) 2007-2011, 2012, 2015 ETH Zurich.
3-- All rights reserved.
4--
5-- This file is distributed under the terms in the attached LICENSE file.
6-- If you do not find this file, copies can be found by writing to:-
7-- ETH Zurich D-INFK CAB F.78, Universitaetstr 6, CH-8092 Zurich.
8-- Attn: Systems Group.
9--
10-- Basic Hake rule definitions and combinators
11--
12--------------------------------------------------------------------------
13
14module RuleDefs where
15import Data.List (intersect, isSuffixOf, union, (\\), nub, sortBy, elemIndex)
16import Data.Maybe (fromMaybe)
17import System.FilePath
18import qualified X86_64
19import qualified K1om
20import qualified X86_32
21import qualified ARMv7
22import qualified ARMv8
23import HakeTypes
24import qualified Args
25import qualified Config
26import TreeDB
27
28import Debug.Trace
29-- enable debug spew
30-- should we move this to Config.hs? -AB
31debugFlag = False
32
33--
34-- Is a token to be displayed in a rule?
35--
36inRule :: RuleToken -> Bool
37inRule (Dep _ _ _) = False
38inRule (PreDep _ _ _) = False
39inRule (Target _ _) = False
40inRule _ = True
41
42--
43-- Look for a set of files: this is called using the "find" combinator
44--
45withSuffix :: TreeDB -> String -> String -> [String]
46withSuffix srcDB hakepath extension =
47    map (\f -> "/" </> f) $
48        fromMaybe [] $ tdbByDirExt (takeDirectory hakepath) extension srcDB
49
50withSuffices :: TreeDB -> String -> [String] -> [String]
51withSuffices srcDB hakepath extensions =
52    map (\f -> "/" </> f) $
53        fromMaybe [] $ tdbByDirExts (takeDirectory hakepath) extensions srcDB
54
55--
56-- Find files with a given suffix in a given dir
57--
58inDir :: TreeDB -> String -> String -> String -> [String]
59inDir srcDB hakepath dir extension =
60    map (\f -> "/" </> f) $
61        fromMaybe [] $
62            tdbByDirExt (dropTrailingPathSeparator $ normalise $
63                            takeDirectory hakepath </> dir)
64                        extension srcDB
65
66cInDir :: TreeDB -> String -> String -> [String]
67cInDir tdb tf dir = inDir tdb tf dir ".c"
68
69cxxInDir :: TreeDB -> String -> String -> [String]
70cxxInDir tdb tf dir = (inDir tdb tf dir ".cpp") ++ (inDir tdb tf dir ".cc")
71
72sInDir :: TreeDB -> String -> String -> [String]
73sInDir tdb tf dir = inDir tdb tf dir ".S"
74
75-------------------------------------------------------------------------
76--
77-- Architecture specific definitions
78--
79-------------------------------------------------------------------------
80
81options :: String -> Options
82options "x86_64" = X86_64.options
83options "k1om" = K1om.options
84options "x86_32" = X86_32.options
85options "armv7" = ARMv7.options
86options "armv8" = ARMv8.options
87options s = error $ "Unknown architecture " ++ s
88
89kernelCFlags "x86_64" = X86_64.kernelCFlags
90kernelCFlags "k1om" = K1om.kernelCFlags
91kernelCFlags "x86_32" = X86_32.kernelCFlags
92kernelCFlags "armv7" = ARMv7.kernelCFlags
93kernelCFlags "armv8" = ARMv8.kernelCFlags
94kernelCFlags s = error $ "Unknown architecture " ++ s
95
96kernelLdFlags "x86_64" = X86_64.kernelLdFlags
97kernelLdFlags "k1om" = K1om.kernelLdFlags
98kernelLdFlags "x86_32" = X86_32.kernelLdFlags
99kernelLdFlags "armv7" = ARMv7.kernelLdFlags
100kernelLdFlags "armv8" = ARMv8.kernelLdFlags
101kernelLdFlags s = error $ "Unknown architecture " ++ s
102
103archFamily :: String -> String
104archFamily arch = optArchFamily (options arch)
105
106-------------------------------------------------------------------------
107--
108-- Options for compiling the kernel, which is special
109--
110-------------------------------------------------------------------------
111
112kernelOptIncludes :: String -> [ RuleToken ]
113kernelOptIncludes arch
114    | arch == "k1om"  = K1om.kernelOptIncludes
115    | otherwise = [ ]
116
117kernelIncludes arch = [ NoDep BuildTree arch f | f <- [
118                    "/include" ]]
119                 ++
120                 [ NoDep SrcTree "src" f | f <- [
121                    "/kernel/include/arch" </> arch,
122                    "/kernel/include/arch" </> archFamily arch,
123                    "/kernel/include",
124                    "/include",
125                    "/include/arch" </> archFamily arch,
126                    "/include/target" </> archFamily arch]]
127                 ++ kernelOptIncludes arch
128
129kernelOptions arch = Options {
130            optArch = arch,
131            optArchFamily = archFamily arch,
132            optFlags = kernelCFlags arch,
133            optCxxFlags = [],
134            optDefines = (optDefines (options arch)) ++ [ Str "-DIN_KERNEL",
135                Str ("-DCONFIG_SCHEDULER_" ++ (show Config.scheduler)),
136                Str ("-DCONFIG_TIMESLICE=" ++ (show Config.timeslice)) ],
137            optIncludes = kernelIncludes arch,
138            optDependencies =
139                [ Dep InstallTree arch "/include/errors/errno.h",
140                  Dep InstallTree arch "/include/barrelfish_kpi/capbits.h",
141                  Dep InstallTree arch "/include/asmoffsets.h",
142                  Dep InstallTree arch "/include/trace_definitions/trace_defs.h" ],
143            optLdFlags = kernelLdFlags arch,
144            optLdCxxFlags = [],
145            optLibs = [],
146            optCxxLibs = [],
147            optSuffix = [],
148            optInterconnectDrivers = [],
149            optFlounderBackends = [],
150            extraFlags = [],
151            extraCxxFlags = [],
152            extraDefines = [],
153            extraIncludes = [],
154            extraDependencies = [],
155            extraLdFlags = [],
156            optInstallPath = OptionsPath {
157                optPathBin = "/sbin",
158                optPathLib = "/lib"
159            }
160          }
161
162
163-------------------------------------------------------------------------
164--
165-- IMPORTANT: This section contains extraction of functions from the
166-- relevant architecture module.  The names and types should be
167-- exactly the same as in the architecture.hs file.  This section
168-- should not contain any logic; ony architecture extraction.
169--
170--------------------------------------------------------------------------
171
172--
173-- First, the default C compiler for an architecture
174--
175
176compiler :: Options -> String
177compiler opts
178    | optArch opts == "x86_64"  = X86_64.compiler
179    | optArch opts == "k1om"    = K1om.compiler
180    | optArch opts == "x86_32"  = X86_32.compiler
181    | optArch opts == "armv7" = ARMv7.compiler
182    | optArch opts == "armv8" = ARMv8.compiler
183
184cCompiler :: Options -> String -> String -> String -> [ RuleToken ]
185cCompiler opts phase src obj
186    | optArch opts == "x86_64"  = X86_64.cCompiler opts phase src obj
187    | optArch opts == "k1om"    = K1om.cCompiler opts phase src obj
188    | optArch opts == "x86_32"  = X86_32.cCompiler opts phase src obj
189    | optArch opts == "armv7" = ARMv7.cCompiler opts phase src obj
190    | optArch opts == "armv8" = ARMv8.cCompiler opts phase src obj
191    | otherwise = [ ErrorMsg ("no C compiler for " ++ (optArch opts)) ]
192
193cPreprocessor :: Options -> String -> String -> String -> [ RuleToken ]
194cPreprocessor opts phase src obj
195    | otherwise = [ ErrorMsg ("no C preprocessor for " ++ (optArch opts)) ]
196
197--
198-- C++ compiler, where supported
199--
200cxxCompiler :: Options -> String -> String -> String -> [ RuleToken ]
201cxxCompiler opts phase src obj
202    | optArch opts == "x86_64"  = X86_64.cxxCompiler opts phase src obj
203    | optArch opts == "k1om"  = K1om.cxxCompiler opts phase src obj
204    | otherwise = [ ErrorMsg ("no C++ compiler for " ++ (optArch opts)) ]
205
206
207--
208-- makeDepend step; note that obj can be whatever the intended output is
209--
210makeDepend :: Options -> String -> String -> String -> String -> [ RuleToken ]
211makeDepend opts phase src obj depfile
212    | optArch opts == "x86_64" =
213        X86_64.makeDepend opts phase src obj depfile
214    | optArch opts == "k1om" =
215        K1om.makeDepend opts phase src obj depfile
216    | optArch opts == "x86_32" =
217        X86_32.makeDepend opts phase src obj depfile
218    | optArch opts == "armv7" =
219        ARMv7.makeDepend opts phase src obj depfile
220    | optArch opts == "armv8" =
221        ARMv8.makeDepend opts phase src obj depfile
222    | otherwise = [ ErrorMsg ("no dependency generator for " ++ (optArch opts)) ]
223
224makeCxxDepend :: Options -> String -> String -> String -> String -> [ RuleToken ]
225makeCxxDepend opts phase src obj depfile
226    | optArch opts == "x86_64" =
227        X86_64.makeCxxDepend opts phase src obj depfile
228    | optArch opts == "k1om" =
229        K1om.makeCxxDepend opts phase src obj depfile
230    | optArch opts == "x86_32" =
231        X86_32.makeCxxDepend opts phase src obj depfile
232    | otherwise = [ ErrorMsg ("no C++ dependency generator for " ++ (optArch opts)) ]
233
234cToAssembler :: Options -> String -> String -> String -> String -> [ RuleToken ]
235cToAssembler opts phase src afile objdepfile
236    | optArch opts == "x86_64"  = X86_64.cToAssembler opts phase src afile objdepfile
237    | optArch opts == "k1om"  = K1om.cToAssembler opts phase src afile objdepfile
238    | optArch opts == "x86_32"  = X86_32.cToAssembler opts phase src afile objdepfile
239    | optArch opts == "armv7" = ARMv7.cToAssembler opts phase src afile objdepfile
240    | optArch opts == "armv8" = ARMv8.cToAssembler opts phase src afile objdepfile
241    | otherwise = [ ErrorMsg ("no C compiler for " ++ (optArch opts)) ]
242
243--
244-- Assemble an assembly language file
245--
246assembler :: Options -> String -> String -> [ RuleToken ]
247assembler opts src obj
248    | optArch opts == "x86_64"  = X86_64.assembler opts src obj
249    | optArch opts == "k1om"  = K1om.assembler opts src obj
250    | optArch opts == "x86_32"  = X86_32.assembler opts src obj
251    | optArch opts == "armv7" = ARMv7.assembler opts src obj
252    | optArch opts == "armv8" = ARMv8.assembler opts src obj
253    | otherwise = [ ErrorMsg ("no assembler for " ++ (optArch opts)) ]
254
255archive :: Options -> [String] -> [String] -> String -> String -> [ RuleToken ]
256archive opts objs libs name libname
257    | optArch opts == "x86_64"  = X86_64.archive opts objs libs name libname
258    | optArch opts == "k1om"  = K1om.archive opts objs libs name libname
259    | optArch opts == "x86_32"  = X86_32.archive opts objs libs name libname
260    | optArch opts == "armv7" = ARMv7.archive opts objs libs name libname
261    | optArch opts == "armv8" = ARMv8.archive opts objs libs name libname
262    | otherwise = [ ErrorMsg ("Can't build a library for " ++ (optArch opts)) ]
263
264linker :: Options -> [String] -> [String] -> [String] -> String -> [RuleToken]
265linker opts objs libs mods bin
266    | optArch opts == "x86_64" = X86_64.linker opts objs libs mods bin
267    | optArch opts == "k1om" = K1om.linker opts objs libs mods bin
268    | optArch opts == "x86_32" = X86_32.linker opts objs libs mods bin
269    | optArch opts == "armv7" = ARMv7.linker opts objs libs mods bin
270    | optArch opts == "armv8" = ARMv8.linker opts objs libs mods bin
271    | otherwise = [ ErrorMsg ("Can't link executables for " ++ (optArch opts)) ]
272
273strip :: Options -> String -> String -> String -> [RuleToken]
274strip opts src debuglink target
275    | optArch opts == "x86_64" = X86_64.strip opts src debuglink target
276    | optArch opts == "k1om" = K1om.strip opts src debuglink target
277    | optArch opts == "x86_32" = X86_32.strip opts src debuglink target
278    | optArch opts == "armv7" = ARMv7.strip opts src debuglink target
279    | optArch opts == "armv8" = ARMv8.strip opts src debuglink target
280    | otherwise = [ ErrorMsg ("Can't strip executables for " ++ (optArch opts)) ]
281
282debug :: Options -> String -> String -> [RuleToken]
283debug opts src target
284    | optArch opts == "x86_64" = X86_64.debug opts src target
285    | optArch opts == "k1om" = K1om.debug opts src target
286    | optArch opts == "x86_32" = X86_32.debug opts src target
287    | optArch opts == "armv7" = ARMv7.debug opts src target
288    | optArch opts == "armv8" = ARMv8.debug opts src target
289    | otherwise = [ ErrorMsg ("Can't extract debug symbols for " ++ (optArch opts)) ]
290
291cxxlinker :: Options -> [String] -> [String] -> [String] -> String -> [RuleToken]
292cxxlinker opts objs libs mods bin
293    | optArch opts == "x86_64" = X86_64.cxxlinker opts objs libs mods bin
294    | optArch opts == "k1om" = K1om.cxxlinker opts objs libs mods bin
295    | otherwise = [ ErrorMsg ("Can't link C++ executables for " ++ (optArch opts)) ]
296
297--
298-- The C compiler for compiling things on the host
299--
300nativeCCompiler :: String
301nativeCCompiler = "$(CC)"
302
303nativeArchiver :: String
304nativeArchiver = "ar"
305
306-------------------------------------------------------------------------
307--
308-- Functions to create useful filenames
309--
310
311dependFilePath :: String -> String
312dependFilePath obj = obj ++ ".depend"
313
314objectFilePath :: Options -> String -> String
315objectFilePath opts src = optSuffix opts </> replaceExtension src ".o"
316
317generatedObjectFilePath :: Options -> String -> String
318generatedObjectFilePath opts src = replaceExtension src ".o"
319
320preprocessedFilePath :: Options -> String -> String
321preprocessedFilePath opts src = optSuffix opts </> replaceExtension src ".i"
322
323-- Standard convention is that human generated assembler is .S, machine generated is .s
324assemblerFilePath :: Options -> String -> String
325assemblerFilePath opts src = optSuffix opts </> replaceExtension src ".s"
326
327
328-------------------------------------------------------------------------
329--
330-- Functions with logic to start doing things
331--
332
333--
334-- Create C file dependencies
335--
336
337-- Since this is where we know what the depfile is called it is here that we also
338-- decide to include it.  This stops many different places below trying to
339-- guess what the depfile is called
340--
341makeDependArchSub :: Options -> String -> String -> String -> String -> [ RuleToken ]
342makeDependArchSub opts phase src objfile depfile =
343   [ Str ("@if [ -z $Q ]; then echo Generating $@; fi"), NL ] ++
344     makeDepend opts phase src objfile depfile
345
346makeDependArch :: Options -> String -> String -> String -> String -> HRule
347makeDependArch opts phase src objfile depfile =
348    Rules [ Rule (makeDependArchSub opts phase src objfile depfile),
349            Include (Out (optArch opts) depfile)
350          ]
351
352-- Make depend for a standard object file
353makeDependObj :: Options -> String -> String -> HRule
354makeDependObj opts phase src =
355    let objfile = (objectFilePath opts src)
356    in
357      makeDependArch opts phase src objfile (dependFilePath objfile)
358
359-- Make depend for a C++ object file
360makeDependCxxArchSub :: Options -> String -> String -> String -> String -> [ RuleToken ]
361makeDependCxxArchSub opts phase src objfile depfile =
362   [ Str ("@if [ -z $Q ]; then echo Generating $@; fi"), NL ] ++
363     makeCxxDepend opts phase src objfile depfile
364
365makeDependCxxArch :: Options -> String -> String -> String -> String -> HRule
366makeDependCxxArch opts phase src objfile depfile =
367    Rules [ Rule (makeDependCxxArchSub opts phase src objfile depfile),
368            Include (Out (optArch opts) depfile)
369          ]
370
371makeDependCxxObj :: Options -> String -> String -> HRule
372makeDependCxxObj opts phase src =
373    let objfile = (objectFilePath opts src)
374    in
375      makeDependCxxArch opts phase src objfile (dependFilePath objfile)
376
377-- Make depend for an assembler output
378makeDependAssembler :: Options -> String -> String -> HRule
379makeDependAssembler opts phase src =
380    let objfile = (assemblerFilePath opts src)
381    in
382      makeDependArch opts phase src objfile (dependFilePath objfile)
383
384--
385-- Compile a C program to assembler
386--
387makecToAssembler :: Options -> String -> String -> String -> [ RuleToken ]
388makecToAssembler opts phase src obj =
389    cToAssembler opts phase src (assemblerFilePath opts src) (dependFilePath obj)
390
391--
392-- Assemble an assembly language file
393--
394assemble :: Options -> String -> [ RuleToken ]
395assemble opts src =
396    assembler opts src (objectFilePath opts src)
397
398--
399-- Create a library from a set of object files
400--
401archiveLibrary :: Options -> String -> [String] -> [String] -> [ RuleToken ]
402archiveLibrary opts name objs libs =
403    archive opts objs libs name (libraryPath opts name)
404
405--
406-- Link an executable
407--
408linkExecutable :: Options -> [String] -> [String] -> [String] -> String -> [RuleToken]
409linkExecutable opts objs libs mods bin =
410    linker opts objs libs mods (applicationPath opts bin)
411
412--
413-- Strip debug symbols from an executable
414--
415stripExecutable :: Options -> String -> String -> String -> [RuleToken]
416stripExecutable opts src debuglink target =
417    strip opts (applicationPath opts src) (applicationPath opts debuglink)
418               (applicationPath opts target)
419
420--
421-- Extract debug symbols from an executable
422--
423debugExecutable :: Options -> String -> String -> [RuleToken]
424debugExecutable opts src target =
425    debug opts (applicationPath opts src) (applicationPath opts target)
426
427--
428-- Link a C++ executable
429--
430linkCxxExecutable :: Options -> [String] -> [String] -> [String] -> String -> [RuleToken]
431linkCxxExecutable opts objs libs mods bin =
432    cxxlinker opts objs libs mods (applicationPath opts bin)
433
434-------------------------------------------------------------------------
435
436
437
438
439
440-------------------------------------------------------------------------
441--
442-- Hake macros (hacros?): each of these evaluates to HRule, i.e. a
443-- list of templates for Makefile rules
444--
445-------------------------------------------------------------------------
446
447--
448-- Compile a C file for a particular architecture
449-- We include cToAssembler to permit humans to type "make foo/bar.s"
450--
451compileCFile :: Options -> String -> HRule
452compileCFile opts src =
453    Rules [ Rule (cCompiler opts "src" src (objectFilePath opts src)),
454            Rule (makecToAssembler opts "src" src (objectFilePath opts src)),
455            makeDependObj opts "src" src
456          ]
457
458--
459-- Compile a C++ file for a particular architecture
460--
461compileCxxFile :: Options -> String -> HRule
462compileCxxFile opts src =
463    Rules [ Rule (cxxCompiler opts "src" src (objectFilePath opts src)),
464            makeDependCxxObj opts "src" src
465          ]
466
467--
468-- Compile a C file for a particular architecture
469--
470compileGeneratedCFile :: Options -> String -> HRule
471compileGeneratedCFile opts src =
472    let o2 = opts { optSuffix = "" }
473        arch = optArch o2
474    in
475      Rules [ Rule (cCompiler o2 arch src (objectFilePath o2 src) ),
476              Rule (makecToAssembler o2 arch src (objectFilePath o2 src)),
477              makeDependObj o2 arch src
478            ]
479
480compileGeneratedCxxFile :: Options -> String -> HRule
481compileGeneratedCxxFile opts src =
482    let o2 = opts { optSuffix = "" }
483        arch = optArch o2
484    in
485      Rules [ Rule (cxxCompiler o2 arch src (objectFilePath o2 src) ),
486              makeDependCxxObj o2 arch src
487            ]
488
489compileCFiles :: Options -> [String] -> HRule
490compileCFiles opts srcs = Rules [ compileCFile opts s | s <- srcs ]
491compileCxxFiles :: Options -> [String] -> HRule
492compileCxxFiles opts srcs = Rules [ compileCxxFile opts s | s <- srcs ]
493compileGeneratedCFiles :: Options -> [String] -> HRule
494compileGeneratedCFiles opts srcs =
495    Rules [ compileGeneratedCFile opts s | s <- srcs ]
496compileGeneratedCxxFiles :: Options -> [String] -> HRule
497compileGeneratedCxxFiles opts srcs =
498    Rules [ compileGeneratedCxxFile opts s | s <- srcs ]
499
500--
501-- Add a set of C (or whatever) dependences on a *generated* file.
502-- Somewhere else this file has to be defined as a target, of
503-- course...
504--
505extraCDependencyForObj :: Options -> String -> String -> String -> [RuleToken]
506extraCDependencyForObj opts file s obj =
507    let arch = optArch opts
508    in
509      [ Target arch (dependFilePath obj),
510        Target arch obj,
511        Dep BuildTree arch file
512      ]
513
514extraCDependency :: Options -> String -> String -> HRule
515extraCDependency opts file s = Rule (extraCDependencyForObj opts file s obj)
516    where obj = objectFilePath opts s
517
518
519extraCDependencies :: Options -> String -> [String] -> HRule
520extraCDependencies opts file srcs =
521    Rules [ extraCDependency opts file s | s <- srcs ]
522
523extraGeneratedCDependency :: Options -> String -> String -> HRule
524extraGeneratedCDependency opts file s =
525    extraCDependency (opts { optSuffix = "" }) file s
526
527--
528-- Copy include files to the appropriate directory
529--
530includeFile :: [ String ] -> HRule
531includeFile hdrs =
532    Rules ([ Rule [ Str "cp", In SrcTree "src" hdr, Out "root" hdr] | hdr <- hdrs ]
533    ++ [
534        Phony "install_headers" False [ Dep BuildTree "root" hdr | hdr <- hdrs ]
535    ])
536
537--
538-- Build a Mackerel header file from a definition.
539--
540mackerelProgLoc = In InstallTree "tools" "/bin/mackerel"
541mackerelDevFileLoc d = In SrcTree "src" ("/devices" </> (d ++ ".dev"))
542mackerelDevHdrPath d = "/include/dev/" </> (d ++ "_dev.h")
543
544mackerel2 :: Options -> String -> HRule
545mackerel2 opts dev = mackerel_generic opts dev "shift-driver"
546
547mackerel :: Options -> String -> HRule
548mackerel opts dev = mackerel_generic opts dev "bitfield-driver"
549
550mackerel_generic :: Options -> String -> String -> HRule
551mackerel_generic opts dev flag =
552    let
553        arch = optArch opts
554    in
555      Rule [ mackerelProgLoc,
556             Str ("--" ++ flag),
557             Str "-c", mackerelDevFileLoc dev,
558             Str "-o", Out arch (mackerelDevHdrPath dev)
559           ]
560
561mackerelDependencies :: Options -> String -> [String] -> HRule
562mackerelDependencies opts d srcs =
563    extraCDependencies opts (mackerelDevHdrPath d) srcs
564
565--
566-- Basic Flounder definitions: where things are
567--
568
569flounderProgLoc = In InstallTree "tools" "/bin/flounder"
570flounderIfFileLoc ifn = In SrcTree "src" ("/if" </> (ifn ++ ".if"))
571
572-- new-style stubs: path for generic header
573flounderIfDefsPath ifn = "/include/if" </> (ifn ++ "_defs.h")
574-- new-style stubs: path for specific backend header
575flounderIfDrvDefsPath ifn drv = "/include/if" </> (ifn ++ "_" ++ drv ++ "_defs.h")
576
577-- new-style stubs: generated C code (for all default enabled backends)
578flounderBindingPath opts ifn =
579    (optSuffix opts) </> (ifn ++ "_flounder_bindings.c")
580-- new-style stubs: generated C code (for extra backends enabled by the user)
581flounderExtraBindingPath opts ifn =
582    (optSuffix opts) </> (ifn ++ "_flounder_extra_bindings.c")
583
584flounderTHCHdrPath ifn = "/include/if" </> (ifn ++ "_thc.h")
585flounderTHCStubPath opts ifn =
586    (optSuffix opts) </> (ifn ++ "_thc.c")
587
588applicationPath :: Options -> String -> String
589applicationPath opts name = optPathBin (optInstallPath opts) </> name
590
591libraryPath :: Options -> String -> String
592libraryPath opts libname = optPathLib (optInstallPath opts) </> ("lib" ++ libname ++ ".a")
593
594kernelPath = "/sbin/cpu"
595
596-- construct include arguments to flounder for common types
597-- these are:
598--  1. platform-specific types (if/platform/foo.if)
599--  2. architecture-specific types (if/arch/foo.if)
600--  3. generic types (if/types.if)
601flounderIncludes :: Options -> [RuleToken]
602flounderIncludes opts
603    = concat [ [Str "-i", flounderIfFileLoc ifn]
604               | ifn <- [ "platform" </> (optArch opts), -- XXX: optPlatform
605                          "arch" </> (optArch opts),
606                          "types" ] ]
607
608flounderRule :: Options -> [RuleToken] -> HRule
609flounderRule opts args
610    = Rule $ [ flounderProgLoc ] ++ (flounderIncludes opts) ++ args
611
612--
613-- Build new-style Flounder header files from a definition
614-- (generic header, plus one per backend)
615--
616flounderGenDefs :: Options -> String -> HRule
617flounderGenDefs opts ifn =
618    Rules $ flounderRule opts [
619           Str "--generic-header", flounderIfFileLoc ifn,
620           Out (optArch opts) (flounderIfDefsPath ifn)
621         ] : [ flounderRule opts [
622           Str $ "--" ++ drv ++ "-header", flounderIfFileLoc ifn,
623           Out (optArch opts) (flounderIfDrvDefsPath ifn drv)]
624           | drv <- Args.allFlounderBackends ]
625
626--
627-- Build a new Flounder binding file from a definition.
628-- This builds the binding for all enabled backends
629--
630flounderBinding :: Options -> String -> [String] -> HRule
631flounderBinding opts ifn =
632    flounderBindingHelper opts ifn backends (flounderBindingPath opts ifn)
633    where
634        backends = "generic" : (optFlounderBackends opts)
635
636-- as above, but for a specific set of user-specified backends
637flounderExtraBinding :: Options -> String -> [String] -> [String] -> HRule
638flounderExtraBinding opts ifn backends =
639    flounderBindingHelper opts ifn backends (flounderExtraBindingPath opts ifn)
640
641flounderBindingHelper :: Options -> String -> [String] -> String -> [String] -> HRule
642flounderBindingHelper opts ifn backends cfile srcs = Rules $
643    [ flounderRule opts $ args ++ [flounderIfFileLoc ifn, Out arch cfile ],
644        compileGeneratedCFile opts cfile,
645        flounderDefsDepend opts ifn allbackends srcs]
646    ++ [extraGeneratedCDependency opts (flounderIfDefsPath ifn) cfile]
647    ++ [extraGeneratedCDependency opts (flounderIfDrvDefsPath ifn d) cfile
648        | d <- allbackends]
649    where
650        arch = optArch opts
651        archfam = optArchFamily opts
652        args = [Str "-a", Str archfam] ++ [Str $ "--" ++ d ++ "-stub" | d <- backends]
653        allbackends = backends `union` optFlounderBackends opts \\ ["generic"]
654
655--
656-- Build a Flounder THC header file from a definition.
657--
658flounderTHCFile :: Options -> String -> HRule
659flounderTHCFile opts ifn =
660    flounderRule opts [
661           Str "--thc-header", flounderIfFileLoc ifn,
662           Out (optArch opts) (flounderTHCHdrPath ifn)
663         ]
664
665--
666-- Build a Flounder THC stubs file from a definition.
667--
668flounderTHCStub :: Options -> String -> [String] -> HRule
669flounderTHCStub opts ifn srcs =
670    let cfile = flounderTHCStubPath opts ifn
671        hfile = flounderTHCHdrPath ifn
672        arch = optArch opts
673    in
674      Rules [ flounderRule opts [
675                     Str "--thc-stubs", flounderIfFileLoc ifn,
676                     Out arch cfile
677                   ],
678              compileGeneratedCFile opts cfile,
679              extraCDependencies opts hfile srcs,
680              extraGeneratedCDependency opts hfile cfile,
681              extraGeneratedCDependency opts (flounderIfDefsPath ifn) cfile
682            ]
683
684--
685-- Create a dependency on a Flounder header file for a set of files,
686-- but don't actually build either stub (useful for libraries)
687--
688flounderDefsDepend :: Options -> String -> [String] -> [String] -> HRule
689flounderDefsDepend opts ifn backends srcs = Rules $
690    (extraCDependencies opts (flounderIfDefsPath ifn) srcs) :
691    [extraCDependencies opts (flounderIfDrvDefsPath ifn drv) srcs
692           | drv <- backends, drv /= "generic" ]
693
694--
695-- Emit all the Flounder-related rules/dependencies for a given target
696--
697
698flounderRules :: Options -> Args.Args -> [String] -> [HRule]
699flounderRules opts args csrcs =
700    ([ flounderBinding opts f csrcs | f <- Args.flounderBindings args ]
701     ++
702     [ flounderExtraBinding opts f backends csrcs
703       | (f, backends) <- Args.flounderExtraBindings args ]
704     ++
705     [ flounderTHCStub opts f csrcs | f <- Args.flounderTHCStubs args ]
706     ++
707     -- Flounder extra defs (header files) also depend on the base
708     -- Flounder headers for the same interface
709     [ flounderDefsDepend opts f baseBackends csrcs | f <- allIf ]
710     ++
711     -- Extra defs only for non-base backends (those were already emitted above)
712     [ flounderDefsDepend opts f (backends \\ baseBackends) csrcs
713       | (f, backends) <- Args.flounderExtraDefs args ]
714    )
715    where
716      -- base backends enabled by default
717      baseBackends = optFlounderBackends opts
718
719      -- all interfaces mentioned in flounderDefs or ExtraDefs
720      allIf = nub $ Args.flounderDefs args ++ [f | (f,_) <- Args.flounderExtraDefs args]
721
722
723 --
724 -- Build a Skate library and header file
725 --
726
727
728skateSchemaPath opts ifn = (optSuffix opts) </> (ifn ++ "_skate_schema.c")
729skateProgLoc = In InstallTree "tools" "/bin/skate"
730skateSksFileLoc schema = In SrcTree "src" ("/schemas" </> (schema ++ ".sks"))
731skateSchemaDefsPath schema = "/include/schemas" </> (schema ++ "_schema.h")
732
733
734skateSchemaHelper :: Options -> String -> String -> [String] -> HRule
735skateSchemaHelper opts ifn cfile srcs = Rules $
736    [ skateRule opts $ args ++ [
737        Str "-o", Out arch cfile, skateSksFileLoc ifn],
738        compileGeneratedCFile opts cfile,
739        skateDefsDepend opts ifn srcs]
740    ++ [extraGeneratedCDependency opts (skateSchemaDefsPath ifn) cfile]
741    where
742        arch = optArch opts
743        archfam = optArchFamily opts
744        args = [Str "-a", Str arch, Str "-C"]
745
746
747skateSchema :: Options -> String -> [String] -> HRule
748skateSchema opts schema =
749    skateSchemaHelper opts schema (skateSchemaPath opts schema)
750
751
752skateDefsDepend :: Options -> String -> [String] -> HRule
753skateDefsDepend opts schema srcs = Rules $
754    [(extraCDependencies opts (skateSchemaDefsPath schema) srcs)]
755
756
757skateRules :: Options -> Args.Args -> [String] -> [HRule]
758skateRules opts args csrcs =
759    ([ skateSchema opts f csrcs | f <- Args.skateSchemas args ]
760     ++
761     [ skateDefsDepend opts f csrcs | f <- nub $ Args.skateSchemaDefs args ])
762
763
764skateIncludes :: Options -> [RuleToken]
765skateIncludes opts = []
766
767
768skateRule :: Options -> [RuleToken] -> HRule
769skateRule opts args = Rule $ [ skateProgLoc ] ++ (skateIncludes opts) ++ args
770
771
772skateGenSchemas :: Options -> String -> HRule
773skateGenSchemas opts schema =
774 Rules $ [skateRule opts [
775        Str "-H",
776        Str "-o", Out (optArch opts) (skateSchemaDefsPath schema),
777        skateSksFileLoc schema
778      ]]
779
780
781--
782-- Build SKB facts from Sockeye file
783--
784sockeyeProgLoc = In InstallTree "tools" "/bin/sockeye"
785sockeyeSocDir = In SrcTree "src" "/socs"
786sockeyeSocFileLoc d = In SrcTree "src" ("/socs" </> d <.> "soc")
787sockeyeFactFilePath d = "/sockeyefacts" </> d <.> "pl"
788sockeyeFactFileLoc d = In BuildTree "" $ sockeyeFactFilePath d
789
790sockeyeNS :: String -> String -> HRule
791sockeyeNS net rootns = 
792    let
793        factFile = sockeyeFactFilePath net
794        depFile = dependFilePath factFile
795    in Rules
796        [ Rule
797            [ sockeyeProgLoc
798            , Str "-i", sockeyeSocDir
799            , Str "-o", Out "" factFile
800            , Str "-d", Out "" depFile
801            , Str "-r", Str rootns
802            , sockeyeSocFileLoc net
803            ]
804        , Include (Out "" depFile)
805        ]
806
807sockeye :: String -> HRule
808sockeye net = 
809    let
810        factFile = sockeyeFactFilePath net
811        depFile = dependFilePath factFile
812    in Rules
813        [ Rule
814            [ sockeyeProgLoc
815            , Str "-i", sockeyeSocDir
816            , Str "-o", Out "" factFile
817            , Str "-d", Out "" depFile
818            , sockeyeSocFileLoc net
819            ]
820        , Include (Out "" depFile)
821        ]
822
823--
824-- Build a Fugu library
825--
826fuguCFile :: Options -> String -> HRule
827fuguCFile opts file =
828    let arch = optArch opts
829        cfile = file ++ ".c"
830    in
831      Rules [ Rule [ In InstallTree "tools" "/bin/fugu",
832                     In SrcTree "src" (file++".fugu"),
833                     Str "-c",
834                     Out arch cfile ],
835              compileGeneratedCFile opts cfile
836         ]
837
838fuguHFile :: Options -> String -> HRule
839fuguHFile opts file =
840    let arch = optArch opts
841        hfile = "/include/errors/" ++ file ++ ".h"
842    in
843      Rule [ In InstallTree "tools" "/bin/fugu",
844             In SrcTree "src" (file++".fugu"),
845             Str "-h",
846             Out arch hfile ]
847
848--
849-- Build a Pleco library
850--
851plecoFile :: Options -> String -> HRule
852plecoFile opts file =
853    let arch = optArch opts
854        cfile = file ++ ".c"
855        hfile = "/include/trace_definitions/" ++ file ++ ".h"
856        jsonfile = "/trace_definitions/" ++ file ++ ".json"
857    in
858      Rules [ Rule [In InstallTree "tools" "/bin/pleco",
859                    In SrcTree "src" (file++".pleco"),
860                    Out arch hfile,
861                    Out arch jsonfile,
862                    Out arch cfile ],
863              compileGeneratedCFile opts cfile
864         ]
865
866--
867-- Build a Hamlet file
868--
869hamletFile :: Options -> String -> HRule
870hamletFile opts file =
871    let arch = optArch opts
872        hfile = "/include/barrelfish_kpi/capbits.h"
873        cfile = "cap_predicates.c"
874        usercfile = "user_cap_predicates.c"
875        ofile = "user_cap_predicates.o"
876        nfile = "cap_predicates"
877        afile = "/lib/libcap_predicates.a"
878    in
879      Rules [ Rule [In InstallTree "tools" "/bin/hamlet",
880                    In SrcTree "src" (file++".hl"),
881                    Out arch hfile,
882                    Out arch cfile,
883                    Out arch usercfile ],
884              compileGeneratedCFile opts usercfile,
885              Rule (archive opts [ ofile ] [] nfile afile)
886         ]
887
888--
889-- Link a set of object files and libraries together
890--
891link :: Options -> [String] -> [String] -> [String] -> String -> HRule
892link opts objs libs mods bin =
893    let full = bin ++ ".full"
894        debug = bin ++ ".debug"
895    in Rules [
896        Rule $ linkExecutable opts objs libs mods full,
897        Rule $ debugExecutable opts full debug,
898        Rule $ stripExecutable opts full debug bin
899    ]
900
901--
902-- Link a set of C++ object files and libraries together
903--
904linkCxx :: Options -> [String] -> [String] -> [String] -> String -> HRule
905linkCxx opts objs libs mods bin =
906    Rule (linkCxxExecutable opts objs libs mods bin)
907
908--
909-- Link a CPU driver.  This is where it gets distinctly architecture-specific.
910--
911linkKernel :: Options -> String -> [String] -> [String] -> String -> HRule
912linkKernel opts name objs libs driverType
913    | optArch opts == "x86_64" = X86_64.linkKernel opts objs [libraryPath opts l | l <- libs ] ("/sbin" </> name)
914    | optArch opts == "k1om" = K1om.linkKernel opts objs [libraryPath opts l | l <- libs ] ("/sbin" </> name)
915    | optArch opts == "x86_32" = X86_32.linkKernel opts objs [libraryPath opts l | l <- libs ] ("/sbin" </> name)
916    | optArch opts == "armv7" = ARMv7.linkKernel opts objs [libraryPath opts l | l <- libs ] name driverType
917    | optArch opts == "armv8" = ARMv8.linkKernel opts objs [libraryPath opts l | l <- libs ] name driverType
918    | otherwise = Rule [ Str ("Error: Can't link kernel for '" ++ (optArch opts) ++ "'") ]
919
920--
921-- Copy a file from one place to another
922--
923copy :: Options -> String -> String -> HRule
924copy opts src dest =
925    Rule [ Str "cp", In BuildTree (optArch opts) src, Out (optArch opts) dest ]
926
927--
928-- Assemble a list of S files for a particular architecture
929--
930assembleSFile :: Options -> String -> HRule
931assembleSFile opts src =
932    Rules [ Rule (assemble opts src),
933            makeDependObj opts "src" src
934          ]
935
936assembleSFiles :: Options -> [String] -> HRule
937assembleSFiles opts srcs = Rules [ assembleSFile opts s | s <- srcs ]
938
939--
940-- Archive a bunch of objects into a library
941--
942staticLibrary :: Options -> String -> [String] -> [String] -> HRule
943staticLibrary opts libpath objs libs =
944    Rule (archiveLibrary opts libpath objs libs)
945
946--
947-- Compile a Haskell binary (for the host architecture)
948--
949compileHaskell prog main deps = compileHaskellWithLibs prog main deps []
950compileHaskellWithLibs prog main deps dirs =
951  let
952    tools_dir = (Dep InstallTree "tools" "/tools/.marker")
953  in
954    Rule ([ NStr "ghc -i",
955            NoDep SrcTree "src" ".",
956            Str "-odir ", NoDep BuildTree "tools" ".",
957            Str "-hidir ", NoDep BuildTree "tools" ".",
958            Str "-rtsopts=all",
959            Str "--make ",
960            In SrcTree "src" main,
961            Str "-o ",
962            Out "tools" ("/bin" </> prog),
963            Str "$(LDFLAGS)" ]
964          ++ concat [[ NStr "-i", NoDep SrcTree "src" d] | d <- dirs]
965          ++ [ (Dep SrcTree "src" dep) | dep <- deps ]
966          ++ [ tools_dir ])
967
968nativeOptions = Options {
969      optArch                = "",
970      optArchFamily          = "",
971      optFlags               = [],
972      optCxxFlags            = [],
973      optDefines             = [],
974      optIncludes            = [],
975      optDependencies        = [],
976      optLdFlags             = [],
977      optLdCxxFlags          = [],
978      optLibs                = [],
979      optCxxLibs             = [],
980      optInterconnectDrivers = [],
981      optFlounderBackends    = [],
982      extraFlags             = [],
983      extraCxxFlags          = [],
984      extraDefines           = [],
985      extraIncludes          = [],
986      extraDependencies      = [],
987      extraLdFlags           = [],
988      optSuffix              = "",
989      optInstallPath         = OptionsPath {
990            optPathBin = "/sbin",
991            optPathLib = "/lib"
992      }
993    }
994
995--
996-- Compile (and link) a C binary (for the host architecture)
997--
998compileNativeC :: String -> [String] -> [String] -> [String] -> [String] ->
999                  HRule
1000compileNativeC prog cfiles cflags ldflags localLibs =
1001    Rule ([ Str nativeCCompiler,
1002            Str "-o",
1003            Out "tools" ("/bin" </> prog),
1004            Str "$(CFLAGS)",
1005            Str "$(LDFLAGS)" ]
1006          ++ [ (Str flag) | flag <- cflags ]
1007          ++ [ (In SrcTree "src" dep) | dep <- cfiles ]
1008          -- source file needs to be left of ldflags for modern-ish GCC
1009          ++ [ (Str flag) | flag <- ldflags ]
1010          ++ [ In BuildTree "tools" ("/lib" </> ("lib" ++ l ++ ".a")) |
1011               l <- localLibs ])
1012
1013--
1014-- Compile a static library for the host architecture
1015--
1016compileNativeLib :: String -> [String] -> [String] -> HRule
1017compileNativeLib name cfiles cflags =
1018    Rules (
1019        [ Rule ([ Str nativeCCompiler,
1020                  Str "-c", In SrcTree "src" s,
1021                  Str "-o", Out "tools" (objectFilePath nativeOptions s),
1022                  Str "$(CFLAGS)",
1023                  Str "$(LDFLAGS)" ]
1024                ++ [ (Str flag) | flag <- cflags ])
1025            | s <- cfiles ] ++
1026        [ Rule ([ Str nativeArchiver,
1027                  Str "rcs",
1028                  Out "tools" ("/lib" </> ("lib" ++ name ++ ".a")) ] ++
1029                [ In BuildTree "tools" o | o <- objs ]) ]
1030        )
1031    where
1032        objs = [ objectFilePath nativeOptions s | s <- cfiles ]
1033--
1034-- Build a Technical Note
1035--
1036buildTechNote :: String -> String -> Bool -> Bool -> [String] -> HRule
1037buildTechNote input output bib glo figs =
1038    buildTechNoteWithDeps input output bib glo figs []
1039buildTechNoteWithDeps :: String -> String -> Bool -> Bool -> [String] -> [RuleToken] -> HRule
1040buildTechNoteWithDeps input output bib glo figs deps =
1041    let
1042        working_dir = NoDep BuildTree "tools" "/tmp/"
1043        style_files = [ "bfish-logo.pdf", "bftn.sty", "defs.bib", "barrelfish.bib" ]
1044    in
1045      Rule ( [ Dep SrcTree "src" (f ++ ".pdf") | f <- figs]
1046             ++
1047             [ Dep SrcTree "src" ("/doc/style" </> f) | f <- style_files ]
1048             ++
1049             [ Str "mkdir", Str "-p", working_dir, NL ]
1050             ++
1051             deps
1052             ++
1053             [ In SrcTree "src" "/tools/run-pdflatex.sh",
1054               Str "--input-tex", In SrcTree "src" input,
1055               Str "--working-dir", working_dir,
1056               Str "--output-pdf", Out "docs" ("/" ++ output),
1057               Str "--texinput", NoDep SrcTree "src" "/doc/style",
1058               Str "--bibinput", NoDep SrcTree "src" "/doc/style"
1059             ]
1060             ++ (if bib then [ Str "--has-bib" ] else [])
1061             ++ (if glo then [ Str "--has-glo" ] else [])
1062           )
1063
1064---------------------------------------------------------------------
1065--
1066-- Transformations on file names
1067--
1068----------------------------------------------------------------------
1069
1070allObjectPaths :: Options -> Args.Args -> [String]
1071allObjectPaths opts args =
1072    [objectFilePath opts g
1073         | g <- (Args.cFiles args)++(Args.cxxFiles args)++(Args.assemblyFiles args)]
1074    ++
1075    [generatedObjectFilePath opts g
1076         | g <- [ flounderBindingPath opts f
1077                      | f <- (Args.flounderBindings args)]
1078                ++
1079                [ flounderExtraBindingPath opts f
1080                      | (f, _) <- (Args.flounderExtraBindings args)]
1081                ++
1082                [ flounderTHCStubPath opts f
1083                      | f <- (Args.flounderTHCStubs args)]
1084                ++
1085                [ skateSchemaPath opts f
1086                      | f <- (Args.skateSchemas args)]
1087                ++
1088                (Args.generatedCFiles args) ++ (Args.generatedCxxFiles args)
1089    ]
1090
1091allLibraryPaths :: Options -> Args.Args -> [String]
1092allLibraryPaths opts args =
1093    [ libraryPath opts l | l <- Args.addLibraries args ]
1094
1095
1096allModulesPaths :: Options -> Args.Args -> [String]
1097allModulesPaths opts args =
1098    [ libraryPath opts l | l <- Args.addModules args ]
1099
1100---------------------------------------------------------------------
1101--
1102-- Very large-scale macros
1103--
1104----------------------------------------------------------------------
1105
1106--
1107-- Build an application binary
1108--
1109
1110application :: Args.Args
1111application = Args.defaultArgs { Args.buildFunction = applicationBuildFn }
1112
1113system :: Args.Args -> Args.Args
1114system args = args { Args.installDirs = (Args.installDirs args) { Args.bindir = "/sbin" }}
1115
1116applicationBuildFn :: TreeDB -> String -> Args.Args -> HRule
1117applicationBuildFn tdb tf args
1118    | debugFlag && trace (Args.showArgs (tf ++ " Application ") args) False
1119        = undefined
1120applicationBuildFn tdb tf args =
1121    Rules [ appBuildArch tdb tf args arch | arch <- Args.architectures args ]
1122
1123extraIncs libs =
1124    [ NoDep SrcTree "src" ("/include" </> l) | l <- filter libNeedsInc libs ]
1125    where
1126        libNeedsInc lib
1127           | lib == "lwip"  = True
1128           | lib == "lwip2" = True
1129           | otherwise      = False
1130
1131appGetOptionsForArch arch args =
1132    (options arch) { extraIncludes =
1133                         [ NoDep SrcTree "src" a | a <- Args.addIncludes args]
1134                         ++
1135                         [ NoDep BuildTree arch a | a <- Args.addGeneratedIncludes args]
1136                         ++
1137                         -- Only add extra include directory for libraries
1138                         -- that actually need it. -SG,2017-09-19.
1139                         extraIncs (Args.addLibraries args),
1140                     optIncludes = (optIncludes $ options arch) \\
1141                         [ NoDep SrcTree "src" i | i <- Args.omitIncludes args ],
1142                     optFlags = (optFlags $ options arch) \\
1143                                [ Str f | f <- Args.omitCFlags args ],
1144                     optCxxFlags = (optCxxFlags $ options arch) \\
1145                                   [ Str f | f <- Args.omitCxxFlags args ],
1146                     optSuffix = "_for_app_" ++ Args.target args,
1147                     extraFlags = Args.addCFlags args,
1148                     extraCxxFlags = Args.addCxxFlags args,
1149                     extraLdFlags = [ Str f | f <- Args.addLinkFlags args ],
1150                     extraDependencies =
1151                         [Dep BuildTree arch s |
1152                            s <- Args.addGeneratedDependencies args],
1153                     optInstallPath = OptionsPath {
1154                        optPathBin = Args.bindir (Args.installDirs args),
1155                        optPathLib = Args.libdir (Args.installDirs args)
1156                     }
1157                   }
1158
1159fullTarget :: Options -> String -> String -> HRule
1160fullTarget opts arch appname =
1161    Phony (arch ++ "_All") False
1162        [ Dep BuildTree arch (applicationPath opts appname) ]
1163
1164appBuildArch tdb tf args arch =
1165    let -- Fiddle the options
1166        opts = appGetOptionsForArch arch args
1167        csrcs = Args.cFiles args
1168        cxxsrcs = Args.cxxFiles args
1169        gencsrc = Args.generatedCFiles args
1170        gencxxsrc = Args.generatedCxxFiles args
1171
1172
1173        appname = Args.target args
1174        -- XXX: Not sure if this is correct. Currently assuming that if the app
1175        -- contains C++ files, we have to use the C++ linker.
1176        mylink = if cxxsrcs == [] then link else linkCxx
1177    in
1178      Rules ( flounderRules opts args csrcs
1179              ++
1180              skateRules opts args csrcs
1181              ++
1182              [ mackerelDependencies opts m csrcs | m <- Args.mackerelDevices args ]
1183              ++
1184              [ compileCFiles opts csrcs,
1185                compileCxxFiles opts cxxsrcs,
1186                compileGeneratedCFiles opts gencsrc,
1187                compileGeneratedCxxFiles opts gencxxsrc,
1188                assembleSFiles opts (Args.assemblyFiles args),
1189                mylink opts (allObjectPaths opts args) (allLibraryPaths opts args) (allModulesPaths opts args)
1190                       appname,
1191                fullTarget opts arch appname
1192              ]
1193            )
1194
1195--
1196-- Build an Arrakis application binary
1197--
1198
1199arrakisapplication :: Args.Args
1200arrakisapplication = Args.defaultArgs { Args.buildFunction = arrakisApplicationBuildFn }
1201
1202arrakisApplicationBuildFn :: TreeDB -> String -> Args.Args -> HRule
1203arrakisApplicationBuildFn tdb tf args
1204    | debugFlag && trace (Args.showArgs (tf ++ " Arrakis Application ") args) False
1205        = undefined
1206arrakisApplicationBuildFn tdb tf args =
1207    Rules [ arrakisAppBuildArch tdb tf args arch | arch <- Args.architectures args ]
1208
1209arrakisAppGetOptionsForArch arch args =
1210    (options arch) { extraIncludes =
1211                         [ NoDep SrcTree "src" a | a <- Args.addIncludes args],
1212                     optIncludes = (optIncludes $ options arch) \\
1213                         [ NoDep SrcTree "src" i | i <- Args.omitIncludes args ],
1214                     optFlags = ((optFlags $ options arch) ++ [ Str "-DARRAKIS" ]) \\
1215                                [ Str f | f <- Args.omitCFlags args ],
1216                     optCxxFlags = (optCxxFlags $ options arch) \\
1217                                   [ Str f | f <- Args.omitCxxFlags args ],
1218                     optSuffix = "_for_app_" ++ Args.target args,
1219                     optLibs = [ In InstallTree arch "/lib/libarrakis.a" ] ++
1220                               ((optLibs $ options arch) \\
1221                                [ In InstallTree arch "/lib/libbarrelfish.a" ]),
1222                     extraFlags = Args.addCFlags args,
1223                     extraCxxFlags = Args.addCxxFlags args,
1224                     extraLdFlags = [ Str f | f <- Args.addLinkFlags args ],
1225                     extraDependencies =
1226                         [Dep BuildTree arch s | s <- Args.addGeneratedDependencies args]
1227                   }
1228
1229arrakisAppBuildArch tdb tf args arch =
1230    let -- Fiddle the options
1231        opts = arrakisAppGetOptionsForArch arch args
1232        csrcs = Args.cFiles args
1233        cxxsrcs = Args.cxxFiles args
1234        gencsrc = Args.generatedCFiles args
1235        gencxxsrc = Args.generatedCxxFiles args
1236        appname = Args.target args
1237        -- XXX: Not sure if this is correct. Currently assuming that if the app
1238        -- contains C++ files, we have to use the C++ linker.
1239        mylink = if cxxsrcs == [] then link else linkCxx
1240    in
1241      Rules ( flounderRules opts args csrcs
1242              ++
1243              skateRules opts args csrcs
1244              ++
1245              [ mackerelDependencies opts m csrcs | m <- Args.mackerelDevices args ]
1246              ++
1247              [ compileCFiles opts csrcs,
1248                compileCxxFiles opts cxxsrcs,
1249                compileGeneratedCFiles opts gencsrc,
1250                compileGeneratedCxxFiles opts gencxxsrc,
1251                assembleSFiles opts (Args.assemblyFiles args),
1252                mylink opts (allObjectPaths opts args) (allLibraryPaths opts args) (allModulesPaths opts args) appname
1253              ]
1254            )
1255
1256--
1257-- Build a static library
1258--
1259
1260library :: Args.Args
1261library = Args.defaultArgs { Args.buildFunction = libraryBuildFn }
1262
1263libraryBuildFn :: TreeDB -> String -> Args.Args -> HRule
1264libraryBuildFn tdb tf args | debugFlag && trace (Args.showArgs (tf ++ " Library ") args) False = undefined
1265libraryBuildFn tdb tf args =
1266    Rules [ libBuildArch tdb tf args arch | arch <- Args.architectures args ]
1267
1268libGetOptionsForArch arch args =
1269    (options arch) { extraIncludes =
1270                         [ NoDep SrcTree "src" a | a <- Args.addIncludes args]
1271                         ++
1272                         [ NoDep SrcTree "src" ("/include" </> l) | l <- Args.addLibraries args ],
1273                     optIncludes = (optIncludes $ options arch) \\
1274                         [ NoDep SrcTree "src" i | i <- Args.omitIncludes args ],
1275                     optFlags = (optFlags $ options arch) \\
1276                                [ Str f | f <- Args.omitCFlags args ],
1277                     optCxxFlags = (optCxxFlags $ options arch) \\
1278                                   [ Str f | f <- Args.omitCxxFlags args ],
1279                     optSuffix = "_for_lib_" ++ Args.target args,
1280                     extraFlags = Args.addCFlags args,
1281                     extraCxxFlags = Args.addCxxFlags args,
1282                     extraDependencies =
1283                         [Dep BuildTree arch s | s <- Args.addGeneratedDependencies args]
1284                   }
1285
1286libBuildArch tdb tf args arch =
1287    let -- Fiddle the options
1288        opts = libGetOptionsForArch arch args
1289        csrcs = Args.cFiles args
1290        cxxsrcs = Args.cxxFiles args
1291        gencsrc = Args.generatedCFiles args
1292        gencxxsrc = Args.generatedCxxFiles args
1293    in
1294      Rules ( flounderRules opts args csrcs
1295              ++
1296              skateRules opts args csrcs
1297              ++
1298              [ mackerelDependencies opts m csrcs | m <- Args.mackerelDevices args ]
1299              ++
1300              [ compileCFiles opts csrcs,
1301                compileCxxFiles opts cxxsrcs,
1302                compileGeneratedCFiles opts gencsrc,
1303                compileGeneratedCxxFiles opts gencxxsrc,
1304                assembleSFiles opts (Args.assemblyFiles args),
1305                staticLibrary opts (Args.target args) (allObjectPaths opts args) (allLibraryPaths opts args)
1306              ]
1307            )
1308
1309--
1310-- Library dependecies
1311--
1312
1313-- The following code is under heavy construction, and also somewhat ugly
1314data LibDepTree = LibDep String | LibDeps [LibDepTree] deriving (Show,Eq)
1315
1316-- manually add dependencies for now (it would be better if each library
1317-- defined each own dependencies locally, but that does not seem to be an
1318-- easy thing to do currently
1319libposixcompat_deps   = LibDeps [ LibDep "posixcompat",
1320                                  (libvfs_deps_all "vfs"), LibDep "term_server" ]
1321liblwip_deps          = LibDeps $ [ LibDep x | x <- deps ]
1322    where deps = ["lwip" ,"net_if_raw" ,"timer" ,"hashtable", "netbench" ]
1323libnetQmng_deps       = LibDeps $ [ LibDep x | x <- deps ]
1324    where deps = ["net_queue_manager"]
1325libnfs_deps           = LibDeps $ [ LibDep "nfs", liblwip_deps]
1326
1327-- we need to make vfs more modular to make this actually useful
1328data VFSModules = VFS_RamFS | VFS_NFS | VFS_BlockdevFS | VFS_FAT
1329vfsdeps :: [VFSModules] -> String -> [LibDepTree]
1330vfsdeps [] t                  = [LibDep t]
1331vfsdeps (VFS_RamFS:xs) t      = [] ++ vfsdeps xs t
1332vfsdeps (VFS_NFS:xs) t        = [libnfs_deps] ++ vfsdeps xs t
1333vfsdeps (VFS_BlockdevFS:xs) t = [LibDep "ahci", LibDep "megaraid"] ++ vfsdeps xs t
1334vfsdeps (VFS_FAT:xs) t        = [] ++ vfsdeps xs t
1335
1336libvfs_deps_all t        = LibDeps $ (vfsdeps [VFS_NFS, VFS_RamFS, VFS_BlockdevFS,
1337                                               VFS_FAT] t)
1338libvfs_deps_noblockdev t = LibDeps $ (vfsdeps [VFS_NFS, VFS_RamFS] t)
1339libvfs_deps_nonfs t      = LibDeps $ (vfsdeps [VFS_RamFS, VFS_BlockdevFS, VFS_FAT] t)
1340libvfs_deps_nfs t        = LibDeps $ (vfsdeps [VFS_NFS] t)
1341libvfs_deps_ramfs t      = LibDeps $ (vfsdeps [VFS_RamFS] t)
1342libvfs_deps_blockdevfs t = LibDeps $ (vfsdeps [VFS_BlockdevFS] t)
1343libvfs_deps_fat t        = LibDeps $ (vfsdeps [VFS_FAT, VFS_BlockdevFS] t)
1344
1345-- flatten the dependency tree
1346flat :: [LibDepTree] -> [LibDepTree]
1347flat [] = []
1348flat ((LibDep  l):xs) = [LibDep l] ++ flat xs
1349flat ((LibDeps t):xs) = flat t ++ flat xs
1350
1351str2dep :: String -> LibDepTree
1352str2dep  str
1353    | str == "vfs"           = libvfs_deps_all str
1354    | str == "vfs_ramfs"     = libvfs_deps_ramfs str
1355    | str == "vfs_nonfs"     = libvfs_deps_nonfs str
1356    | str == "vfs_noblockdev"= libvfs_deps_noblockdev str
1357    | str == "lwip"          = liblwip_deps
1358    | str == "netQmng"       = libnetQmng_deps
1359    | otherwise              = LibDep str
1360
1361-- get library depdencies
1362--   we need a specific order for the .a, so we define a total order
1363libDeps :: [String] -> [String]
1364libDeps xs = [x | (LibDep x) <- (sortBy xcmp) . nub . flat $ map str2dep xs ]
1365    where xord = [  "crypto"
1366                  , "zlib"
1367                  , "posixcompat"
1368                  , "term_server"
1369                  , "vfs"
1370                  , "ahci"
1371                  , "megaraid"
1372                  , "nfs"
1373                  , "net_queue_manager"
1374                  , "bfdmuxvm"
1375                  , "lwip"
1376                  , "arranet"
1377                  , "e1000n"
1378                  , "e10k"
1379                  , "e10k_vf"
1380                  , "contmng"
1381                  , "procon"
1382                  , "net_if_raw"
1383                  , "vfsfd"
1384                  , "timer"
1385                  , "hashtable"]
1386          xcmp (LibDep a) (LibDep b) = compare (elemIndex a xord) (elemIndex b xord)
1387
1388
1389--
1390-- Build a CPU driver
1391--
1392
1393cpuDriver :: Args.Args
1394cpuDriver = Args.defaultArgs { Args.buildFunction = cpuDriverBuildFn,
1395                               Args.target = "cpu",
1396                               Args.driverType = "cpu" }
1397
1398bootDriver :: Args.Args
1399bootDriver = Args.defaultArgs { Args.buildFunction = cpuDriverBuildFn,
1400                                Args.driverType = "boot" }
1401
1402-- CPU drivers are built differently
1403cpuDriverBuildFn :: TreeDB -> String -> Args.Args -> HRule
1404cpuDriverBuildFn tdb tf args = Rules []
1405
1406bootDriverBuildFn :: TreeDB -> String -> Args.Args -> HRule
1407bootDriverBuildFn tdb tf args = Rules []
1408
1409--
1410-- Build a platform
1411--
1412platform :: String -> [ String ] -> [ ( String, String ) ] -> String -> HRule
1413platform name archs files docstr =
1414  if null $ archs Data.List.\\ Config.architectures then
1415    Rules [
1416      Phony name False
1417      ([ NStr "@echo 'Built platform <",  NStr name, NStr ">'" ] ++
1418       [ Dep BuildTree arch file | (arch,file) <- files ]) ,
1419      Phony "clean-platform" True
1420      ([ NStr "@echo 'Cleaning platform <",  NStr name, NStr ">'", NL,
1421         Str "$(RM)" ] ++
1422       [ NoDep BuildTree arch file | (arch,file) <- files ]),
1423      Phony ("install_" ++ name) False
1424      ([ NStr "@echo 'Installing platform <",  NStr name, NStr ">'" ] ++
1425       [ NL, Str "rsync -v -a --relative" ] ++
1426       [ In BuildTree arch file | (arch,file) <- files ] ++
1427       [ Str "${INSTALL_PREFIX}" ]),
1428      Phony "help-platforms" True
1429      [ Str "@echo \"", NStr name, Str ":\\n\\t", NStr docstr, Str "\"",
1430        Dep BuildTree "root" "/help-platforms-header" ]
1431      ]
1432  else
1433    Rules []
1434
1435--
1436-- Boot an image.
1437--   name: the boot target name
1438--   archs: list of architectures required
1439--   tokens: the hake tokens for the target
1440--   docstr: description of the target
1441--
1442boot :: String -> [ String ] -> [ RuleToken ] -> String -> HRule
1443boot name archs tokens docstr =
1444  if null $ archs Data.List.\\ Config.architectures then
1445    Rules [
1446      Phony name False tokens,
1447      Phony "help-boot" True
1448      [ Str "@echo \"", NStr name, Str ":\\n\\t", NStr docstr, Str "\"",
1449        Dep BuildTree "root" "/help-boot-header"  ]
1450      ]
1451  else
1452    Rules []
1453
1454--
1455-- Copy a file from the source tree
1456--
1457copyFile :: TreeRef -> String -> String -> String -> String -> HRule
1458copyFile stree sarch spath darch dpath =
1459  Rule [ Str "cp", Str "-v", In stree sarch spath, Out darch dpath ]
1460
1461getExternalDependency :: String -> String -> [ HRule ]
1462getExternalDependency url name =
1463    [
1464        Rule ( [
1465            Str "curl",
1466            Str "--insecure",
1467            Str "--create-dirs",
1468            Str "-o",
1469            Out "cache" name,
1470            Str url
1471        ] ),
1472        copyFile SrcTree "cache" name "" name
1473    ]
1474