Skip to content
Snippets Groups Projects
ghc.cabal.in 12.9 KiB
Newer Older
-- WARNING: ghc.cabal is automatically generated from ghc.cabal.in by
-- ./configure.  Make sure you are editing ghc.cabal.in, not ghc.cabal.

Version: @ProjectVersionMunged@
License: BSD3
Author: The GHC Team
Maintainer: glasgow-haskell-users@haskell.org
Homepage: http://www.haskell.org/ghc/
Synopsis: The GHC API
    GHC's functionality can be useful for more things than just
    compiling Haskell programs. Important use cases are programs
    that analyse (and perhaps transform) Haskell code. Others
    include loading Haskell code dynamically in a GHCi-like manner.
    For this reason, a lot of GHC's functionality is made available
    through this package.
Category: Development

Flag ghci
    Description: Build GHCi support.
    Default: False
    Manual: True

Flag stage1
    Description: Is this stage 1?
    Default: False

Flag stage2
    Description: Is this stage 2?
    Default: False

Flag stage3
    Description: Is this stage 3?
    Default: False
    Default-Language: Haskell2010
    Exposed: False

    Build-Depends: base       >= 4   && < 5,
                   deepseq    >= 1.4 && < 1.5,
                   directory  >= 1   && < 1.3,
                   bytestring >= 0.9 && < 0.11,
                   time       >= 1.4 && < 1.7,
                   containers >= 0.5 && < 0.6,
                   template-haskell == 2.11.*,
                   hpc        == 0.6.*,
                   transformers == 0.5.*,
                   ghc-boot   == @ProjectVersionMunged@,
                   hoopl      >= 3.10.2 && < 3.11
        Build-Depends: Win32  == 2.3.*
        Build-Depends: unix   == 2.7.*
    if flag(ghci)
        Build-Depends: ghci == @ProjectVersionMunged@
    GHC-Options: -Wall -fno-warn-name-shadowing

    if flag(ghci)
        CPP-Options: -DGHCI
        Include-Dirs: ../rts/dist/build @FFIIncludeDir@
    Other-Extensions:
        BangPatterns
        CPP
        DataKinds
        DeriveDataTypeable
        DeriveFoldable
        DeriveFunctor
        DeriveTraversable
        DisambiguateRecordFields
        ExplicitForAll
        FlexibleContexts
        FlexibleInstances
        GADTs
        GeneralizedNewtypeDeriving
        MagicHash
        MultiParamTypeClasses
        NamedFieldPuns
        NondecreasingIndentation
        RankNTypes
        RecordWildCards
        ScopedTypeVariables
        StandaloneDeriving
        Trustworthy
        TupleSections
        TypeFamilies
        TypeSynonymInstances
        UnboxedTuples
        UndecidableInstances
    -- We need to set the unit id to ghc (without a version number)
    -- as it's magic.  But we can't set it for old versions of GHC (e.g.
    -- when bootstrapping) because those versions of GHC don't understand
    -- that GHC is wired-in.
    if impl ( ghc >= 7.11 )
        GHC-Options: -this-unit-id ghc
    else
        if impl( ghc >= 7.9 )
            GHC-Options: -this-package-key ghc
    if flag(stage1)
        Include-Dirs: stage1
    else
        if flag(stage2)
            Include-Dirs: stage2
        else
            if flag(stage3)
                Include-Dirs: stage2

    Install-Includes: HsVersions.h, ghc_boot_platform.h

    c-sources:
        parser/cutils.c
        ghci/keepCAFsForGHCi.c
        cbits/genSym.c

    hs-source-dirs:
        basicTypes
        cmm
        codeGen
        coreSyn
        deSugar
        ghci
        hsSyn
        iface
        parser
        prelude
        profiling
        rename
        simplCore
        simplStg
        specialise
        stgSyn
        stranal
        typecheck
        types
        utils
        vectorise

    Exposed-Modules:
Gergő Érdi's avatar
Gergő Érdi committed
        ConLike
