GHC new build system megapatch
[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
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 editline
35     Description: Use editline
36     Default: False
37     Manual: True
38
39 Flag ghci
40     Description: Build GHCi support.
41     Default: False
42     Manual: True
43
44 Flag ncg
45     Description: Build the NCG.
46     Default: False
47     Manual: True
48
49 Flag stage1
50     Description: Is this stage 1?
51     Default: False
52
53 Flag stage2
54     Description: Is this stage 2?
55     Default: False
56
57 Flag stage3
58     Description: Is this stage 3?
59     Default: False
60
61 Library
62     Exposed: False
63
64     if flag(base4)
65         Build-Depends: base       >= 4   && < 5
66     if flag(base3)
67         Build-Depends: base       >= 3   && < 4
68     if !flag(base3) && !flag(base4)
69         Build-Depends: base       < 3
70
71     if flag(base3) || flag(base4)
72         Build-Depends: directory  >= 1   && < 1.1,
73                        process    >= 1   && < 1.1,
74                        bytestring >= 0.9 && < 0.10,
75                        old-time   >= 1   && < 1.1,
76                        containers >= 0.1 && < 0.3,
77                        array      >= 0.1 && < 0.3
78
79     Build-Depends: filepath >= 1 && < 1.2
80     Build-Depends: haskell98, Cabal, hpc
81     if os(windows)
82         Build-Depends: Win32
83     else
84         Build-Depends: unix
85
86     if flag(editline)
87         Build-Depends: editline
88         CPP-Options: -DUSE_EDITLINE
89
90     GHC-Options: -Wall -fno-warn-name-shadowing -fno-warn-orphans
91
92     if flag(ghci)
93         Build-Depends: template-haskell
94         CPP-Options: -DGHCI
95         Include-Dirs: ../libffi/build/include
96
97     if !flag(ncg)
98         CPP-Options: -DOMIT_NATIVE_CODEGEN
99
100     -- GHC 6.4.2 needs to be able to find WCsubst.c, which needs to be
101     -- able to find WCsubst.h
102     Include-Dirs: ../libraries/base/cbits, ../libraries/base/include
103
104     Extensions: CPP, MagicHash, UnboxedTuples, PatternGuards,
105                 ForeignFunctionInterface, EmptyDataDecls,
106                 TypeSynonymInstances, MultiParamTypeClasses,
107                 FlexibleInstances, Rank2Types, ScopedTypeVariables,
108                 DeriveDataTypeable, RelaxedPolyRec
109
110     Include-Dirs: . parser utils
111
112     if flag(stage1)
113         Include-Dirs: stage1
114         if impl(ghc < 6.9)
115             Build-Depends: extensible-exceptions
116             Extensions: PatternSignatures
117     else
118         if flag(stage2)
119             Include-Dirs: stage2
120         else
121             if flag(stage3)
122                 Include-Dirs: stage2
123
124     Install-Includes: HsVersions.h, ghc_boot_platform.h
125
126     c-sources:
127         parser/cutils.c
128         utils/md5.c
129
130     if flag(dynlibs)
131         c-sources:
132             ghci/keepCAFsForGHCi.c
133
134     hs-source-dirs:
135         basicTypes
136         cmm
137         codeGen
138         coreSyn
139         cprAnalysis
140         deSugar
141         ghci
142         hsSyn
143         iface
144         main
145         parser
146         prelude
147         profiling
148         rename
149         simplCore
150         simplStg
151         specialise
152         stgSyn
153         stranal
154         typecheck
155         types
156         utils
157         vectorise
158
159     Exposed-Modules:
160         BasicTypes
161         DataCon
162         Demand
163         Exception
164         Id
165         IdInfo
166         Literal
167         MkId
168         Module
169         Name
170         NameEnv
171         NameSet
172         NewDemand
173         OccName
174         RdrName
175         SrcLoc
176         UniqSupply
177         Unique
178         Var
179         VarEnv
180         VarSet
181         BlockId
182         CLabel
183         Cmm
184         CmmBrokenBlock
185         CmmBuildInfoTables
186         CmmCPS
187         CmmCPSGen
188         CmmCPSZ
189         CmmCallConv
190         CmmCommonBlockElimZ
191         CmmContFlowOpt
192         CmmCvt
193         CmmExpr
194         CmmInfo
195         CmmLex
196         CmmLint
197         CmmLive
198         CmmLiveZ
199         CmmOpt
200         CmmParse
201         CmmProcPoint
202         CmmProcPointZ
203         CmmSpillReload
204         CmmStackLayout
205         CmmTx
206         CmmUtils
207         CmmZipUtil
208         DFMonad
209         Dataflow
210         MkZipCfg
211         MkZipCfgCmm
212         OptimizationFuel
213         PprC
214         PprCmm
215         PprCmmZ
216         StackColor
217         StackPlacements
218         ZipCfg
219         ZipCfgCmmRep
220         ZipCfgExtras
221         ZipDataflow
222         Bitmap
223         CgBindery
224         CgCallConv
225         CgCase
226         CgClosure
227         CgCon
228         CgExpr
229         CgForeignCall
230         CgHeapery
231         CgHpc
232         CgInfoTbls
233         CgLetNoEscape
234         CgMonad
235         CgParallel
236         CgPrimOp
237         CgProf
238         CgStackery
239         CgTailCall
240         CgTicky
241         CgUtils
242         StgCmm
243         StgCmmBind
244         StgCmmClosure
245         StgCmmCon
246         StgCmmEnv
247         StgCmmExpr
248         StgCmmForeign
249         StgCmmGran
250         StgCmmHeap
251         StgCmmHpc
252         StgCmmLayout
253         StgCmmMonad
254         StgCmmPrim
255         StgCmmProf
256         StgCmmTicky
257         StgCmmUtils
258         ClosureInfo
259         CodeGen
260         SMRep
261         CoreArity
262         CoreFVs
263         CoreLint
264         CorePrep
265         CoreSubst
266         CoreSyn
267         CoreTidy
268         CoreUnfold
269         CoreUtils
270         ExternalCore
271         MkCore
272         MkExternalCore
273         PprCore
274         PprExternalCore
275         CprAnalyse
276         Check
277         Coverage
278         Desugar
279         DsArrows
280         DsBinds
281         DsCCall
282         DsExpr
283         DsForeign
284         DsGRHSs
285         DsListComp
286         DsMonad
287         DsUtils
288         Match
289         MatchCon
290         MatchLit
291         HsBinds
292         HsDecls
293         HsDoc
294         HsExpr
295         HsImpExp
296         HsLit
297         HsPat
298         HsSyn
299         HsTypes
300         HsUtils
301         BinIface
302         BuildTyCl
303         IfaceEnv
304         IfaceSyn
305         IfaceType
306         LoadIface
307         MkIface
308         TcIface
309         Annotations
310         BreakArray
311         CmdLineParser
312         CodeOutput
313         Config
314         Constants
315         DriverMkDepend
316         DriverPhases
317         DriverPipeline
318         DynFlags
319         ErrUtils
320         Finder
321         GHC
322         HeaderInfo
323         HscMain
324         HscStats
325         HscTypes
326         InteractiveEval
327         PackageConfig
328         Packages
329         ParsePkgConf
330         PprTyThing
331         StaticFlags
332         StaticFlagParser
333         SysTools
334         TidyPgm
335         Ctype
336         HaddockLex
337         HaddockParse
338         HaddockUtils
339         LexCore
340         Lexer
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         SaAbsInt
387         SaLib
388         StrictAnal
389         WorkWrap
390         WwLib
391         FamInst
392         Inst
393         TcAnnotations
394         TcArrows
395         TcBinds
396         TcClassDcl
397         TcDefaults
398         TcDeriv
399         TcEnv
400         TcExpr
401         TcForeign
402         TcGenDeriv
403         TcHsSyn
404         TcHsType
405         TcInstDcls
406         TcMType
407         TcMatches
408         TcPat
409         TcRnDriver
410         TcRnMonad
411         TcRnTypes
412         TcRules
413         TcSimplify
414         TcTyClsDecls
415         TcTyDecls
416         TcTyFuns
417         TcType
418         TcUnify
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         LazyUniqFM
448         ListSetOps
449         Maybes
450         MonadUtils
451         OrdList
452         Outputable
453         Panic
454         Pretty
455         Serialized
456         State
457         StringBuffer
458         UniqFM
459         UniqSet
460         Util
461         VectBuiltIn
462         VectCore
463         VectMonad
464         VectType
465         VectUtils
466         Vectorise
467
468     if flag(ncg)
469         hs-source-dirs:
470             nativeGen
471
472         Exposed-Modules:
473             AsmCodeGen
474             TargetReg
475             NCGMonad
476             Instruction
477             Size
478             Reg
479             RegClass
480             PprBase
481             PIC
482             Platform
483             Alpha.Regs
484             Alpha.RegInfo
485             Alpha.Instr
486             Alpha.CodeGen
487             X86.Regs
488             X86.RegInfo
489             X86.Instr
490             X86.Cond
491             X86.Ppr
492             X86.CodeGen
493             PPC.Regs
494             PPC.RegInfo
495             PPC.Instr
496             PPC.Cond
497             PPC.Ppr
498             PPC.CodeGen
499             SPARC.Base
500             SPARC.Regs
501             SPARC.RegPlate
502             SPARC.Imm
503             SPARC.AddrMode          
504             SPARC.Cond
505             SPARC.Instr
506             SPARC.Stack    
507             SPARC.ShortcutJump
508             SPARC.Ppr
509             SPARC.CodeGen
510             SPARC.CodeGen.Amode
511             SPARC.CodeGen.Base
512             SPARC.CodeGen.CCall
513             SPARC.CodeGen.CondCode
514             SPARC.CodeGen.Gen32
515             SPARC.CodeGen.Gen64
516             SPARC.CodeGen.Sanity
517             RegAlloc.Liveness
518             RegAlloc.Graph.Main
519             RegAlloc.Graph.Stats
520             RegAlloc.Graph.ArchBase
521             RegAlloc.Graph.ArchX86
522             RegAlloc.Graph.Coalesce
523             RegAlloc.Graph.Spill
524             RegAlloc.Graph.SpillClean
525             RegAlloc.Graph.SpillCost
526             RegAlloc.Graph.TrivColorable
527             RegAlloc.Linear.Main
528             RegAlloc.Linear.JoinToTargets
529             RegAlloc.Linear.State
530             RegAlloc.Linear.Stats
531             RegAlloc.Linear.FreeRegs
532             RegAlloc.Linear.StackMap
533             RegAlloc.Linear.Base
534             RegAlloc.Linear.X86.FreeRegs
535             RegAlloc.Linear.PPC.FreeRegs
536             RegAlloc.Linear.SPARC.FreeRegs
537
538     if flag(ghci)
539         Exposed-Modules:
540             DsMeta
541             TcSplice
542             Convert
543             ByteCodeAsm
544             ByteCodeFFI
545             ByteCodeGen
546             ByteCodeInstr
547             ByteCodeItbls
548             ByteCodeLink
549             Debugger
550             GhciMonad
551             GhciTags
552             InteractiveUI
553             LibFFI
554             Linker
555             ObjLink
556             RtClosureInspect
557