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