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