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