Fix a build failure on non-{x86,amd64}
[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         ExternalCore
265         MkCore
266         MkExternalCore
267         PprCore
268         PprExternalCore
269         Check
270         Coverage
271         Desugar
272         DsArrows
273         DsBinds
274         DsCCall
275         DsExpr
276         DsForeign
277         DsGRHSs
278         DsListComp
279         DsMonad
280         DsUtils
281         Match
282         MatchCon
283         MatchLit
284         HsBinds
285         HsDecls
286         HsDoc
287         HsExpr
288         HsImpExp
289         HsLit
290         HsPat
291         HsSyn
292         HsTypes
293         HsUtils
294         BinIface
295         BuildTyCl
296         IfaceEnv
297         IfaceSyn
298         IfaceType
299         LoadIface
300         MkIface
301         TcIface
302         Annotations
303         BreakArray
304         CmdLineParser
305         CodeOutput
306         Config
307         Constants
308         DriverMkDepend
309         DriverPhases
310         DriverPipeline
311         DynFlags
312         ErrUtils
313         Finder
314         GHC
315         GhcMake
316         HeaderInfo
317         HscMain
318         HscStats
319         HscTypes
320         InteractiveEval
321         PackageConfig
322         Packages
323         PprTyThing
324         StaticFlags
325         StaticFlagParser
326         SysTools
327         TidyPgm
328         Ctype
329         HaddockUtils
330         LexCore
331         Lexer
332         OptCoercion
333         Parser
334         ParserCore
335         ParserCoreUtils
336         RdrHsSyn
337         ForeignCall
338         PrelInfo
339         PrelNames
340         PrelRules
341         PrimOp
342         TysPrim
343         TysWiredIn
344         CostCentre
345         ProfInit
346         SCCfinal
347         RnBinds
348         RnEnv
349         RnExpr
350         RnHsDoc
351         RnHsSyn
352         RnNames
353         RnPat
354         RnSource
355         RnTypes
356         CoreMonad
357         CSE
358         FloatIn
359         FloatOut
360         LiberateCase
361         OccurAnal
362         SAT
363         SetLevels
364         SimplCore
365         SimplEnv
366         SimplMonad
367         SimplUtils
368         Simplify
369         SRT
370         SimplStg
371         StgStats
372         Rules
373         SpecConstr
374         Specialise
375         CoreToStg
376         StgLint
377         StgSyn
378         DmdAnal
379         WorkWrap
380         WwLib
381         FamInst
382         Inst
383         TcAnnotations
384         TcArrows
385         TcBinds
386         TcClassDcl
387         TcDefaults
388         TcDeriv
389         TcEnv
390         TcExpr
391         TcForeign
392         TcGenDeriv
393         TcHsSyn
394         TcHsType
395         TcInstDcls
396         TcMType
397         TcMatches
398         TcPat
399         TcRnDriver
400         TcRnMonad
401         TcRnTypes
402         TcRules
403         TcSimplify
404         TcErrors
405         TcTyClsDecls
406         TcTyDecls
407         TcType
408         TcUnify
409         TcInteract
410         TcCanonical
411         TcSMonad
412         Class
413         Coercion
414         FamInstEnv
415         FunDeps
416         Generics
417         InstEnv
418         TyCon
419         Kind
420         Type
421         TypeRep
422         Unify
423         Bag
424         Binary
425         BufWrite
426         Digraph
427         Encoding
428         FastBool
429         FastFunctions
430         FastMutInt
431         FastString
432         FastTypes
433         Fingerprint
434         FiniteMap
435         GraphBase
436         GraphColor
437         GraphOps
438         GraphPpr
439         IOEnv
440         Interval
441         ListSetOps
442         Maybes
443         MonadUtils
444         OrdList
445         Outputable
446         Pair
447         Panic
448         Pretty
449         Serialized
450         State
451         StringBuffer
452         UniqFM
453         UniqSet
454         Util
455         Vectorise.Builtins.Base
456         Vectorise.Builtins.Initialise
457         Vectorise.Builtins.Modules
458         Vectorise.Builtins.Prelude
459         Vectorise.Builtins
460         Vectorise.Monad.Base
461         Vectorise.Monad.Naming
462         Vectorise.Monad.Local
463         Vectorise.Monad.Global
464         Vectorise.Monad.InstEnv
465         Vectorise.Monad
466         Vectorise.Utils.Base
467         Vectorise.Utils.Closure
468         Vectorise.Utils.Hoisting
469         Vectorise.Utils.PADict
470         Vectorise.Utils.Poly
471         Vectorise.Utils
472         Vectorise.Type.Env
473         Vectorise.Type.Repr
474         Vectorise.Type.PData
475         Vectorise.Type.PRepr
476         Vectorise.Type.PADict
477         Vectorise.Type.Type
478         Vectorise.Type.TyConDecl
479         Vectorise.Type.Classify
480         Vectorise.Convert
481         Vectorise.Vect
482         Vectorise.Var
483         Vectorise.Env
484         Vectorise.Exp
485         Vectorise
486
487     Exposed-Modules:
488             AsmCodeGen
489             TargetReg
490             NCGMonad
491             Instruction
492             Size
493             Reg
494             RegClass
495             PIC
496             Platform
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             ByteCodeGen
556             ByteCodeInstr
557             ByteCodeItbls
558             ByteCodeLink
559             Debugger
560             LibFFI
561             Linker
562             ObjLink
563             RtClosureInspect
564