[commit: ghc] wip/nfs-locking: Base: Don't reexport Data.Char (a9aa2ac)
git at git.haskell.org
git at git.haskell.org
Thu Oct 26 23:31:44 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/a9aa2ac5825514967ea60f28473ec1a6d435c1a4/ghc
>---------------------------------------------------------------
commit a9aa2ac5825514967ea60f28473ec1a6d435c1a4
Author: Ben Gamari <ben at smart-cactus.org>
Date: Thu Dec 24 14:02:38 2015 +0100
Base: Don't reexport Data.Char
It's really not used often enough to warrant special treatment
>---------------------------------------------------------------
a9aa2ac5825514967ea60f28473ec1a6d435c1a4
src/Base.hs | 2 --
src/Oracles/WindowsRoot.hs | 1 +
src/Rules/Library.hs | 2 ++
src/Rules/Program.hs | 2 ++
4 files changed, 5 insertions(+), 2 deletions(-)
diff --git a/src/Base.hs b/src/Base.hs
index 47a4285..3c62ed5 100644
--- a/src/Base.hs
+++ b/src/Base.hs
@@ -3,7 +3,6 @@ module Base (
module Control.Applicative,
module Control.Monad.Extra,
module Control.Monad.Reader,
- module Data.Char,
module Data.Function,
module Data.List,
module Data.Maybe,
@@ -34,7 +33,6 @@ module Base (
import Control.Applicative
import Control.Monad.Extra
import Control.Monad.Reader
-import Data.Char
import Data.Function
import Data.List
import Data.Maybe
diff --git a/src/Oracles/WindowsRoot.hs b/src/Oracles/WindowsRoot.hs
index 2ec13c7..89dd011 100644
--- a/src/Oracles/WindowsRoot.hs
+++ b/src/Oracles/WindowsRoot.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
module Oracles.WindowsRoot (windowsRoot, windowsRootOracle) where
+import Data.Char (isSpace)
import Base
newtype WindowsRoot = WindowsRoot ()
diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs
index 1df83a8..db1624b 100644
--- a/src/Rules/Library.hs
+++ b/src/Rules/Library.hs
@@ -1,5 +1,7 @@
module Rules.Library (buildPackageLibrary, cSources, hSources) where
+import Data.Char
+
import Expression hiding (splitPath)
import GHC
import Oracles
diff --git a/src/Rules/Program.hs b/src/Rules/Program.hs
index a24fcdc..962ce1d 100644
--- a/src/Rules/Program.hs
+++ b/src/Rules/Program.hs
@@ -1,5 +1,7 @@
module Rules.Program (buildProgram) where
+import Data.Char
+
import Expression hiding (splitPath)
import GHC hiding (ghci)
import Oracles
More information about the ghc-commits
mailing list