Gergő Érdi's avatar
Gergő Érdi committed
        PatSyn
        Exception
        FieldLabel
        Llvm.PpLlvm
        Llvm.Types
        LlvmCodeGen
        LlvmCodeGen.Base
        LlvmCodeGen.CodeGen
        LlvmCodeGen.Data
        LlvmCodeGen.Ppr
        LlvmCodeGen.Regs
        MkId
        Module
        Name
        NameEnv
        NameSet
        OccName
        RdrName
        SrcLoc
        UniqSupply
        Unique
        Var
        VarEnv
        VarSet
        UnVarGraph
        CmmPipeline
        CmmCommonBlockElim
        CmmImplementSwitchPlans
        CmmContFlowOpt
        CmmExpr
        CmmInfo
        CmmLex
        CmmLint
        CmmLive
        CmmMachOp
Simon Marlow's avatar
Simon Marlow committed
        CmmLayoutStack
        PprCmmDecl
        PprCmmExpr
        CodeGen.Platform
        CodeGen.Platform.ARM
        CodeGen.Platform.ARM64
        CodeGen.Platform.NoRegs
        CodeGen.Platform.PPC
        CodeGen.Platform.PPC_Darwin
        CodeGen.Platform.SPARC
        CodeGen.Platform.X86
        CodeGen.Platform.X86_64
        StgCmm
        StgCmmBind
        StgCmmClosure
        StgCmmCon
        StgCmmEnv
        StgCmmExpr
        StgCmmForeign
        StgCmmHeap
        StgCmmHpc
nfrisby's avatar
nfrisby committed
        StgCmmArgRep
        StgCmmLayout
        StgCmmMonad
        StgCmmPrim
        StgCmmProf
        StgCmmTicky
        StgCmmUtils
        StgCmmExtCode
        CoreFVs
        CoreLint
        CorePrep
        CoreSubst
        CoreSyn
        TrieMap
        Check
        Coverage
        Desugar
        DsArrows
        DsBinds
        DsCCall
        DsExpr
        DsForeign
        DsGRHSs
        DsListComp
        DsMonad
        DsUtils
        Match
        MatchCon
        MatchLit
        HsBinds
        HsDecls
        HsDoc
        HsExpr
        HsImpExp
        HsLit
        PlaceHolder
        HsPat
        HsSyn
        HsTypes
        HsUtils
        BinIface
        BuildTyCl
        IfaceEnv
        IfaceSyn
        IfaceType
        LoadIface
        MkIface
        TcIface
        CmdLineParser
        CodeOutput
        Config
        Constants
        DriverMkDepend
        DriverPhases
        DriverPipeline
        DynFlags
        ErrUtils
        Finder
        GHC
        HeaderInfo
        HscMain
        HscStats
        HscTypes
        InteractiveEval
        Plugins
        TcPluginM
        StaticPtrTable
Alan Zimmerman's avatar
Alan Zimmerman committed
        ApiAnnotation
        ForeignCall
        PrelInfo
        PrelNames
        PrelRules
        PrimOp
        TysPrim
        TysWiredIn
        CostCentre
        SCCfinal
        RnBinds
        RnEnv
        RnExpr
        RnHsDoc
        RnNames
        RnPat
        RnSource
        CSE
        FloatIn
        FloatOut
        LiberateCase
        OccurAnal
        SAT
        SetLevels
        SimplCore
        SimplEnv
        SimplMonad
        SimplUtils
        Simplify
        SimplStg
        StgStats
        Rules
        SpecConstr
        Specialise
        CoreToStg
        StgLint
        StgSyn
        CallArity
        TcClassDcl
        TcDefaults
        TcDeriv
        TcEnv
        TcExpr
        TcForeign
        TcGenDeriv
        TcHsSyn
        TcHsType
        TcInstDcls
        TcMType
