Skip to content

Commit

Permalink
Ship transformers with GHC
Browse files Browse the repository at this point in the history
This means that we can use the standard MonadIO class, rather than
needing our own copy.
  • Loading branch information
Ian Lynagh committed Jan 2, 2013
1 parent b13d546 commit 71feb10
Show file tree
Hide file tree
Showing 6 changed files with 24 additions and 56 deletions.
3 changes: 2 additions & 1 deletion compiler/ghc.cabal.in
Expand Up @@ -52,7 +52,8 @@ Library
array >= 0.1 && < 0.5,
filepath >= 1 && < 1.4,
Cabal,
hpc
hpc,
transformers

if flag(stage1) && impl(ghc < 7.5)
Build-Depends: old-time >= 1 && < 1.2
Expand Down
23 changes: 1 addition & 22 deletions compiler/utils/MonadUtils.hs
Expand Up @@ -23,37 +23,16 @@ module MonadUtils
, maybeMapM
) where

-------------------------------------------------------------------------------
-- Detection of available libraries
-------------------------------------------------------------------------------

-- we don't depend on MTL for now
#define HAVE_MTL 0

-------------------------------------------------------------------------------
-- Imports
-------------------------------------------------------------------------------

import Maybes

import Control.Applicative
#if HAVE_MTL
import Control.Monad.Trans
#endif
import Control.Monad
import Control.Monad.Fix

-------------------------------------------------------------------------------
-- MTL
-------------------------------------------------------------------------------

#if !HAVE_MTL

class Monad m => MonadIO m where
liftIO :: IO a -> m a

instance MonadIO IO where liftIO = id
#endif
import Control.Monad.IO.Class

-------------------------------------------------------------------------------
-- Lift combinators
Expand Down
22 changes: 11 additions & 11 deletions ghc.mk
Expand Up @@ -330,7 +330,7 @@ endif
# They do not say "this package will be built"; see $(PACKAGES_xx) for that

# Packages that are built but not installed
PKGS_THAT_ARE_INTREE_ONLY := haskeline transformers terminfo xhtml
PKGS_THAT_ARE_INTREE_ONLY := haskeline terminfo xhtml

PKGS_THAT_ARE_DPH := \
dph/dph-base \
Expand All @@ -355,7 +355,7 @@ PKGS_THAT_USE_TH := $(PKGS_THAT_ARE_DPH)
#
# We assume that the stage0 compiler has a suitable bytestring package,
# so we don't have to include it below.
PKGS_THAT_BUILD_WITH_STAGE0 = Cabal/Cabal hpc binary bin-package-db hoopl
PKGS_THAT_BUILD_WITH_STAGE0 = Cabal/Cabal hpc binary bin-package-db hoopl transformers

# $(EXTRA_PACKAGES) is another classification, of packages built but
# not installed
Expand Down Expand Up @@ -1337,17 +1337,17 @@ BINDIST_LIBRARY_FLAGS = --enable-library-vanilla --disable-shared
endif
BINDIST_LIBRARY_FLAGS += --disable-library-prof

.PHONY: validate_build_transformers
validate_build_transformers:
cd libraries/transformers && "$(BINDIST_PREFIX)/bin/ghc" --make Setup
cd libraries/transformers && ./Setup configure --with-ghc="$(BINDIST_PREFIX)/bin/ghc" $(BINDIST_HADDOCK_FLAG) $(BINDIST_LIBRARY_FLAGS) --global --builddir=dist-bindist --prefix="$(BINDIST_PREFIX)"
cd libraries/transformers && ./Setup build --builddir=dist-bindist
.PHONY: validate_build_xhtml
validate_build_xhtml:
cd libraries/xhtml && "$(BINDIST_PREFIX)/bin/ghc" --make Setup
cd libraries/xhtml && ./Setup configure --with-ghc="$(BINDIST_PREFIX)/bin/ghc" $(BINDIST_HADDOCK_FLAG) $(BINDIST_LIBRARY_FLAGS) --global --builddir=dist-bindist --prefix="$(BINDIST_PREFIX)"
cd libraries/xhtml && ./Setup build --builddir=dist-bindist
ifeq "$(HADDOCK_DOCS)" "YES"
cd libraries/transformers && ./Setup haddock --builddir=dist-bindist
cd libraries/xhtml && ./Setup haddock --builddir=dist-bindist
endif
cd libraries/transformers && ./Setup install --builddir=dist-bindist
cd libraries/transformers && ./Setup clean --builddir=dist-bindist
cd libraries/transformers && rm -f Setup Setup.exe Setup.hi Setup.o
cd libraries/xhtml && ./Setup install --builddir=dist-bindist
cd libraries/xhtml && ./Setup clean --builddir=dist-bindist
cd libraries/xhtml && rm -f Setup Setup.exe Setup.hi Setup.o

