merge GHC HEAD
[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         CmmCPS
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         CmmStackLayout
203         CmmType
204         CmmUtils
205         MkGraph
206         OldCmm
207         OldCmmUtils
208         OldPprCmm
209         OptimizationFuel
210         PprBase
211         PprC
212         PprCmm
213         PprCmmDecl
214         PprCmmExpr
215         Bitmap
216         CgBindery
217         CgCallConv
218         CgCase
219         CgClosure
220         CgCon
221         CgExpr
222         CgExtCode
223         CgForeignCall
224         CgHeapery
225         CgHpc
226         CgInfoTbls
227         CgLetNoEscape
228         CgMonad
229         CgParallel
230         CgPrimOp
231         CgProf
232         CgStackery
233         CgTailCall
234         CgTicky
235         CgUtils
236         StgCmm
237         StgCmmBind
238         StgCmmClosure
239         StgCmmCon
240         StgCmmEnv
241         StgCmmExpr
242         StgCmmForeign
243         StgCmmGran
244         StgCmmHeap
245         StgCmmHpc
246         StgCmmLayout
247         StgCmmMonad
248         StgCmmPrim
249         StgCmmProf
250         StgCmmTicky
251         StgCmmUtils
252         ClosureInfo
253         CodeGen
254         SMRep
255         CoreArity
256         CoreFVs
257         CoreLint
258         CorePrep
259         CoreSubst
260         CoreSyn
261         CoreTidy
262         CoreUnfold
263         CoreUtils
264         CoqPass
265         ExternalCore
266         MkCore
267         MkExternalCore
268         PprCore
269         PprExternalCore
270         Check
271         Coverage
272         Desugar
273         DsArrows
274         DsBinds
275         DsCCall
276         DsExpr
277         DsForeign
278         DsGRHSs
279         DsListComp
280         DsMonad
281         DsUtils
282         Match
283         MatchCon
284         MatchLit
285         HsBinds
286         HsDecls
287         HsDoc
288         HsExpr
289         HsImpExp
290         HsLit
291         HsPat
292         HsSyn
293         HsTypes
294         HsUtils
295         BinIface
296         BuildTyCl
297         IfaceEnv
298         IfaceSyn
299         IfaceType
300         LoadIface
301         MkIface
302         TcIface
303         Annotations
304         BreakArray
305         CmdLineParser
306         CodeOutput
307         Config
308         Constants
309         DriverMkDepend
310         DriverPhases
311         DriverPipeline
312         DynFlags
313         ErrUtils
314         Finder
315         GHC
316         GhcMake
317         HeaderInfo
318         HscMain
319         HscStats
320         HscTypes
321         InteractiveEval
322         PackageConfig
323         Packages
324         PprTyThing
325         StaticFlags
326         StaticFlagParser
327         SysTools
328         TidyPgm
329         Ctype
330         HaddockUtils
331         LexCore
332         Lexer
333         OptCoercion
334         Parser
335         ParserCore
336         ParserCoreUtils
337         RdrHsSyn
338         ForeignCall
339         PrelInfo
340         PrelNames
341         PrelRules
342         PrimOp
343         TysPrim
344         TysWiredIn
345         CostCentre
346         ProfInit
347         SCCfinal
348         RnBinds
349         RnEnv
350         RnExpr
351         RnHsDoc
352         RnHsSyn
353         RnNames
354         RnPat
355         RnSource
356         RnTypes
357         CoreMonad
358         CSE
359         FloatIn
360         FloatOut
361         LiberateCase
362         OccurAnal
363         SAT
364         SetLevels
365         SimplCore
366         SimplEnv
367         SimplMonad
368         SimplUtils
369         Simplify
370         SRT
371         SimplStg
372         StgStats
373         Rules
374         SpecConstr
375         Specialise
376         CoreToStg
377         StgLint
378         StgSyn
379         DmdAnal
380         WorkWrap
381         WwLib
382         FamInst
383         Inst
384         TcAnnotations
385         TcArrows
386         TcBinds
387         TcClassDcl
388         TcDefaults
389         TcDeriv
390         TcEnv
391         TcExpr
392         TcForeign
393         TcGenDeriv
394         TcHsSyn
395         TcHsType
396         TcInstDcls
397         TcMType
398         TcMatches
399         TcPat
400         TcRnDriver
401         TcRnMonad
402         TcRnTypes
403         TcRules
404         TcSimplify
405         TcErrors
406         TcTyClsDecls
407         TcTyDecls
408         TcType
409         TcUnify
410         TcInteract
411         TcCanonical
412         TcSMonad
413         Class
414         Coercion
415         FamInstEnv
416         FunDeps
417         Generics
418         InstEnv
419         TyCon
420         Kind
421         Type
422         TypeRep
423         Unify
424         Bag
425         Binary
426         BufWrite
427         Digraph
428         Encoding
429         FastBool
430         FastFunctions
431         FastMutInt
432         FastString
433         FastTypes
434         Fingerprint
435         FiniteMap
436         GraphBase
437         GraphColor
438         GraphOps
439         GraphPpr
440         IOEnv
441         Interval
442         ListSetOps
443         Maybes
444         MonadUtils
445         OrdList
446         Outputable
447         Pair
448         Panic
449         Pretty
450         Serialized
451         State
452         StringBuffer
453         UniqFM
454         UniqSet
455         Util
456         Vectorise.Builtins.Base
457         Vectorise.Builtins.Initialise
458         Vectorise.Builtins.Modules
459         Vectorise.Builtins.Prelude
460         Vectorise.Builtins
461         Vectorise.Monad.Base
462         Vectorise.Monad.Naming
463         Vectorise.Monad.Local
464         Vectorise.Monad.Global
465         Vectorise.Monad.InstEnv
466         Vectorise.Monad
467         Vectorise.Utils.Base
468         Vectorise.Utils.Closure
469         Vectorise.Utils.Hoisting
470         Vectorise.Utils.PADict
471         Vectorise.Utils.Poly
472         Vectorise.Utils
473         Vectorise.Type.Env
474         Vectorise.Type.Repr
475         Vectorise.Type.PData
476         Vectorise.Type.PRepr
477         Vectorise.Type.PADict
478         Vectorise.Type.Type
479         Vectorise.Type.TyConDecl
480         Vectorise.Type.Classify
481         Vectorise.Convert
482         Vectorise.Vect
483         Vectorise.Var
484         Vectorise.Env
485         Vectorise.Exp
486         Vectorise
487
488     Exposed-Modules:
489             AsmCodeGen
490             TargetReg
491             NCGMonad
492             Instruction
493             Size
494             Reg
495             RegClass
496             PIC
497             Platform
498             X86.Regs
499             X86.RegInfo
500             X86.Instr
501             X86.Cond
502             X86.Ppr
503             X86.CodeGen
504             PPC.Regs
505             PPC.RegInfo
506             PPC.Instr
507             PPC.Cond
508             PPC.Ppr
509             PPC.CodeGen
510             SPARC.Base
511             SPARC.Regs
512             SPARC.RegPlate
513             SPARC.Imm
514             SPARC.AddrMode
515             SPARC.Cond
516             SPARC.Instr
517             SPARC.Stack
518             SPARC.ShortcutJump
519             SPARC.Ppr
520             SPARC.CodeGen
521             SPARC.CodeGen.Amode
522             SPARC.CodeGen.Base
523             SPARC.CodeGen.CCall
524             SPARC.CodeGen.CondCode
525             SPARC.CodeGen.Gen32
526             SPARC.CodeGen.Gen64
527             SPARC.CodeGen.Sanity
528             SPARC.CodeGen.Expand
529             RegAlloc.Liveness
530             RegAlloc.Graph.Main
531             RegAlloc.Graph.Stats
532             RegAlloc.Graph.ArchBase
533             RegAlloc.Graph.ArchX86
534             RegAlloc.Graph.Coalesce
535             RegAlloc.Graph.Spill
536             RegAlloc.Graph.SpillClean
537             RegAlloc.Graph.SpillCost
538             RegAlloc.Graph.TrivColorable
539             RegAlloc.Linear.Main
540             RegAlloc.Linear.JoinToTargets
541             RegAlloc.Linear.State
542             RegAlloc.Linear.Stats
543             RegAlloc.Linear.FreeRegs
544             RegAlloc.Linear.StackMap
545             RegAlloc.Linear.Base
546             RegAlloc.Linear.X86.FreeRegs
547             RegAlloc.Linear.PPC.FreeRegs
548             RegAlloc.Linear.SPARC.FreeRegs
549
550     if flag(ghci)
551         Exposed-Modules:
552             DsMeta
553             TcSplice
554             Convert
555             ByteCodeAsm
556             ByteCodeGen
557             ByteCodeInstr
558             ByteCodeItbls
559             ByteCodeLink
560             Debugger
561             LibFFI
562             Linker
563             ObjLink
564             RtClosureInspect
565