cabal-install-parsers-0.3.0.1: Utilities to work with cabal-install files

Safe HaskellNone
LanguageHaskell2010

Cabal.Config

Contents

Synopsis

Types

data Config f Source #

Very minimal representation of ~/.cabal/config file.

Instances
Show (f FilePath) => Show (Config f) Source # 
Instance details

Defined in Cabal.Config

Methods

showsPrec :: Int -> Config f -> ShowS #

show :: Config f -> String #

showList :: [Config f] -> ShowS #

Generic (Config f) Source # 
Instance details

Defined in Cabal.Config

Associated Types

type Rep (Config f) :: Type -> Type #

Methods

from :: Config f -> Rep (Config f) x #

to :: Rep (Config f) x -> Config f #

NFData (f FilePath) => NFData (Config f) Source #

Since: 0.2.1

Instance details

Defined in Cabal.Config

Methods

rnf :: Config f -> () #

type Rep (Config f) Source # 
Instance details

Defined in Cabal.Config

type Rep (Config f) = D1 (MetaData "Config" "Cabal.Config" "cabal-install-parsers-0.3.0.1-2fD8GIxvoR0GeTwPo5RQnW" False) (C1 (MetaCons "Config" PrefixI True) ((S1 (MetaSel (Just "cfgRepositories") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map RepoName Repo)) :*: S1 (MetaSel (Just "cfgRemoteRepoCache") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f FilePath))) :*: (S1 (MetaSel (Just "cfgInstallDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f FilePath)) :*: S1 (MetaSel (Just "cfgStoreDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f FilePath)))))

data Repo Source #

Repository.

missing root-keys, key-threshold which we don't need now.

Constructors

Repo 

Fields

Instances
Show Repo Source # 
Instance details

Defined in Cabal.Config

Methods

showsPrec :: Int -> Repo -> ShowS #

show :: Repo -> String #

showList :: [Repo] -> ShowS #

Generic Repo Source # 
Instance details

Defined in Cabal.Config

Associated Types

type Rep Repo :: Type -> Type #

Methods

from :: Repo -> Rep Repo x #

to :: Rep Repo x -> Repo #

NFData Repo Source #

Since: 0.2.1

Instance details

Defined in Cabal.Config

Methods

rnf :: Repo -> () #

type Rep Repo Source # 
Instance details

Defined in Cabal.Config

type Rep Repo = D1 (MetaData "Repo" "Cabal.Config" "cabal-install-parsers-0.3.0.1-2fD8GIxvoR0GeTwPo5RQnW" False) (C1 (MetaCons "Repo" PrefixI True) (S1 (MetaSel (Just "repoURL") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 URI) :*: S1 (MetaSel (Just "repoSecure") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))

type RepoName = String Source #

Repository name, bare String.

Parsing

readConfig :: IO (Config Identity) Source #

High level convinience function to find and read ~.cabalconfig file

May throw IOException when file doesn't exist, and ParseError on parse error.

findConfig :: IO FilePath Source #

Find the ~/.cabal/config file.

parseConfig :: FilePath -> ByteString -> Either (ParseError NonEmpty) (Config Maybe) Source #

Parse ~/.cabal/config file.

resolveConfig :: Config Maybe -> IO (Config Identity) Source #

Fill the default in ~/.cabal/config file.

Hackage

cfgRepoIndex :: Config Identity -> RepoName -> Maybe FilePath Source #

Find a 01-index.tar for particular repository

hackageHaskellOrg :: RepoName Source #

The default repository of haskell packages, https://hackage.haskell.org/.