Adding an option to cabal-install

jim burton jim at sdf-eu.org
Sun Nov 25 11:06:01 EST 2007


Hi, I was planning to make a small change to Fetch.hs to let it be used
behind a proxy server, using the value of $http_proxy or $HTTP_PROXY
where one of them exists -- hope that sounds OK? This is easy to do, but
so that windows users can benefit it would be good to make this an
option read from the config file and/or opts and I'm having a much
harder time working out how to do that. I tried to mimic the way other
options work but can't get it working. Can you point out why? Several of
the functions below aren't expected to work properly but should allow
this line to be read from .cabal/conf:

http_proxy:http://proxy.server.com:80

But I get this: 

> $ ~/haskell/bin/cabal -v3 clean
> Config file warning: Unrecognized stanza on line 5
> Configuration:
> compiler: GHC
> ...
> http_proxy: Nothing


Here are the main places that I thought I needed to make changes:

-- added to Types.hs
data Option = OptCompilerFlavor CompilerFlavor
            ...
            | OptHttpProxy ProxyInfo
  deriving (Eq,Show)

data ConfigFlags = ConfigFlags {
        configCompiler    :: CompilerFlavor,
        ...
        configHttpProxy   :: Maybe ProxyInfo
   }
  deriving (Show) 

data ProxyInfo = ProxyInfo { proxyhost :: String
                           , proxyport :: Int
                           , proxyuser :: Maybe String
                           , proxypass :: Maybe String }
                 deriving (Show, Eq)

-- added to Config.hs
defaultConfigFlags = 
    do ...
       return $ ConfigFlags 
               { configCompiler    = defaultCompiler
               ...
               , configHttpProxy   = Nothing
               }

configFieldDescrs :: [FieldDescr ConfigFlags]
configFieldDescrs = 
    configWriteFieldDescrs
    ++ map userInstallDirField installDirDescrs
    ++ map globalInstallDirField installDirDescrs
    ++ [proxyField]

proxyField :: FieldDescr ConfigFlags
proxyField = liftProxyField "http_proxy" (text . show) parseProxy
configProxy (\p cfg -> cfg { configHttpProxy = p} ) 

{- This will need to be in IO, using getEnv to read the env vars by
preference -}
parseProxy :: ReadP r (Maybe ProxyInfo)
parseProxy = do host <- munch1 (\c -> isAlphaNum c || c `elem` "_-.")
                char ':'
                port <- munch1 (\c -> isAlphaNum c)
                return $ Just (ProxyInfo host ((read port)::Int) Nothing
Nothing)

{- For consistency these functions should be in Distribution.ParseUtils
-}

configProxy :: ConfigFlags -> Maybe ProxyInfo
configProxy = configHttpProxy

liftProxyField :: String -> (a -> Doc) -> (ReadP a a)
            -> (b -> a) -> (a -> b -> b) -> FieldDescr b
liftProxyField name showF readF get set
  = liftField get set $ field name showF readF
-----------------------------------------------------

Thanks,

Jim




More information about the cabal-devel mailing list