cabal-helper-1.0.0.0: Give Haskell development tools access to Cabal project environment

LicenseApache-2.0
Safe HaskellSafe
LanguageHaskell2010

CabalHelper.Shared.InterfaceTypes

Description

These types are used to communicate between the cabal-helper library and helper executable, using Show/Read. If any types in this module change the major version must be bumped since this will be exposed in the Distribution.Helper module.

The cached executables in $XDG_CACHE_HOME/cabal-helper use the cabal-helper version (among other things) as a cache key so we don't need to worry about talking to an old executable.

Documentation

data ChResponse Source #

Instances
Eq ChResponse Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Ord ChResponse Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Read ChResponse Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Show ChResponse Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Generic ChResponse Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Associated Types

type Rep ChResponse :: Type -> Type #

type Rep ChResponse Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

data ChComponentName Source #

Instances
Eq ChComponentName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Ord ChComponentName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Read ChComponentName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Show ChComponentName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Generic ChComponentName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Associated Types

type Rep ChComponentName :: Type -> Type #

type Rep ChComponentName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

data ChLibraryName Source #

Instances
Eq ChLibraryName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Ord ChLibraryName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Read ChLibraryName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Show ChLibraryName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Generic ChLibraryName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Associated Types

type Rep ChLibraryName :: Type -> Type #

type Rep ChLibraryName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

type Rep ChLibraryName = D1 (MetaData "ChLibraryName" "CabalHelper.Shared.InterfaceTypes" "cabal-helper-1.0.0.0-3RovMtTNraDHCRO0uwfQKJ-c-h-internal" False) (C1 (MetaCons "ChMainLibName" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ChSubLibName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

newtype ChModuleName Source #

Constructors

ChModuleName 
Instances
Eq ChModuleName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Ord ChModuleName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Read ChModuleName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Show ChModuleName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Generic ChModuleName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Associated Types

type Rep ChModuleName :: Type -> Type #

type Rep ChModuleName Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

type Rep ChModuleName = D1 (MetaData "ChModuleName" "CabalHelper.Shared.InterfaceTypes" "cabal-helper-1.0.0.0-3RovMtTNraDHCRO0uwfQKJ-c-h-internal" True) (C1 (MetaCons "ChModuleName" PrefixI True) (S1 (MetaSel (Just "unChModuleName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

data ChComponentInfo Source #

Constructors

ChComponentInfo 

Fields

  • ciComponentName :: ChComponentName

    The component's type and name

  • ciGhcOptions :: [String]

    Full set of GHC options, ready for loading this component into GHCi.

  • ciSourceDirs :: [String]

    A component's hs-source-dirs field, note that this only contains the directories specified by the cabal file, however cabal also adds the output directory of preprocessors to GHC's search path when building. TODO: make this easier to use.

  • ciEntrypoints :: ChEntrypoint

    Modules or files Cabal would have the compiler build directly. Can be used to compute the home module closure for a component.

data ChEntrypoint Source #

Instances
Eq ChEntrypoint Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Ord ChEntrypoint Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Read ChEntrypoint Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Show ChEntrypoint Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Generic ChEntrypoint Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Associated Types

type Rep ChEntrypoint :: Type -> Type #

type Rep ChEntrypoint Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

type Rep ChEntrypoint = D1 (MetaData "ChEntrypoint" "CabalHelper.Shared.InterfaceTypes" "cabal-helper-1.0.0.0-3RovMtTNraDHCRO0uwfQKJ-c-h-internal" False) (C1 (MetaCons "ChSetupEntrypoint" PrefixI True) (S1 (MetaSel (Just "chMainIs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)) :+: (C1 (MetaCons "ChLibEntrypoint" PrefixI True) (S1 (MetaSel (Just "chExposedModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ChModuleName]) :*: (S1 (MetaSel (Just "chOtherModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ChModuleName]) :*: S1 (MetaSel (Just "chSignatures") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ChModuleName]))) :+: C1 (MetaCons "ChExeEntrypoint" PrefixI True) (S1 (MetaSel (Just "chMainIs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath) :*: S1 (MetaSel (Just "chOtherModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ChModuleName]))))

data ChPkgDb Source #

Instances
Eq ChPkgDb Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Methods

(==) :: ChPkgDb -> ChPkgDb -> Bool #

(/=) :: ChPkgDb -> ChPkgDb -> Bool #

Ord ChPkgDb Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Read ChPkgDb Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Show ChPkgDb Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Generic ChPkgDb Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

Associated Types

type Rep ChPkgDb :: Type -> Type #

Methods

from :: ChPkgDb -> Rep ChPkgDb x #

to :: Rep ChPkgDb x -> ChPkgDb #

type Rep ChPkgDb Source # 
Instance details

Defined in CabalHelper.Shared.InterfaceTypes

type Rep ChPkgDb = D1 (MetaData "ChPkgDb" "CabalHelper.Shared.InterfaceTypes" "cabal-helper-1.0.0.0-3RovMtTNraDHCRO0uwfQKJ-c-h-internal" False) (C1 (MetaCons "ChPkgGlobal" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ChPkgUser" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ChPkgSpecific" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath))))