1--------------------------------------------------------------------------
2-- Copyright (c) 2007-2010, 2012, 2013, 2015 ETH Zurich.
3-- Copyright (c) 2014, HP Labs.
4-- All rights reserved.
5--
6-- This file is distributed under the terms in the attached LICENSE file.
7-- If you do not find this file, copies can be found by writing to:
8-- ETH Zurich D-INFK, CAB F.78, Universitaetstrasse 6, CH-8092 Zurich,
9-- Attn: Systems Group.
10--
11-- Configuration options for Hake
12--
13--------------------------------------------------------------------------
14
15module Config where
16
17import HakeTypes
18import Data.Char
19import qualified Args
20import Data.List
21import Data.Maybe
22import System.FilePath
23import Tools (findTool, ToolDetails, toolPath, toolPrefix)
24import qualified Tools
25
26-- Set by hake.sh
27toolroot         :: Maybe FilePath
28arm_toolspec     :: Maybe (Maybe FilePath -> ToolDetails)
29aarch64_toolspec :: Maybe (Maybe FilePath -> ToolDetails)
30thumb_toolspec   :: Maybe (Maybe FilePath -> ToolDetails)
31armeb_toolspec   :: Maybe (Maybe FilePath -> ToolDetails)
32x86_toolspec     :: Maybe (Maybe FilePath -> ToolDetails)
33k1om_toolspec    :: Maybe (Maybe FilePath -> ToolDetails)
34
35-- Default toolchains
36arm_tools     = fromMaybe Tools.arm_system
37                          arm_toolspec
38                toolroot
39aarch64_tools = fromMaybe Tools.aarch64_system
40                          aarch64_toolspec
41                toolroot
42thumb_tools   = fromMaybe Tools.arm_netos_arm_2015q2
43                          thumb_toolspec
44                toolroot
45armeb_tools   = fromMaybe Tools.arm_netos_linaro_be_2015_02
46                          armeb_toolspec
47                toolroot
48x86_tools     = fromMaybe Tools.x86_system
49                          x86_toolspec
50                toolroot
51k1om_tools    = fromMaybe Tools.k1om_netos_mpss_3_7_1
52                          k1om_toolspec
53                toolroot
54
55-- ARM toolchain
56arm_gnu_tool = findTool (toolPath arm_tools) (toolPrefix arm_tools)
57arm_cc       = arm_gnu_tool "gcc"
58arm_objcopy  = arm_gnu_tool "objcopy"
59arm_objdump  = arm_gnu_tool "objdump"
60arm_ar       = arm_gnu_tool "ar"
61arm_ranlib   = arm_gnu_tool "ranlib"
62arm_cxx      = arm_gnu_tool "g++"
63
64-- ARM AArch64
65aarch64_gnu_tool = findTool (toolPath aarch64_tools) (toolPrefix aarch64_tools)
66aarch64_cc       = aarch64_gnu_tool "gcc"
67aarch64_objcopy  = aarch64_gnu_tool "objcopy"
68aarch64_objdump  = aarch64_gnu_tool "objdump"
69aarch64_ar       = aarch64_gnu_tool "ar"
70aarch64_ranlib   = aarch64_gnu_tool "ranlib"
71aarch64_cxx      = aarch64_gnu_tool "g++"
72
73-- ARM thumb (e.g. -M profile) toolchain
74thumb_gnu_tool = findTool (toolPath thumb_tools) (toolPrefix thumb_tools)
75thumb_cc       = thumb_gnu_tool "gcc"
76thumb_objcopy  = thumb_gnu_tool "objcopy"
77thumb_objdump  = thumb_gnu_tool "objdump"
78thumb_ar       = thumb_gnu_tool "ar"
79thumb_ranlib   = thumb_gnu_tool "ranlib"
80thumb_cxx      = thumb_gnu_tool "g++"
81
82-- ARM big-endian (e.g. XScale) toolchain
83armeb_gnu_tool = findTool (toolPath armeb_tools) (toolPrefix armeb_tools)
84armeb_cc       = armeb_gnu_tool "gcc"
85armeb_objcopy  = armeb_gnu_tool "objcopy"
86armeb_objdump  = armeb_gnu_tool "objdump"
87armeb_ar       = armeb_gnu_tool "ar"
88armeb_ranlib   = armeb_gnu_tool "ranlib"
89armeb_cxx      = armeb_gnu_tool "g++"
90
91-- X86_64 toolchain
92x86_gnu_tool = findTool (toolPath x86_tools) (toolPrefix x86_tools)
93x86_cc       = x86_gnu_tool "gcc"
94x86_objcopy  = x86_gnu_tool "objcopy"
95x86_objdump  = x86_gnu_tool "objdump"
96x86_ar       = x86_gnu_tool "ar"
97x86_ranlib   = x86_gnu_tool "ranlib"
98x86_cxx      = x86_gnu_tool "g++"
99
100-- Xeon Phi toolchain
101k1om_gnu_tool = findTool (toolPath k1om_tools) (toolPrefix k1om_tools)
102k1om_cc      = k1om_gnu_tool "gcc"
103k1om_objcopy = k1om_gnu_tool "objcopy"
104k1om_objdump = k1om_gnu_tool "objdump"
105k1om_ar      = k1om_gnu_tool "ar"
106k1om_ranlib  = k1om_gnu_tool "ranlib"
107k1om_cxx     = k1om_gnu_tool "g++"
108
109-- Miscellaneous tools
110gem5         = "gem5.fast"
111runghc       = "runghc"    -- run GHC interactively
112circo        = "circo"     -- from graphviz
113dot          = "dot"       --   "    "
114inkscape     = "inkscape"
115
116-- ARM Fast Models Simulator TODO: make this in
117fastmodels_root    = "/home/netos/tools/FastModels_11.6/FastModelsTools_11.6"
118fastmodels_env     = fastmodels_root </> "/source_all.sh"
119fastmodels_simgen  = fastmodels_root </> "bin/simgen"
120
121
122-- path to source and install directories; these are automatically set by
123-- hake.sh at setup time
124source_dir :: String
125-- source_dir = undefined -- (set by hake.sh, see end of file)
126
127install_dir :: String
128-- install_dir = undefined -- (set by hake.sh, see end of file)
129
130cache_dir :: String
131-- cache_dir = undefined -- (set by hake.sh, see end of file)
132
133-- Set of architectures for which to generate rules
134architectures :: [String]
135-- architectures = undefined -- (set by hake.sh, see end of file)
136
137-- Optimisation flags (-Ox -g etc.) passed to compiler
138cOptFlags :: [String]
139cOptFlags = ["-g", "-O2"]
140
141newlib_malloc :: String
142--newlib_malloc = "sbrk"     -- use sbrk and newlib's malloc()
143--newlib_malloc = "dlmalloc" -- use dlmalloc
144newlib_malloc = "oldmalloc"
145
146-- Print NYI mmap() flags for each call
147libc_mmap_nyi_flags :: Bool
148libc_mmap_nyi_flags = False
149
150-- Configure pagesize for libbarrelfish's morecore implementation
151-- x86_64 accepts "small", "large", and "huge" for 4kB, 2MB and 1GB pages
152-- respectively. All other architectures default to their default page size.
153morecore_pagesize :: String
154morecore_pagesize = "small"
155
156-- Use a frame pointer
157use_fp :: Bool
158use_fp = True
159
160-- Default timeslice duration in milliseconds
161timeslice :: Integer
162timeslice = 80
163
164-- Put kernel into microbenchmarks mode
165microbenchmarks :: Bool
166microbenchmarks = False
167
168-- Enable tracing
169trace :: Bool
170trace = False
171
172-- Enable QEMU networking. (ie. make network work in small memory)
173support_qemu_networking :: Bool
174support_qemu_networking  = False
175
176-- enable network tracing
177trace_network_subsystem :: Bool
178trace_network_subsystem = False
179
180-- May want to disable LRPC to improve trace visuals
181trace_disable_lrpc :: Bool
182trace_disable_lrpc = False
183
184-- use Kaluga
185use_kaluga_dvm :: Bool
186use_kaluga_dvm = True
187
188-- Domain and driver debugging
189global_debug :: Bool
190global_debug = False
191
192e1000n_debug :: Bool
193e1000n_debug = False
194
195eMAC_debug :: Bool
196eMAC_debug = False
197
198rtl8029_debug :: Bool
199rtl8029_debug = False
200
201ahcid_debug :: Bool
202ahcid_debug = False
203
204libahci_debug :: Bool
205libahci_debug = False
206
207vfs_debug :: Bool
208vfs_debug = False
209
210ethersrv_debug :: Bool
211ethersrv_debug = False
212
213netd_debug :: Bool
214netd_debug = False
215
216libacpi_debug :: Bool
217libacpi_debug = False
218
219acpi_interface_debug :: Bool
220acpi_interface_debug = False
221
222acpi_service_debug :: Bool
223acpi_service_debug = False
224
225acpi_server_debug :: Bool
226acpi_server_debug = False
227
228lpc_timer_debug :: Bool
229lpc_timer_debug = False
230
231lwip_debug :: Bool
232lwip_debug = False
233
234libpci_debug :: Bool
235libpci_debug = False
236
237usrpci_debug :: Bool
238usrpci_debug = False
239
240timer_debug :: Bool
241timer_debug = False
242
243eclipse_kernel_debug :: Bool
244eclipse_kernel_debug = False
245
246skb_debug :: Bool
247skb_debug = False
248
249skb_client_debug :: Bool
250skb_client_debug = False
251
252flounder_debug :: Bool
253flounder_debug = False
254
255flounder_failed_debug :: Bool
256flounder_failed_debug = False
257
258webserver_debug :: Bool
259webserver_debug = False
260
261sqlclient_debug :: Bool
262sqlclient_debug = False
263
264sqlite_debug :: Bool
265sqlite_debug = False
266
267sqlite_backend_debug :: Bool
268sqlite_backend_debug = False
269
270nfs_debug :: Bool
271nfs_debug = False
272
273rpc_debug :: Bool
274rpc_debug = False
275
276loopback_debug :: Bool
277loopback_debug = False
278
279octopus_debug :: Bool
280octopus_debug = False
281
282term_debug :: Bool
283term_debug = False
284
285serial_debug :: Bool
286serial_debug = False
287
288-- Deadlock debugging
289debug_deadlocks :: Bool
290debug_deadlocks = False
291
292-- Partitioned memory server
293memserv_percore :: Bool
294memserv_percore = False
295
296-- Lazy THC implementation (requires use_fp = True)
297lazy_thc :: Bool
298lazy_thc
299    | elem "armv7" architectures   = False
300    | elem "armv8" architectures   = False
301    | otherwise                    = True
302
303-- Enable capability tracing debug facility
304caps_trace :: Bool
305caps_trace = False
306
307-- Mapping Database configuration options (this affects lib/mdb/)
308-- enable extensive tracing of mapping db implementation
309mdb_trace :: Bool
310mdb_trace = False
311
312-- enable tracing of top level mdb_insert, mdb_remove calls
313mdb_trace_no_recursive :: Bool
314mdb_trace_no_recursive = False
315
316-- fail on invariant violations
317mdb_fail_invariants :: Bool
318mdb_fail_invariants = True
319
320-- check invariants before/after mdb_insert/mdb_remove.
321mdb_check_invariants :: Bool
322mdb_check_invariants = False
323
324-- recheck invariants at each tracing point
325mdb_recheck_invariants :: Bool
326mdb_recheck_invariants = False
327
328-- enable extensive tracing of mapping db implementation (userspace version)
329mdb_trace_user :: Bool
330mdb_trace_user = False
331
332-- fail on invariant violations
333mdb_fail_invariants_user :: Bool
334mdb_fail_invariants_user = True
335
336-- recheck invariants at each tracing point
337mdb_recheck_invariants_user :: Bool
338mdb_recheck_invariants_user = True
339
340-- check invariants before/after mdb_insert/mdb_remove.
341mdb_check_invariants_user :: Bool
342mdb_check_invariants_user = True
343
344-- Select scheduler
345data Scheduler = RBED | RR deriving (Show,Eq)
346scheduler :: Scheduler
347scheduler = RBED
348
349-- No Execute Extensions (NXE)-enabled paging on x86
350nxe_paging :: Bool
351nxe_paging = False
352
353oneshot_timer :: Bool
354oneshot_timer = False
355
356-- Enable hardware VM support for AMD's Secure Virtual Machine (SVM)
357-- If disabled, Intel's VMX hardware is supported instead
358config_svm :: Bool
359config_svm = True
360
361-- Enable the use of only Arrakis domains (with arrakismon)
362-- If disabled, use normal VM-guests (with vmkitmon)
363config_arrakismon :: Bool
364config_arrakismon = False
365
366-- Registry of library OSes.
367--
368-- This is necessary so we can add the right compiler flags (#defines etc)
369-- when an application wants to link against a particular library OS.
370--
371-- each libraryos option is an instance of (Maybe Args.Args) with the right
372-- content and is used when generating make rules.
373--
374-- Applications and libraries use "libbarrelfish" when the libraryOs field in
375-- their Args is not overwritten by the Hakefile.
376--
377-- Implementation notes:
378--  * Unfortunately we need to have the list of available  library OSes here,
379--    because providing these flags and names in the library OS Hakefile is
380--    non-trivial
381--  * We need to name the library in these expressions so hake knows which .a
382--    to include when linking.
383--  * The library OS itself needs to use the matching Args from below as its
384--    own Args.libraryOs, see lib/barrelfish/Hakefile for examples.
385--  * All of these need to be instances of (Maybe Args).
386--  * The library OS choices provided by the default tree are all variations of
387--    the code in lib/barrelfish, gated by different preprocessor flags.
388--
389libbarrelfish_pmap_array :: Maybe Args.Args
390libbarrelfish_pmap_array = Just Args.defaultArgs {
391    Args.target = "barrelfish_pmap_array",
392    Args.addCFlags = [ "-DPMAP_ARRAY" ]
393}
394libbarrelfish_pmap_list :: Maybe Args.Args
395libbarrelfish_pmap_list = Just Args.defaultArgs {
396    Args.target = "barrelfish_pmap_ll",
397    Args.addCFlags = [ "-DPMAP_LL" ]
398}
399libarrakis :: Maybe Args.Args
400libarrakis = Just Args.defaultArgs {
401    -- lib/barrelfish/Hakefile defines libarrakis to use PMAP_ARRAY but not
402    -- global mapping cnodes.
403    Args.target = "arrakis",
404    Args.addCFlags = [ "-DARRAKIS", "-DPMAP_ARRAY" ]
405}
406libbarrelfish_pmap_array_mcn :: Maybe Args.Args
407libbarrelfish_pmap_array_mcn = Just Args.defaultArgs {
408    Args.target = "barrelfish_pmap_array_mcn",
409    Args.addCFlags = [ "-DGLOBAL_MCN", "-DPMAP_ARRAY" ]
410}
411libbarrelfish_pmap_list_mcn :: Maybe Args.Args
412libbarrelfish_pmap_list_mcn = Just Args.defaultArgs {
413    Args.target = "barrelfish_pmap_ll_mcn",
414    Args.addCFlags = [ "-DGLOBAL_MCN", "-DPMAP_LL" ]
415}
416
417-- Select default library OS for applications that don't specify one
418-- this is used as Config.libbarrelfish in the rest of the hake
419-- implementation.
420libbarrelfish :: String -> Maybe Args.Args
421-- armv7 only supports pmap_ll!
422libbarrelfish "armv7" = libbarrelfish_pmap_list
423libbarrelfish _       = libbarrelfish_pmap_array
424
425defines :: [RuleToken]
426defines = [ Str ("-D" ++ d) | d <- [
427             if microbenchmarks then "CONFIG_MICROBENCHMARKS" else "",
428             if trace then "CONFIG_TRACE" else "",
429             if support_qemu_networking then "CONFIG_QEMU_NETWORK" else "",
430             if trace_network_subsystem then "NETWORK_STACK_TRACE" else "",
431             if trace_disable_lrpc then "TRACE_DISABLE_LRPC" else "",
432             if global_debug then "GLOBAL_DEBUG" else "",
433             if e1000n_debug then "E1000N_SERVICE_DEBUG" else "",
434             if ahcid_debug then "AHCI_SERVICE_DEBUG" else "",
435             if libahci_debug then "AHCI_LIB_DEBUG" else "",
436             if vfs_debug then "VFS_DEBUG" else "",
437             if eMAC_debug then "EMAC_SERVICE_DEBUG" else "",
438             if rtl8029_debug then "RTL8029_SERVICE_DEBUG" else "",
439             if ethersrv_debug then "ETHERSRV_SERVICE_DEBUG" else "",
440             if netd_debug then "NETD_SERVICE_DEBUG" else "",
441             if libacpi_debug then "ACPI_DEBUG_OUTPUT" else "",
442             if acpi_interface_debug then "ACPI_BF_DEBUG" else "",
443             if acpi_service_debug then "ACPI_SERVICE_DEBUG" else "",
444             if lpc_timer_debug then "LPC_TIMER_DEBUG" else "",
445             if lwip_debug then "LWIP_BARRELFISH_DEBUG" else "",
446             if libpci_debug then "PCI_LIB_DEBUG" else "",
447             if usrpci_debug then "PCI_SERVICE_DEBUG" else "",
448             if timer_debug then "TIMER_CLIENT_DEBUG" else "",
449             if eclipse_kernel_debug then "ECLIPSE_KERNEL_DEBUG" else "",
450             if skb_debug then "SKB_SERVICE_DEBUG" else "",
451             if skb_client_debug then "SKB_CLIENT_DEBUG" else "",
452             if flounder_debug then "FLOUNDER_DEBUG" else "",
453             if flounder_failed_debug then "FLOUNDER_FAILED_DEBUG" else "",
454             if webserver_debug then "WEBSERVER_DEBUG" else "",
455             if sqlclient_debug then "SQL_CLIENT_DEBUG" else "",
456             if sqlite_debug then "SQL_SERVICE_DEBUG" else "",
457             if sqlite_backend_debug then "SQL_BACKEND_DEBUG" else "",
458             if nfs_debug then "NFS_CLIENT_DEBUG" else "",
459             if rpc_debug then "RPC_DEBUG" else "",
460             if loopback_debug then "LOOPBACK_DEBUG" else "",
461             if octopus_debug then "DIST_SERVICE_DEBUG" else "",
462             if term_debug then "TERMINAL_LIBRARY_DEBUG" else "",
463             if serial_debug then "SERIAL_DRIVER_DEBUG" else "",
464             if debug_deadlocks then "CONFIG_DEBUG_DEADLOCKS" else "",
465             if memserv_percore then "CONFIG_MEMSERV_PERCORE" else "",
466             if lazy_thc then "CONFIG_LAZY_THC" else "",
467             if nxe_paging then "CONFIG_NXE" else "",
468             if oneshot_timer then "CONFIG_ONESHOT_TIMER" else "",
469             if config_svm then "CONFIG_SVM" else "",
470             if config_arrakismon then "CONFIG_ARRAKISMON" else "",
471             if use_kaluga_dvm then "USE_KALUGA_DVM" else "",
472             if caps_trace then "TRACE_PMEM_CAPS" else ""
473             ], d /= "" ]
474
475
476-- some defines depend on the architecture/compile options
477arch_defines :: Options -> [RuleToken]
478arch_defines opts
479    -- enable config flags for interconnect drivers in use for this arch
480    = [ Str ("-D" ++ d)
481       | d <- ["CONFIG_INTERCONNECT_DRIVER_" ++ (map toUpper n)
482               | n <- optInterconnectDrivers opts]
483      ]
484    -- enable config flags for flounder backends in use for this arch
485    ++ [ Str ("-D" ++ d)
486       | d <- ["CONFIG_FLOUNDER_BACKEND_" ++ (map toUpper n)
487               | n <- optFlounderBackends opts]
488      ]
489