Break out closure utils into own module
[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
48 Flag stage2
49     Description: Is this stage 2?
50     Default: False
51
52 Flag stage3
53     Description: Is this stage 3?
54     Default: False
55
56 Library
57     Exposed: False
58
59     if flag(base4)
60         Build-Depends: base       >= 4   && < 5
61     if flag(base3)
62         Build-Depends: base       >= 3   && < 4
63     if !flag(base3) && !flag(base4)
64         Build-Depends: base       < 3
65
66     if flag(base3) || flag(base4)
67         Build-Depends: directory  >= 1   && < 1.1,
68                        process    >= 1   && < 1.1,
69                        bytestring >= 0.9 && < 0.10,
70                        old-time   >= 1   && < 1.1,
71                        containers >= 0.1 && < 0.5,
72                        array      >= 0.1 && < 0.4
73
74     Build-Depends: filepath >= 1 && < 1.3
75     Build-Depends: Cabal, hpc
76     if os(windows)
77         Build-Depends: Win32
78     else
79         Build-Depends: unix
80
81     GHC-Options: -Wall -fno-warn-name-shadowing -fno-warn-orphans
82
83     if flag(ghci)
84         Build-Depends: template-haskell
85         CPP-Options: -DGHCI
86         Include-Dirs: ../libffi/build/include
87
88     if !flag(ncg)
89         CPP-Options: -DOMIT_NATIVE_CODEGEN
90
91     Build-Depends: bin-package-db
92
93     -- GHC 6.4.2 needs to be able to find WCsubst.c, which needs to be
94     -- able to find WCsubst.h
95     Include-Dirs: ../libraries/base/cbits, ../libraries/base/include
96
97     Extensions: CPP, MagicHash, UnboxedTuples, PatternGuards,
98                 ForeignFunctionInterface, EmptyDataDecls,
99                 TypeSynonymInstances, MultiParamTypeClasses,
100                 FlexibleInstances, Rank2Types, ScopedTypeVariables,
101                 DeriveDataTypeable, RelaxedPolyRec
102
103     Include-Dirs: . parser utils
104
105     if flag(stage1)
106         Include-Dirs: stage1
107     else
108         if flag(stage2)
109             Include-Dirs: stage2
110         else
111             if flag(stage3)
112                 Include-Dirs: stage2
113
114     Install-Includes: HsVersions.h, ghc_boot_platform.h
115
116     c-sources:
117         parser/cutils.c
118         utils/md5.c
119
120     if flag(dynlibs)
121         c-sources:
122             ghci/keepCAFsForGHCi.c
123
124     hs-source-dirs:
125         basicTypes
126         cmm
127         codeGen
128         coreSyn
129         deSugar
130         ghci
131         hsSyn
132         iface
133         llvmGen
134         main
135         nativeGen
136         parser
137         prelude
138         profiling
139         rename
140         simplCore
141         simplStg
142         specialise
143         stgSyn
144         stranal
145         typecheck
146         types
147         utils
148         vectorise
149
150     Exposed-Modules:
151         BasicTypes
152         DataCon
153         Demand
154         Exception
155         Id
156         IdInfo
157         Literal
158         Llvm
159         Llvm.AbsSyn
160         Llvm.PpLlvm
161         Llvm.Types
162         LlvmCodeGen
163         LlvmCodeGen.Base
164         LlvmCodeGen.CodeGen
165         LlvmCodeGen.Data
166         LlvmCodeGen.Ppr
167         LlvmCodeGen.Regs
168         LlvmMangler
169         MkId
170         Module
171         Name
172         NameEnv
173         NameSet
174         OccName
175         RdrName
176         SrcLoc
177         UniqSupply
178         Unique
179         Var
180         VarEnv
181         VarSet
182         BlockId
183         CLabel
184         Cmm
185         CmmBrokenBlock
186         CmmBuildInfoTables
187         CmmCPS
188         CmmCPSGen
189         CmmCPSZ
190         CmmCallConv
191         CmmCommonBlockElimZ
192         CmmContFlowOpt
193         CmmCvt
194         CmmExpr
195         CmmInfo
196         CmmLex
197         CmmLint
198         CmmLive
199         CmmLiveZ
200         CmmOpt
201         CmmParse
202         CmmProcPoint
203         CmmProcPointZ
204         CmmSpillReload
205         CmmStackLayout
206         CmmTx
207         CmmUtils
208         CmmZipUtil
209         DFMonad
210         Dataflow
211         MkZipCfg
212         MkZipCfgCmm
213         OptimizationFuel
214         PprBase
215         PprC
216         PprCmm
217         PprCmmZ
218         StackColor
219         StackPlacements
220         ZipCfg
221         ZipCfgCmmRep
222         ZipCfgExtras
223         ZipDataflow
224         Bitmap
225         CgBindery
226         CgCallConv
227         CgCase
228         CgClosure
229         CgCon
230         CgExpr
231         CgExtCode
232         CgForeignCall
233         CgHeapery
234         CgHpc
235         CgInfoTbls
236         CgLetNoEscape
237         CgMonad
238         CgParallel
239         CgPrimOp
240         CgProf
241         CgStackery
242         CgTailCall
243         CgTicky
244         CgUtils
245         StgCmm
246         StgCmmBind
247         StgCmmClosure
248         StgCmmCon
249         StgCmmEnv
250         StgCmmExpr
251         StgCmmForeign
252         StgCmmGran
253         StgCmmHeap
254         StgCmmHpc
255         StgCmmLayout
256         StgCmmMonad
257         StgCmmPrim
258         StgCmmProf
259         StgCmmTicky
260         StgCmmUtils
261         ClosureInfo
262         CodeGen
263         SMRep
264         CoreArity
265         CoreFVs
266         CoreLint
267         CorePrep
268         CoreSubst
269         CoreSyn
270         CoreTidy
271         CoreUnfold
272         CoreUtils
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         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         TcTyClsDecls
412         TcTyDecls
413         TcTyFuns
414         TcType
415         TcUnify
416         Class
417         Coercion
418         FamInstEnv
419         FunDeps
420         Generics
421         InstEnv
422         TyCon
423         Type
424         TypeRep
425         Unify
426         Bag
427         Binary
428         BufWrite
429         Digraph
430         Encoding
431         FastBool
432         FastFunctions
433         FastMutInt
434         FastString
435         FastTypes
436         Fingerprint
437         FiniteMap
438         GraphBase
439         GraphColor
440         GraphOps
441         GraphPpr
442         IOEnv
443         Interval
444         ListSetOps
445         Maybes
446         MonadUtils
447         OrdList
448         Outputable
449         Panic
450         Pretty
451         Serialized
452         State
453         StringBuffer
454         UniqFM
455         UniqSet
456         Util
457         VectType
458         VectUtils
459         Vectorise.Var
460         Vectorise.Env
461         Vectorise.Vect
462         Vectorise.Exp
463         Vectorise.Type.Type
464         Vectorise.Type.TyConDecl
465         Vectorise.Type.Classify
466         Vectorise.Utils.Closure
467         Vectorise.Builtins.Base
468         Vectorise.Builtins.Initialise
469         Vectorise.Builtins.Modules
470         Vectorise.Builtins.Prelude
471         Vectorise.Builtins
472         Vectorise.Monad.Base
473         Vectorise.Monad.Naming
474         Vectorise.Monad.Local
475         Vectorise.Monad.Global
476         Vectorise.Monad.InstEnv
477         Vectorise.Monad
478         Vectorise
479
480     -- We only need to expose more modules as some of the ncg code is used
481     -- by the LLVM backend so its always included
482     if flag(ncg)
483         Exposed-Modules:
484             AsmCodeGen
485             TargetReg
486             NCGMonad
487             Instruction
488             Size
489             Reg
490             RegClass
491             PIC
492             Platform
493             Alpha.Regs
494             Alpha.RegInfo
495             Alpha.Instr
496             Alpha.CodeGen
497             X86.Regs
498             X86.RegInfo
499             X86.Instr
500             X86.Cond
501             X86.Ppr
502             X86.CodeGen
503             PPC.Regs
504             PPC.RegInfo
505             PPC.Instr
506             PPC.Cond
507             PPC.Ppr
508             PPC.CodeGen
509             SPARC.Base
510             SPARC.Regs
511             SPARC.RegPlate
512             SPARC.Imm
513             SPARC.AddrMode
514             SPARC.Cond
515             SPARC.Instr
516             SPARC.Stack
517             SPARC.ShortcutJump
518             SPARC.Ppr
519             SPARC.CodeGen
520             SPARC.CodeGen.Amode
521             SPARC.CodeGen.Base
522             SPARC.CodeGen.CCall
523             SPARC.CodeGen.CondCode
524             SPARC.CodeGen.Gen32
525             SPARC.CodeGen.Gen64
526             SPARC.CodeGen.Sanity
527             SPARC.CodeGen.Expand
528             RegAlloc.Liveness
529             RegAlloc.Graph.Main
530             RegAlloc.Graph.Stats
531             RegAlloc.Graph.ArchBase
532             RegAlloc.Graph.ArchX86
533             RegAlloc.Graph.Coalesce
534             RegAlloc.Graph.Spill
535             RegAlloc.Graph.SpillClean
536             RegAlloc.Graph.SpillCost
537             RegAlloc.Graph.TrivColorable
538             RegAlloc.Linear.Main
539             RegAlloc.Linear.JoinToTargets
540             RegAlloc.Linear.State
541             RegAlloc.Linear.Stats
542             RegAlloc.Linear.FreeRegs
543             RegAlloc.Linear.StackMap
544             RegAlloc.Linear.Base
545             RegAlloc.Linear.X86.FreeRegs
546             RegAlloc.Linear.PPC.FreeRegs
547             RegAlloc.Linear.SPARC.FreeRegs
548
549     if flag(ghci)
550         Exposed-Modules:
551             DsMeta
552             TcSplice
553             Convert
554             ByteCodeAsm
555             ByteCodeFFI
556             ByteCodeGen
557             ByteCodeInstr
558             ByteCodeItbls
559             ByteCodeLink
560             Debugger
561             LibFFI
562             Linker
563             ObjLink
564             RtClosureInspect
565