Split main/GHC into GHC and GhcMake
[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         GhcMake
331         HeaderInfo
332         HscMain
333         HscStats
334         HscTypes
335         InteractiveEval
336         PackageConfig
337         Packages
338         PprTyThing
339         StaticFlags
340         StaticFlagParser
341         SysTools
342         TidyPgm
343         Ctype
344         HaddockUtils
345         LexCore
346         Lexer
347         OptCoercion
348         Parser
349         ParserCore
350         ParserCoreUtils
351         RdrHsSyn
352         ForeignCall
353         PrelInfo
354         PrelNames
355         PrelRules
356         PrimOp
357         TysPrim
358         TysWiredIn
359         CostCentre
360         SCCfinal
361         RnBinds
362         RnEnv
363         RnExpr
364         RnHsDoc
365         RnHsSyn
366         RnNames
367         RnPat
368         RnSource
369         RnTypes
370         CoreMonad
371         CSE
372         FloatIn
373         FloatOut
374         LiberateCase
375         OccurAnal
376         SAT
377         SetLevels
378         SimplCore
379         SimplEnv
380         SimplMonad
381         SimplUtils
382         Simplify
383         SRT
384         SimplStg
385         StgStats
386         Rules
387         SpecConstr
388         Specialise
389         CoreToStg
390         StgLint
391         StgSyn
392         DmdAnal
393         WorkWrap
394         WwLib
395         FamInst
396         Inst
397         TcAnnotations
398         TcArrows
399         TcBinds
400         TcClassDcl
401         TcDefaults
402         TcDeriv
403         TcEnv
404         TcExpr
405         TcForeign
406         TcGenDeriv
407         TcHsSyn
408         TcHsType
409         TcInstDcls
410         TcMType
411         TcMatches
412         TcPat
413         TcRnDriver
414         TcRnMonad
415         TcRnTypes
416         TcRules
417         TcSimplify
418         TcErrors
419         TcTyClsDecls
420         TcTyDecls
421         TcType
422         TcUnify
423         TcInteract
424         TcCanonical
425         TcSMonad
426         Class
427         Coercion
428         FamInstEnv
429         FunDeps
430         Generics
431         InstEnv
432         TyCon
433         Type
434         TypeRep
435         Unify
436         Bag
437         Binary
438         BufWrite
439         Digraph
440         Encoding
441         FastBool
442         FastFunctions
443         FastMutInt
444         FastString
445         FastTypes
446         Fingerprint
447         FiniteMap
448         GraphBase
449         GraphColor
450         GraphOps
451         GraphPpr
452         IOEnv
453         Interval
454         ListSetOps
455         Maybes
456         MonadUtils
457         OrdList
458         Outputable
459         Panic
460         Pretty
461         Serialized
462         State
463         StringBuffer
464         UniqFM
465         UniqSet
466         Util
467         Vectorise.Builtins.Base
468         Vectorise.Builtins.Initialise
469         Vectorise.Builtins.Modules
470         Vectorise.Builtins.Prelude
471         Vectorise.Builtins
472         Vectorise.Monad.Base
473         Vectorise.Monad.Naming
474         Vectorise.Monad.Local
475         Vectorise.Monad.Global
476         Vectorise.Monad.InstEnv
477         Vectorise.Monad
478         Vectorise.Utils.Base
479         Vectorise.Utils.Closure
480         Vectorise.Utils.Hoisting
481         Vectorise.Utils.PADict
482         Vectorise.Utils.PRDict
483         Vectorise.Utils.Poly
484         Vectorise.Utils
485         Vectorise.Type.Env
486         Vectorise.Type.Repr
487         Vectorise.Type.PData
488         Vectorise.Type.PRepr
489         Vectorise.Type.PADict
490         Vectorise.Type.PRDict
491         Vectorise.Type.Type
492         Vectorise.Type.TyConDecl
493         Vectorise.Type.Classify
494         Vectorise.Convert
495         Vectorise.Vect
496         Vectorise.Var
497         Vectorise.Env
498         Vectorise.Exp
499         Vectorise
500
501     -- We only need to expose more modules as some of the ncg code is used
502     -- by the LLVM backend so its always included
503     if flag(ncg)
504         Exposed-Modules:
505             AsmCodeGen
506             TargetReg
507             NCGMonad
508             Instruction
509             Size
510             Reg
511             RegClass
512             PIC
513             Platform
514             Alpha.Regs
515             Alpha.RegInfo
516             Alpha.Instr
517             Alpha.CodeGen
518             X86.Regs
519             X86.RegInfo
520             X86.Instr
521             X86.Cond
522             X86.Ppr
523             X86.CodeGen
524             PPC.Regs
525             PPC.RegInfo
526             PPC.Instr
527             PPC.Cond
528             PPC.Ppr
529             PPC.CodeGen
530             SPARC.Base
531             SPARC.Regs
532             SPARC.RegPlate
533             SPARC.Imm
534             SPARC.AddrMode
535             SPARC.Cond
536             SPARC.Instr
537             SPARC.Stack
538             SPARC.ShortcutJump
539             SPARC.Ppr
540             SPARC.CodeGen
541             SPARC.CodeGen.Amode
542             SPARC.CodeGen.Base
543             SPARC.CodeGen.CCall
544             SPARC.CodeGen.CondCode
545             SPARC.CodeGen.Gen32
546             SPARC.CodeGen.Gen64
547             SPARC.CodeGen.Sanity
548             SPARC.CodeGen.Expand
549             RegAlloc.Liveness
550             RegAlloc.Graph.Main
551             RegAlloc.Graph.Stats
552             RegAlloc.Graph.ArchBase
553             RegAlloc.Graph.ArchX86
554             RegAlloc.Graph.Coalesce
555             RegAlloc.Graph.Spill
556             RegAlloc.Graph.SpillClean
557             RegAlloc.Graph.SpillCost
558             RegAlloc.Graph.TrivColorable
559             RegAlloc.Linear.Main
560             RegAlloc.Linear.JoinToTargets
561             RegAlloc.Linear.State
562             RegAlloc.Linear.Stats
563             RegAlloc.Linear.FreeRegs
564             RegAlloc.Linear.StackMap
565             RegAlloc.Linear.Base
566             RegAlloc.Linear.X86.FreeRegs
567             RegAlloc.Linear.PPC.FreeRegs
568             RegAlloc.Linear.SPARC.FreeRegs
569
570     if flag(ghci)
571         Exposed-Modules:
572             DsMeta
573             TcSplice
574             Convert
575             ByteCodeAsm
576             ByteCodeFFI
577             ByteCodeGen
578             ByteCodeInstr
579             ByteCodeItbls
580             ByteCodeLink
581             Debugger
582             LibFFI
583             Linker
584             ObjLink
585             RtClosureInspect
586