Manually control more of the Cabal flags for the compiler and ghc packages
[ghc-hetmet.git] / compiler / ghc.cabal.in
1 -- WARNING: ghc.cabal is automatically generated from ghc.cabal.in by
2 -- ./configure.  Make sure you are editing ghc.cabal.in, not ghc.cabal.
3
4 Name: ghc
5 Version: @ProjectVersion@
6 License: BSD3
7 License-File: ../LICENSE
8 Author: The GHC Team
9 Maintainer: glasgow-haskell-users@haskell.org
10 Homepage: http://www.haskell.org/ghc/
11 Synopsis: The GHC API
12 Description:
13     GHC's functionality can be useful for more things than just
14     compiling Haskell programs. Important use cases are programs
15     that analyse (and perhaps transform) Haskell code. Others
16     include loading Haskell code dynamically in a GHCi-like manner.
17     For this reason, a lot of GHC's functionality is made available
18     through this package.
19 Category: Development
20 Build-Type: Simple
21 Cabal-Version: >= 1.2.3
22
23 Flag base4
24     Description: Choose the even newer, even smaller, split-up base package.
25
26 Flag base3
27     Description: Choose the new smaller, split-up base package.
28
29 Flag dynlibs
30     Description: Dynamic library support
31     Default: False
32     Manual: True
33
34 Flag ghci
35     Description: Build GHCi support.
36     Default: False
37     Manual: True
38
39 Flag ncg
40     Description: Build the NCG.
41     Default: False
42     Manual: True
43
44 Flag stage1
45     Description: Is this stage 1?
46     Default: False
47     Manual: True
48
49 Flag stage2
50     Description: Is this stage 2?
51     Default: False
52     Manual: True
53
54 Flag stage3
55     Description: Is this stage 3?
56     Default: False
57     Manual: True
58
59 Library
60     Exposed: False
61
62     if flag(base4)
63         Build-Depends: base       >= 4   && < 5
64     if flag(base3)
65         Build-Depends: base       >= 3   && < 4
66     if !flag(base3) && !flag(base4)
67         Build-Depends: base       < 3
68
69     if flag(base3) || flag(base4)
70         Build-Depends: directory  >= 1   && < 1.2,
71                        process    >= 1   && < 1.1,
72                        bytestring >= 0.9 && < 0.10,
73                        old-time   >= 1   && < 1.1,
74                        containers >= 0.1 && < 0.5,
75                        array      >= 0.1 && < 0.4
76
77     Build-Depends: filepath >= 1 && < 1.3
78     Build-Depends: Cabal, hpc
79     if os(windows)
80         Build-Depends: Win32
81     else
82         Build-Depends: unix
83
84     GHC-Options: -Wall -fno-warn-name-shadowing -fno-warn-orphans
85
86     if flag(ghci)
87         Build-Depends: template-haskell
88         CPP-Options: -DGHCI
89         Include-Dirs: ../libffi/build/include
90
91     if !flag(ncg)
92         CPP-Options: -DOMIT_NATIVE_CODEGEN
93
94     Build-Depends: bin-package-db
95
96     -- GHC 6.4.2 needs to be able to find WCsubst.c, which needs to be
97     -- able to find WCsubst.h
98     Include-Dirs: ../libraries/base/cbits, ../libraries/base/include
99
100     Extensions: CPP, MagicHash, UnboxedTuples, PatternGuards,
101                 ForeignFunctionInterface, EmptyDataDecls,
102                 TypeSynonymInstances, MultiParamTypeClasses,
103                 FlexibleInstances, Rank2Types, ScopedTypeVariables,
104                 DeriveDataTypeable
105     if impl(ghc >= 7.1)
106         Extensions: NondecreasingIndentation
107
108     Include-Dirs: . parser utils
109
110     if flag(stage1)
111         Include-Dirs: stage1
112     else
113         if flag(stage2)
114             Include-Dirs: stage2
115         else
116             if flag(stage3)
117                 Include-Dirs: stage2
118
119     Install-Includes: HsVersions.h, ghc_boot_platform.h
120
121     c-sources:
122         parser/cutils.c
123         utils/md5.c
124
125     if flag(dynlibs)
126         c-sources:
127             ghci/keepCAFsForGHCi.c
128
129     hs-source-dirs:
130         basicTypes
131         cmm
132         codeGen
133         coreSyn
134         deSugar
135         ghci
136         hsSyn
137         iface
138         llvmGen
139         main
140         nativeGen
141         parser
142         prelude
143         profiling
144         rename
145         simplCore
146         simplStg
147         specialise
148         stgSyn
149         stranal
150         typecheck
151         types
152         utils
153         vectorise
154
155     Exposed-Modules:
156         BasicTypes
157         DataCon
158         Demand
159         Exception
160         GhcMonad
161         Id
162         IdInfo
163         Literal
164         Llvm
165         Llvm.AbsSyn
166         Llvm.PpLlvm
167         Llvm.Types
168         LlvmCodeGen
169         LlvmCodeGen.Base
170         LlvmCodeGen.CodeGen
171         LlvmCodeGen.Data
172         LlvmCodeGen.Ppr
173         LlvmCodeGen.Regs
174         LlvmMangler
175         MkId
176         Module
177         Name
178         NameEnv
179         NameSet
180         OccName
181         RdrName
182         SrcLoc
183         UniqSupply
184         Unique
185         Var
186         VarEnv
187         VarSet
188         BlockId
189         CLabel
190         Cmm
191         CmmBrokenBlock
192         CmmBuildInfoTables
193         CmmCPS
194         CmmCPSGen
195         CmmCPSZ
196         CmmCallConv
197         CmmCommonBlockElimZ
198         CmmContFlowOpt
199         CmmCvt
200         CmmExpr
201         CmmInfo
202         CmmLex
203         CmmLint
204         CmmLive
205         CmmLiveZ
206         CmmOpt
207         CmmParse
208         CmmProcPoint
209         CmmProcPointZ
210         CmmSpillReload
211         CmmStackLayout
212         CmmTx
213         CmmUtils
214         CmmZipUtil
215         DFMonad
216         Dataflow
217         MkZipCfg
218         MkZipCfgCmm
219         OptimizationFuel
220         PprBase
221         PprC
222         PprCmm
223         PprCmmZ
224         StackColor
225         StackPlacements
226         ZipCfg
227         ZipCfgCmmRep
228         ZipCfgExtras
229         ZipDataflow
230         Bitmap
231         CgBindery
232         CgCallConv
233         CgCase
234         CgClosure
235         CgCon
236         CgExpr
237         CgExtCode
238         CgForeignCall
239         CgHeapery
240         CgHpc
241         CgInfoTbls
242         CgLetNoEscape
243         CgMonad
244         CgParallel
245         CgPrimOp
246         CgProf
247         CgStackery
248         CgTailCall
249         CgTicky
250         CgUtils
251         StgCmm
252         StgCmmBind
253         StgCmmClosure
254         StgCmmCon
255         StgCmmEnv
256         StgCmmExpr
257         StgCmmForeign
258         StgCmmGran
259         StgCmmHeap
260         StgCmmHpc
261         StgCmmLayout
262         StgCmmMonad
263         StgCmmPrim
264         StgCmmProf
265         StgCmmTicky
266         StgCmmUtils
267         ClosureInfo
268         CodeGen
269         SMRep
270         CoreArity
271         CoreFVs
272         CoreLint
273         CorePrep
274         CoreSubst
275         CoreSyn
276         CoreTidy
277         CoreUnfold
278         CoreUtils
279         ExternalCore
280         MkCore
281         MkExternalCore
282         PprCore
283         PprExternalCore
284         Check
285         Coverage
286         Desugar
287         DsArrows
288         DsBinds
289         DsCCall
290         DsExpr
291         DsForeign
292         DsGRHSs
293         DsListComp
294         DsMonad
295         DsUtils
296         Match
297         MatchCon
298         MatchLit
299         HsBinds
300         HsDecls
301         HsDoc
302         HsExpr
303         HsImpExp
304         HsLit
305         HsPat
306         HsSyn
307         HsTypes
308         HsUtils
309         BinIface
310         BuildTyCl
311         IfaceEnv
312         IfaceSyn
313         IfaceType
314         LoadIface
315         MkIface
316         TcIface
317         Annotations
318         BreakArray
319         CmdLineParser
320         CodeOutput
321         Config
322         Constants
323         DriverMkDepend
324         DriverPhases
325         DriverPipeline
326         DynFlags
327         ErrUtils
328         Finder
329         GHC
330         HeaderInfo
331         HscMain
332         HscStats
333         HscTypes
334         InteractiveEval
335         PackageConfig
336         Packages
337         PprTyThing
338         StaticFlags
339         StaticFlagParser
340         SysTools
341         TidyPgm
342         Ctype
343         HaddockUtils
344         LexCore
345         Lexer
346         OptCoercion
347         Parser
348         ParserCore
349         ParserCoreUtils
350         RdrHsSyn
351         ForeignCall
352         PrelInfo
353         PrelNames
354         PrelRules
355         PrimOp
356         TysPrim
357         TysWiredIn
358         CostCentre
359         SCCfinal
360         RnBinds
361         RnEnv
362         RnExpr
363         RnHsDoc
364         RnHsSyn
365         RnNames
366         RnPat
367         RnSource
368         RnTypes
369         CoreMonad
370         CSE
371         FloatIn
372         FloatOut
373         LiberateCase
374         OccurAnal
375         SAT
376         SetLevels
377         SimplCore
378         SimplEnv
379         SimplMonad
380         SimplUtils
381         Simplify
382         SRT
383         SimplStg
384         StgStats
385         Rules
386         SpecConstr
387         Specialise
388         CoreToStg
389         StgLint
390         StgSyn
391         DmdAnal
392         WorkWrap
393         WwLib
394         FamInst
395         Inst
396         TcAnnotations
397         TcArrows
398         TcBinds
399         TcClassDcl
400         TcDefaults
401         TcDeriv
402         TcEnv
403         TcExpr
404         TcForeign
405         TcGenDeriv
406         TcHsSyn
407         TcHsType
408         TcInstDcls
409         TcMType
410         TcMatches
411         TcPat
412         TcRnDriver
413         TcRnMonad
414         TcRnTypes
415         TcRules
416         TcSimplify
417         TcErrors
418         TcTyClsDecls
419         TcTyDecls
420         TcType
421         TcUnify
422         TcInteract
423         TcCanonical
424         TcSMonad
425         Class
426         Coercion
427         FamInstEnv
428         FunDeps
429         Generics
430         InstEnv
431         TyCon
432         Type
433         TypeRep
434         Unify
435         Bag
436         Binary
437         BufWrite
438         Digraph
439         Encoding
440         FastBool
441         FastFunctions
442         FastMutInt
443         FastString
444         FastTypes
445         Fingerprint
446         FiniteMap
447         GraphBase
448         GraphColor
449         GraphOps
450         GraphPpr
451         IOEnv
452         Interval
453         ListSetOps
454         Maybes
455         MonadUtils
456         OrdList
457         Outputable
458         Panic
459         Pretty
460         Serialized
461         State
462         StringBuffer
463         UniqFM
464         UniqSet
465         Util
466         Vectorise.Builtins.Base
467         Vectorise.Builtins.Initialise
468         Vectorise.Builtins.Modules
469         Vectorise.Builtins.Prelude
470         Vectorise.Builtins
471         Vectorise.Monad.Base
472         Vectorise.Monad.Naming
473         Vectorise.Monad.Local
474         Vectorise.Monad.Global
475         Vectorise.Monad.InstEnv
476         Vectorise.Monad
477         Vectorise.Utils.Base
478         Vectorise.Utils.Closure
479         Vectorise.Utils.Hoisting
480         Vectorise.Utils.PADict
481         Vectorise.Utils.PRDict
482         Vectorise.Utils.Poly
483         Vectorise.Utils
484         Vectorise.Type.Env
485         Vectorise.Type.Repr
486         Vectorise.Type.PData
487         Vectorise.Type.PRepr
488         Vectorise.Type.PADict
489         Vectorise.Type.PRDict
490         Vectorise.Type.Type
491         Vectorise.Type.TyConDecl
492         Vectorise.Type.Classify
493         Vectorise.Convert
494         Vectorise.Vect
495         Vectorise.Var
496         Vectorise.Env
497         Vectorise.Exp
498         Vectorise
499
500     -- We only need to expose more modules as some of the ncg code is used
501     -- by the LLVM backend so its always included
502     if flag(ncg)
503         Exposed-Modules:
504             AsmCodeGen
505             TargetReg
506             NCGMonad
507             Instruction
508             Size
509             Reg
510             RegClass
511             PIC
512             Platform
513             Alpha.Regs
514             Alpha.RegInfo
515             Alpha.Instr
516             Alpha.CodeGen
517             X86.Regs
518             X86.RegInfo
519             X86.Instr
520             X86.Cond
521             X86.Ppr
522             X86.CodeGen
523             PPC.Regs
524             PPC.RegInfo
525             PPC.Instr
526             PPC.Cond
527             PPC.Ppr
528             PPC.CodeGen
529             SPARC.Base
530             SPARC.Regs
531             SPARC.RegPlate
532             SPARC.Imm
533             SPARC.AddrMode
534             SPARC.Cond
535             SPARC.Instr
536             SPARC.Stack
537             SPARC.ShortcutJump
538             SPARC.Ppr
539             SPARC.CodeGen
540             SPARC.CodeGen.Amode
541             SPARC.CodeGen.Base
542             SPARC.CodeGen.CCall
543             SPARC.CodeGen.CondCode
544             SPARC.CodeGen.Gen32
545             SPARC.CodeGen.Gen64
546             SPARC.CodeGen.Sanity
547             SPARC.CodeGen.Expand
548             RegAlloc.Liveness
549             RegAlloc.Graph.Main
550             RegAlloc.Graph.Stats
551             RegAlloc.Graph.ArchBase
552             RegAlloc.Graph.ArchX86
553             RegAlloc.Graph.Coalesce
554             RegAlloc.Graph.Spill
555             RegAlloc.Graph.SpillClean
556             RegAlloc.Graph.SpillCost
557             RegAlloc.Graph.TrivColorable
558             RegAlloc.Linear.Main
559             RegAlloc.Linear.JoinToTargets
560             RegAlloc.Linear.State
561             RegAlloc.Linear.Stats
562             RegAlloc.Linear.FreeRegs
563             RegAlloc.Linear.StackMap
564             RegAlloc.Linear.Base
565             RegAlloc.Linear.X86.FreeRegs
566             RegAlloc.Linear.PPC.FreeRegs
567             RegAlloc.Linear.SPARC.FreeRegs
568
569     if flag(ghci)
570         Exposed-Modules:
571             DsMeta
572             TcSplice
573             Convert
574             ByteCodeAsm
575             ByteCodeFFI
576             ByteCodeGen
577             ByteCodeInstr
578             ByteCodeItbls
579             ByteCodeLink
580             Debugger
581             LibFFI
582             Linker
583             ObjLink
584             RtClosureInspect
585