# -----------------------------------------------------------------------------
# Numbered phase targets
Expand Down
22 changes: 6 additions & 16 deletions ghc/GhciMonad.hs
Expand Up @@ -37,7 +37,6 @@ import SrcLoc
import Module
import ObjLink
import Linker
import qualified MonadUtils

import Exception
import Numeric
Expand All @@ -47,13 +46,13 @@ import Data.IORef
import System.CPUTime
import System.Environment
import System.IO
import Control.Monad as Monad
import Control.Monad
import GHC.Exts

import System.Console.Haskeline (CompletionFunc, InputT)
import qualified System.Console.Haskeline as Haskeline
import Control.Monad.Trans.Class as Trans
import Control.Monad.IO.Class as Trans
import Control.Monad.Trans.Class
import Control.Monad.IO.Class

-----------------------------------------------------------------------------
-- GHCi monad
Expand Down Expand Up @@ -186,11 +185,8 @@ modifyGHCiState f = GHCi $ \r -> liftIO $ readIORef r >>= writeIORef r . f
liftGhc :: Ghc a -> GHCi a
liftGhc m = GHCi $ \_ -> m

instance MonadUtils.MonadIO GHCi where
liftIO = liftGhc . MonadUtils.liftIO

instance Trans.MonadIO Ghc where
liftIO = MonadUtils.liftIO
instance MonadIO GHCi where
liftIO = liftGhc . liftIO

instance HasDynFlags GHCi where
getDynFlags = getSessionDynFlags
Expand All @@ -206,9 +202,6 @@ instance GhcMonad (InputT GHCi) where
setSession = lift . setSession
getSession = lift getSession

instance MonadUtils.MonadIO (InputT GHCi) where
liftIO = Trans.liftIO

instance ExceptionMonad GHCi where
gcatch m h = GHCi $ \r -> unGHCi m r `gcatch` (\e -> unGHCi (h e) r)
gblock (GHCi m) = GHCi $ \r -> gblock (m r)
Expand All @@ -220,9 +213,6 @@ instance ExceptionMonad GHCi where
in
unGHCi (f g_restore) s

instance MonadIO GHCi where
liftIO = MonadUtils.liftIO

instance Haskeline.MonadException Ghc where
controlIO f = Ghc $ \s -> Haskeline.controlIO $ \(Haskeline.RunIO run) -> let
run' = Haskeline.RunIO (fmap (Ghc . const) . run . flip unGhc s)
Expand Down Expand Up @@ -259,7 +249,7 @@ printForUser :: GhcMonad m => SDoc -> m ()
printForUser doc = do
unqual <- GHC.getPrintUnqual
dflags <- getDynFlags
MonadUtils.liftIO $ Outputable.printForUser dflags stdout unqual doc
liftIO $ Outputable.printForUser dflags stdout unqual doc

printForUserPartWay :: SDoc -> GHCi ()
printForUserPartWay doc = do
Expand Down
1 change: 1 addition & 0 deletions mk/validate-settings.mk
Expand Up @@ -113,6 +113,7 @@ libraries/mtl_dist-install_EXTRA_HC_OPTS += -Wwarn
libraries/primitive_dist-install_EXTRA_HC_OPTS += -Wwarn

# temporarily turn off -Werror for transformers
libraries/transformers_dist-boot_EXTRA_HC_OPTS += -Wwarn
libraries/transformers_dist-install_EXTRA_HC_OPTS += -Wwarn

# vector has some unused match warnings
Expand Down
9 changes: 3 additions & 6 deletions validate
Expand Up @@ -106,16 +106,13 @@ if [ $speed != "FAST" ]; then
$make test_bindist TEST_PREP=YES

#
# Install the transformers package into the bindist, because it is
# used by some tests.
# It isn't essential that we do this (the failing tests will
# be treated as expected failures), but we get a bit more test
# coverage, and also verify that we can install a package into the
# Install the xhtml package into the bindist.
# This verifies that we can install a package into the
# bindist with Cabal.
#
bindistdir="bindisttest/install dir"

$make validate_build_transformers BINDIST_PREFIX="$thisdir/$bindistdir"
$make validate_build_xhtml BINDIST_PREFIX="$thisdir/$bindistdir"
fi

fi # testsuite-only
Expand Down

0 comments on commit 71feb10

Please sign in to comment.