cabal-debian-4.35.3: Create a Debianization for a Cabal package

Safe HaskellNone
LanguageHaskell2010

Debian.GHC

Contents

Synopsis

Documentation

newestAvailable :: FilePath -> BinPkgName -> Either String DebianVersion Source #

Memoized version of newestAvailable'

compilerFlavorOption :: forall a. (CompilerFlavor -> a -> a) -> OptDescr (a -> a) Source #

General function to build a command line option that reads most of the possible values for CompilerFlavor.

data CompilerVendor Source #

Constructors

Debian 
HVR Version 

Instances

Eq CompilerVendor Source # 
Data CompilerVendor Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CompilerVendor -> c CompilerVendor #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CompilerVendor #

toConstr :: CompilerVendor -> Constr #

dataTypeOf :: CompilerVendor -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CompilerVendor) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CompilerVendor) #

gmapT :: (forall b. Data b => b -> b) -> CompilerVendor -> CompilerVendor #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CompilerVendor -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CompilerVendor -> r #

gmapQ :: (forall d. Data d => d -> u) -> CompilerVendor -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CompilerVendor -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CompilerVendor -> m CompilerVendor #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CompilerVendor -> m CompilerVendor #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CompilerVendor -> m CompilerVendor #

Ord CompilerVendor Source # 
Show CompilerVendor Source # 
Memoizable CompilerVendor Source # 

Methods

memoize :: (CompilerVendor -> v) -> CompilerVendor -> v #

hvrCabalVersion :: Version -> Version Source #

What version of Cabal goes with this version of GHC?

hvrHappyVersion :: Version -> Version Source #

What version of Happy goes with this version of GHC?

hvrAlexVersion :: Version -> Version Source #

What version of Alex goes with this version of GHC?

withModifiedPATH :: MonadIO m => (String -> String) -> m a -> m a Source #

data CompilerChoice Source #

Up until now this system only worked with Debian's or Ubuntu's ghc source package, which has binary package names ghc, ghc-prof, ghc-doc, etc. This type is intended to add support for Herbert Valerio Riedel's (hvr's) repository of several different versions of ghc and supporting tools happy, alex and cabal. These have different binary package names, and the packages put the executables in different locations than the Debian (and Ubuntu) packages. This option is activated by the --hvr-version option to cabal-debian.

Instances

Eq CompilerChoice Source # 
Data CompilerChoice Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CompilerChoice -> c CompilerChoice #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CompilerChoice #

toConstr :: CompilerChoice -> Constr #

dataTypeOf :: CompilerChoice -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CompilerChoice) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CompilerChoice) #

gmapT :: (forall b. Data b => b -> b) -> CompilerChoice -> CompilerChoice #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CompilerChoice -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CompilerChoice -> r #

gmapQ :: (forall d. Data d => d -> u) -> CompilerChoice -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CompilerChoice -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CompilerChoice -> m CompilerChoice #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CompilerChoice -> m CompilerChoice #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CompilerChoice -> m CompilerChoice #

Ord CompilerChoice Source # 
Show CompilerChoice Source # 
Memoizable CompilerChoice Source # 

Methods

memoize :: (CompilerChoice -> v) -> CompilerChoice -> v #

getCompilerInfo :: MonadIO m => FilePath -> CompilerFlavor -> WithProcAndSys m (Either String CompilerInfo) Source #

IO based alternative to newestAvailableCompilerId - install the compiler into the chroot if necessary and ask it for its version number. This has the benefit of working for ghcjs, which doesn't make the base ghc version available in the version number.

Orphan instances