Skip to content
Snippets Groups Projects
Commit 300e6859 authored by Duncan Coutts's avatar Duncan Coutts
Browse files

Modules that use cpp have to have cpp language prama to say so

Otherwise we cannot compile with just ghc --make
which is actually essential for bootstrapping.
parent ea174101
No related merge requests found
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -cpp #-}
{-# OPTIONS_NHC98 -cpp #-}
{-# OPTIONS_JHC -fcpp #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Configuration
......@@ -315,6 +319,8 @@ newtype DependencyMap = DependencyMap { unDependencyMap :: Map String VersionRan
#if !defined(__GLASGOW_HASKELL__) || (__GLASGOW_HASKELL__ >= 606)
deriving (Show, Read)
#else
-- The Show/Read instance for Data.Map in ghc-6.4 is useless
-- so we have to re-implement it here:
instance Show DependencyMap where
showsPrec d (DependencyMap m) =
showParen (d > 10) (showString "DependencyMap" . shows (M.toList m))
......
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -cpp #-}
{-# OPTIONS_NHC98 -cpp #-}
{-# OPTIONS_JHC -fcpp #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Simple.PackageIndex
......@@ -90,6 +94,8 @@ data Package pkg => PackageIndex pkg = PackageIndex
#if !defined(__GLASGOW_HASKELL__) || (__GLASGOW_HASKELL__ >= 606)
deriving (Show, Read)
#else
-- The Show/Read instance for Data.Map in ghc-6.4 is useless
-- so we have to re-implement it here:
instance (Package pkg, Show pkg) => Show (PackageIndex pkg) where
showsPrec d (PackageIndex m) =
showParen (d > 10) (showString "PackageIndex" . shows (Map.toList m))
......
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