Skip to content
Snippets Groups Projects
Commit 568b6b74 authored by malcolm wallace's avatar malcolm wallace
Browse files

remove ugly nhc98 cpp+defaulting hack - use explicit typesig instead

parent 61289e6f
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Simple.Haddock
......@@ -99,10 +98,6 @@ import System.FilePath((</>), (<.>), splitFileName, splitExtension,
import System.IO (hClose, hPutStrLn)
import Distribution.Version
#ifdef __NHC__
default (Integer,Double,Version)
#endif
-- --------------------------------------------------------------------------
-- Haddock support
......@@ -169,7 +164,8 @@ haddock pkg_descr lbi suffixes flags = do
when isVersion2 $ do
strHadGhcVers <- rawSystemProgramStdout verbosity confHaddock ["--ghc-version"]
let mHadGhcVers = simpleParse strHadGhcVers
let mHadGhcVers :: Maybe Version
mHadGhcVers = simpleParse strHadGhcVers
when (mHadGhcVers == Nothing) $ die "Could not get GHC version from Haddock"
when (fromJust mHadGhcVers /= compilerVersion comp) $
die "Haddock's internal GHC version must match the configured GHC version"
......
{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Simple.Program
......@@ -100,10 +99,6 @@ import System.IO.Error (try)
import Control.Monad (join, foldM)
import Control.Exception as Exception (catch)
#ifdef __NHC__
default (Integer,Double,Version)
#endif
-- | Represents a program which can be configured.
data Program = Program {
-- | The simple name of the program, eg. ghc
......@@ -188,7 +183,8 @@ findProgramVersion :: ProgArg -- ^ version args
findProgramVersion versionArg selectVersion verbosity path = do
str <- rawSystemStdout verbosity path [versionArg]
`Exception.catch` \_ -> return ""
let version = simpleParse (selectVersion str)
let version :: Maybe Version
version = simpleParse (selectVersion str)
case version of
Nothing -> warn verbosity $ "cannot determine version of " ++ path
++ " :\n" ++ show str
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment