rebase to ghc main repo
[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     Build-Depends: hoopl
96
97     -- GHC 6.4.2 needs to be able to find WCsubst.c, which needs to be
98     -- able to find WCsubst.h
99     Include-Dirs: ../libraries/base/cbits, ../libraries/base/include
100
101     Extensions: CPP, MagicHash, UnboxedTuples, PatternGuards,
102                 ForeignFunctionInterface, EmptyDataDecls,
103                 TypeSynonymInstances, MultiParamTypeClasses,
104                 FlexibleInstances, Rank2Types, ScopedTypeVariables,
105                 DeriveDataTypeable
106     if impl(ghc >= 7.1)
107         Extensions: NondecreasingIndentation
108
109     Include-Dirs: . parser utils
110
111     if flag(stage1)
112         Include-Dirs: stage1
113     else
114         if flag(stage2)
115             Include-Dirs: stage2
116         else
117             if flag(stage3)
118                 Include-Dirs: stage2
119
120     Install-Includes: HsVersions.h, ghc_boot_platform.h
121
122     c-sources:
123         parser/cutils.c
124         utils/md5.c
125
126     if flag(dynlibs)
127         c-sources:
128             ghci/keepCAFsForGHCi.c
129
130     hs-source-dirs:
131         basicTypes
132         cmm
133         codeGen
134         coreSyn
135         deSugar
136         ghci
137         hsSyn
138         iface
139         llvmGen
140         main
141         nativeGen
142         parser
143         prelude
144         profiling
145         rename
146         simplCore
147         simplStg
148         specialise
149         stgSyn
150         stranal
151         typecheck
152         types
153         utils
154         vectorise
155
156     Exposed-Modules:
157         BasicTypes
158         DataCon
159         Demand
160         Exception
161         GhcMonad
162         Id
163         IdInfo
164         Literal
165         Llvm
166         Llvm.AbsSyn
167         Llvm.PpLlvm
168         Llvm.Types
169         LlvmCodeGen
170         LlvmCodeGen.Base
171         LlvmCodeGen.CodeGen
172         LlvmCodeGen.Data
173         LlvmCodeGen.Ppr
174         LlvmCodeGen.Regs
175         LlvmMangler
176         MkId
177         Module
178         Name
179         NameEnv
180         NameSet
181         OccName
182         RdrName
183         SrcLoc
184         UniqSupply
185         Unique
186         Var
187         VarEnv
188         VarSet
189         BlockId
190         CLabel
191         Cmm
192         CmmBuildInfoTables
193         CmmCPS
194         CmmCallConv
195         CmmCommonBlockElim
196         CmmContFlowOpt
197         CmmCvt
198         CmmDecl
199         CmmExpr
200         CmmInfo
201         CmmLex
202         CmmLint
203         CmmLive
204         CmmMachOp
205         CmmNode
206         CmmOpt
207         CmmParse
208         CmmProcPoint
209         CmmSpillReload
210         CmmStackLayout
211         CmmType
212         CmmUtils
213         MkGraph
214         OldCmm
215         OldCmmUtils
216         OldPprCmm
217         OptimizationFuel
218         PprBase
219         PprC
220         PprCmm
221         PprCmmDecl
222         PprCmmExpr
223         Bitmap
224         CgBindery
225         CgCallConv
226         CgCase
227         CgClosure
228         CgCon
229         CgExpr
230         CgExtCode
231         CgForeignCall
232         CgHeapery
233         CgHpc
234         CgInfoTbls
235         CgLetNoEscape
236         CgMonad
237         CgParallel
238         CgPrimOp
239         CgProf
240         CgStackery
241         CgTailCall
242         CgTicky
243         CgUtils
244         StgCmm
245         StgCmmBind
246         StgCmmClosure
247         StgCmmCon
248         StgCmmEnv
249         StgCmmExpr
250         StgCmmForeign
251         StgCmmGran
252         StgCmmHeap
253         StgCmmHpc
254         StgCmmLayout
255         StgCmmMonad
256         StgCmmPrim
257         StgCmmProf
258         StgCmmTicky
259         StgCmmUtils
260         ClosureInfo
261         CodeGen
262         SMRep
263         CoreArity
264         CoreFVs
265         CoreLint
266         CorePrep
267         CoreSubst
268         CoreSyn
269         CoreTidy
270         CoreUnfold
271         CoreUtils
272         ExternalCore
273         MkCore
274         MkExternalCore
275         PprCore
276         PprExternalCore
277         Check
278         Coverage
279         Desugar
280         DsArrows
281         DsBinds
282         DsCCall
283         DsExpr
284         DsForeign
285         DsGRHSs
286         DsListComp
287         DsMonad
288         DsUtils
289         Match
290         MatchCon
291         MatchLit
292         HsBinds
293         HsDecls
294         HsDoc
295         HsExpr
296         HsImpExp
297         HsLit
298         HsPat
299         HsSyn
300         HsTypes
301         HsUtils
302         BinIface
303         BuildTyCl
304         IfaceEnv
305         IfaceSyn
306         IfaceType
307         LoadIface
308         MkIface
309         TcIface
310         Annotations
311         BreakArray
312         CmdLineParser
313         CodeOutput
314         Config
315         Constants
316         DriverMkDepend
317         DriverPhases
318         DriverPipeline
319         DynFlags
320         ErrUtils
321         Finder
322         GHC
323         GhcMake
324         HeaderInfo
325         HscMain
326         HscStats
327         HscTypes
328         InteractiveEval
329         PackageConfig
330         Packages
331         PprTyThing
332         StaticFlags
333         StaticFlagParser
334         SysTools
335         TidyPgm
336         Ctype
337         HaddockUtils
338         LexCore
339         Lexer
340         OptCoercion
341         Parser
342         ParserCore
343         ParserCoreUtils
344         RdrHsSyn
345         ForeignCall
346         PrelInfo
347         PrelNames
348         PrelRules
349         PrimOp
350         TysPrim
351         TysWiredIn
352         CostCentre
353         SCCfinal
354         RnBinds
355         RnEnv
356         RnExpr
357         RnHsDoc
358         RnHsSyn
359         RnNames
360         RnPat
361         RnSource
362         RnTypes
363         CoreMonad
364         CSE
365         FloatIn
366         FloatOut
367         LiberateCase
368         OccurAnal
369         SAT
370         SetLevels
371         SimplCore
372         SimplEnv
373         SimplMonad
374         SimplUtils
375         Simplify
376         SRT
377         SimplStg
378         StgStats
379         Rules
380         SpecConstr
381         Specialise
382         CoreToStg
383         StgLint
384         StgSyn
385         DmdAnal
386         WorkWrap
387         WwLib
388         FamInst
389         Inst
390         TcAnnotations
391         TcArrows
392         TcBinds
393         TcClassDcl
394         TcDefaults
395         TcDeriv
396         TcEnv
397         TcExpr
398         TcForeign
399         TcGenDeriv
400         TcHsSyn
401         TcHsType
402         TcInstDcls
403         TcMType
404         TcMatches
405         TcPat
406         TcRnDriver
407         TcRnMonad
408         TcRnTypes
409         TcRules
410         TcSimplify
411         TcErrors
412         TcTyClsDecls
413         TcTyDecls
414         TcType
415         TcUnify
416         TcInteract
417         TcCanonical
418         TcSMonad
419         Class
420         Coercion
421         FamInstEnv
422         FunDeps
423         Generics
424         InstEnv
425         TyCon
426         Type
427         TypeRep
428         Unify
429         Bag
430         Binary
431         BufWrite
432         Digraph
433         Encoding
434         FastBool
435         FastFunctions
436         FastMutInt
437         FastString
438         FastTypes
439         Fingerprint
440         FiniteMap
441         GraphBase
442         GraphColor
443         GraphOps
444         GraphPpr
445         IOEnv
446         Interval
447         ListSetOps
448         Maybes
449         MonadUtils
450         OrdList
451         Outputable
452         Panic
453         Pretty
454         Serialized
455         State
456         StringBuffer
457         UniqFM
458         UniqSet
459         Util
460         Vectorise.Builtins.Base
461         Vectorise.Builtins.Initialise
462         Vectorise.Builtins.Modules
463         Vectorise.Builtins.Prelude
464         Vectorise.Builtins
465         Vectorise.Monad.Base
466         Vectorise.Monad.Naming
467         Vectorise.Monad.Local
468         Vectorise.Monad.Global
469         Vectorise.Monad.InstEnv
470         Vectorise.Monad
471         Vectorise.Utils.Base
472         Vectorise.Utils.Closure
473         Vectorise.Utils.Hoisting
474         Vectorise.Utils.PADict
475         Vectorise.Utils.Poly
476         Vectorise.Utils
477         Vectorise.Type.Env
478         Vectorise.Type.Repr
479         Vectorise.Type.PData
480         Vectorise.Type.PRepr
481         Vectorise.Type.PADict
482         Vectorise.Type.Type
483         Vectorise.Type.TyConDecl
484         Vectorise.Type.Classify
485         Vectorise.Convert
486         Vectorise.Vect
487         Vectorise.Var
488         Vectorise.Env
489         Vectorise.Exp
490         Vectorise
491
492     -- We only need to expose more modules as some of the ncg code is used
493     -- by the LLVM backend so its always included
494     if flag(ncg)
495         Exposed-Modules:
496             AsmCodeGen
497             TargetReg
498             NCGMonad
499             Instruction
500             Size
501             Reg
502             RegClass
503             PIC
504             Platform
505             Alpha.Regs
506             Alpha.RegInfo
507             Alpha.Instr
508             Alpha.CodeGen
509             X86.Regs
510             X86.RegInfo
511             X86.Instr
512             X86.Cond
513             X86.Ppr
514             X86.CodeGen
515             PPC.Regs
516             PPC.RegInfo
517             PPC.Instr
518             PPC.Cond
519             PPC.Ppr
520             PPC.CodeGen
521             SPARC.Base
522             SPARC.Regs
523             SPARC.RegPlate
524             SPARC.Imm
525             SPARC.AddrMode
526             SPARC.Cond
527             SPARC.Instr
528             SPARC.Stack
529             SPARC.ShortcutJump
530             SPARC.Ppr
531             SPARC.CodeGen
532             SPARC.CodeGen.Amode
533             SPARC.CodeGen.Base
534             SPARC.CodeGen.CCall
535             SPARC.CodeGen.CondCode
536             SPARC.CodeGen.Gen32
537             SPARC.CodeGen.Gen64
538             SPARC.CodeGen.Sanity
539             SPARC.CodeGen.Expand
540             RegAlloc.Liveness
541             RegAlloc.Graph.Main
542             RegAlloc.Graph.Stats
543             RegAlloc.Graph.ArchBase
544             RegAlloc.Graph.ArchX86
545             RegAlloc.Graph.Coalesce
546             RegAlloc.Graph.Spill
547             RegAlloc.Graph.SpillClean
548             RegAlloc.Graph.SpillCost
549             RegAlloc.Graph.TrivColorable
550             RegAlloc.Linear.Main
551             RegAlloc.Linear.JoinToTargets
552             RegAlloc.Linear.State
553             RegAlloc.Linear.Stats
554             RegAlloc.Linear.FreeRegs
555             RegAlloc.Linear.StackMap
556             RegAlloc.Linear.Base
557             RegAlloc.Linear.X86.FreeRegs
558             RegAlloc.Linear.PPC.FreeRegs
559             RegAlloc.Linear.SPARC.FreeRegs
560
561     if flag(ghci)
562         Exposed-Modules:
563             DsMeta
564             TcSplice
565             Convert
566             ByteCodeAsm
567             ByteCodeFFI
568             ByteCodeGen
569             ByteCodeInstr
570             ByteCodeItbls
571             ByteCodeLink
572             Debugger
573             LibFFI
574             Linker
575             ObjLink
576             RtClosureInspect
577