Gergő Érdi's avatar
Gergő Érdi committed
        TcPatSyn
        TcRnDriver
        TcRnMonad
        TcRnTypes
        TcRules
        TcSimplify
        DsMeta
        THNames
        BufWrite
        Digraph
        Encoding
        FastFunctions
        FastMutInt
        FastString
        FastStringEnv
        GraphBase
        GraphColor
        GraphOps
        GraphPpr
        IOEnv
        ListSetOps
        Maybes
        MonadUtils
        OrdList
        Outputable
        UniqDSet
        UniqFM
        Vectorise.Builtins.Base
        Vectorise.Builtins.Initialise
        Vectorise.Builtins
        Vectorise.Monad.Base
        Vectorise.Monad.Naming
        Vectorise.Monad.Local
        Vectorise.Monad.Global
        Vectorise.Monad.InstEnv
        Vectorise.Monad
        Vectorise.Utils.Base
        Vectorise.Utils.Closure
        Vectorise.Utils.Hoisting
        Vectorise.Utils.PADict
        Vectorise.Utils.Poly
        Vectorise.Utils
        Vectorise.Generic.Description
        Vectorise.Generic.PAMethods
        Vectorise.Generic.PADict
        Vectorise.Generic.PData
        Vectorise.Type.Env
        Vectorise.Type.Type
        Vectorise.Type.TyConDecl
        Vectorise.Type.Classify
        Vectorise.Convert
        Vectorise.Vect
        Vectorise.Var
        Vectorise.Env
        Vectorise.Exp
Simon Marlow's avatar
Simon Marlow committed
        Hoopl.Dataflow
        Hoopl
Simon Marlow's avatar
Simon Marlow committed
--        CgInfoTbls used in ghci/DebuggerUtils
--        CgHeapery  mkVirtHeapOffsets used in ghci

    Exposed-Modules:
tibbe's avatar
tibbe committed
            CPrim
            SPARC.Base
            SPARC.Imm
Simon Marlow's avatar
Simon Marlow committed
            SPARC.AddrMode
            SPARC.Instr
Simon Marlow's avatar
Simon Marlow committed
            SPARC.Stack
            SPARC.ShortcutJump
            SPARC.CodeGen.Amode
            SPARC.CodeGen.Base
            SPARC.CodeGen.CondCode
            SPARC.CodeGen.Gen32
            SPARC.CodeGen.Gen64
            SPARC.CodeGen.Sanity
            SPARC.CodeGen.Expand
            RegAlloc.Liveness
            RegAlloc.Graph.Main
            RegAlloc.Graph.Stats
            RegAlloc.Graph.ArchBase
            RegAlloc.Graph.ArchX86
            RegAlloc.Graph.Coalesce
            RegAlloc.Graph.Spill
            RegAlloc.Graph.SpillClean
            RegAlloc.Graph.SpillCost
            RegAlloc.Graph.TrivColorable
benl's avatar
benl committed
            RegAlloc.Linear.Main
            RegAlloc.Linear.JoinToTargets
            RegAlloc.Linear.State
            RegAlloc.Linear.Stats
            RegAlloc.Linear.FreeRegs
            RegAlloc.Linear.StackMap
            RegAlloc.Linear.Base
            RegAlloc.Linear.X86.FreeRegs
Ian Lynagh's avatar
Ian Lynagh committed
            RegAlloc.Linear.X86_64.FreeRegs
benl's avatar
benl committed
            RegAlloc.Linear.PPC.FreeRegs
            RegAlloc.Linear.SPARC.FreeRegs
            Dwarf
            Dwarf.Types
            Dwarf.Constants
    if !flag(stage1)
        -- ghc:Serialized moved to ghc-boot:GHC.Serialized.  So for
        -- compatibility with GHC 7.10 and earlier, we reexport it
        -- under the old name.
        reexported-modules:
            ghc-boot:GHC.Serialized as Serialized

    if flag(ghci)
        Exposed-Modules:
            Convert
            ByteCodeTypes
            ByteCodeAsm
            ByteCodeGen
            ByteCodeInstr
            ByteCodeItbls
            ByteCodeLink
            Debugger
            Linker
            RtClosureInspect