summaryrefslogtreecommitdiff
path: root/ghc/compiler/main
diff options
context:
space:
mode:
Diffstat (limited to 'ghc/compiler/main')
-rw-r--r--ghc/compiler/main/DriverFlags.hs6
-rw-r--r--ghc/compiler/main/DriverPipeline.hs2
-rw-r--r--ghc/compiler/main/DriverState.hs14
-rw-r--r--ghc/compiler/main/Main.hs6
-rw-r--r--ghc/compiler/main/SysTools.lhs4
5 files changed, 16 insertions, 16 deletions
diff --git a/ghc/compiler/main/DriverFlags.hs b/ghc/compiler/main/DriverFlags.hs
index 713b287e89..6a6a744c2e 100644
--- a/ghc/compiler/main/DriverFlags.hs
+++ b/ghc/compiler/main/DriverFlags.hs
@@ -1,7 +1,7 @@
{-# OPTIONS -#include "hschooks.h" #-}
-----------------------------------------------------------------------------
--- $Id: DriverFlags.hs,v 1.90 2002/03/29 21:39:37 sof Exp $
+-- $Id: DriverFlags.hs,v 1.91 2002/04/05 23:24:29 sof Exp $
--
-- Driver flags
--
@@ -138,8 +138,8 @@ findArg spec arg
arg_ok (NoArg _) rest arg = null rest
arg_ok (HasArg _) rest arg = True
arg_ok (SepArg _) rest arg = null rest
-arg_ok (Prefix _) rest arg = not (null rest)
-arg_ok (PrefixPred p _) rest arg = not (null rest) && p rest
+arg_ok (Prefix _) rest arg = notNull rest
+arg_ok (PrefixPred p _) rest arg = notNull rest && p rest
arg_ok (OptPrefix _) rest arg = True
arg_ok (PassFlag _) rest arg = null rest
arg_ok (AnySuffix _) rest arg = True
diff --git a/ghc/compiler/main/DriverPipeline.hs b/ghc/compiler/main/DriverPipeline.hs
index 7dd690aee3..b979232ae2 100644
--- a/ghc/compiler/main/DriverPipeline.hs
+++ b/ghc/compiler/main/DriverPipeline.hs
@@ -862,7 +862,7 @@ mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan = unlines $
-- Complain about non-dynamic flags in OPTIONS pragmas
checkProcessArgsResult flags basename suff
- = do when (not (null flags)) (throwDyn (ProgramError (
+ = do when (notNull flags) (throwDyn (ProgramError (
basename ++ "." ++ suff
++ ": static flags are not allowed in {-# OPTIONS #-} pragmas:\n\t"
++ unwords flags)) (ExitFailure 1))
diff --git a/ghc/compiler/main/DriverState.hs b/ghc/compiler/main/DriverState.hs
index b8684fea51..cd4f1fbed3 100644
--- a/ghc/compiler/main/DriverState.hs
+++ b/ghc/compiler/main/DriverState.hs
@@ -1,5 +1,5 @@
-----------------------------------------------------------------------------
--- $Id: DriverState.hs,v 1.75 2002/04/05 16:43:56 sof Exp $
+-- $Id: DriverState.hs,v 1.76 2002/04/05 23:24:29 sof Exp $
--
-- Settings for the driver
--
@@ -54,7 +54,7 @@ setMode :: GhcMode -> String -> IO ()
setMode m flag = do
old_mode <- readIORef v_GhcMode
old_flag <- readIORef v_GhcModeFlag
- when (not (null (old_flag))) $
+ when (notNull (old_flag)) $
throwDyn (UsageError
("cannot use `" ++ old_flag ++ "' with `" ++ flag ++ "'"))
writeIORef v_GhcMode m
@@ -389,7 +389,7 @@ addToDirList :: IORef [String] -> String -> IO ()
addToDirList ref path
= do paths <- readIORef ref
shiny_new_ones <- splitUp path
- writeIORef ref (paths ++ filter (not.null) shiny_new_ones)
+ writeIORef ref (paths ++ filter notNull shiny_new_ones)
-- empty paths are ignored: there might be a trailing
-- ':' in the initial list, for example. Empty paths can
-- cause confusion when they are translated into -I options
@@ -488,23 +488,23 @@ addPackage package
getPackageImportPath :: IO [String]
getPackageImportPath = do
ps <- getPackageInfo
- return (nub (filter (not.null) (concatMap import_dirs ps)))
+ return (nub (filter notNull (concatMap import_dirs ps)))
getPackageIncludePath :: IO [String]
getPackageIncludePath = do
ps <- getPackageInfo
- return (nub (filter (not.null) (concatMap include_dirs ps)))
+ return (nub (filter notNull (concatMap include_dirs ps)))
-- includes are in reverse dependency order (i.e. rts first)
getPackageCIncludes :: IO [String]
getPackageCIncludes = do
ps <- getPackageInfo
- return (reverse (nub (filter (not.null) (concatMap c_includes ps))))
+ return (reverse (nub (filter notNull (concatMap c_includes ps))))
getPackageLibraryPath :: IO [String]
getPackageLibraryPath = do
ps <- getPackageInfo
- return (nub (filter (not.null) (concatMap library_dirs ps)))
+ return (nub (filter notNull (concatMap library_dirs ps)))
getPackageLibraries :: IO [String]
getPackageLibraries = do
diff --git a/ghc/compiler/main/Main.hs b/ghc/compiler/main/Main.hs
index 5d463a6d8c..03ab8a596e 100644
--- a/ghc/compiler/main/Main.hs
+++ b/ghc/compiler/main/Main.hs
@@ -1,7 +1,7 @@
{-# OPTIONS -fno-warn-incomplete-patterns -optc-DNON_POSIX_SOURCE #-}
-----------------------------------------------------------------------------
--- $Id: Main.hs,v 1.103 2002/04/05 16:43:56 sof Exp $
+-- $Id: Main.hs,v 1.104 2002/04/05 23:24:29 sof Exp $
--
-- GHC Driver program
--
@@ -165,7 +165,7 @@ main =
do putStr "warning: -O conflicts with --interactive; -O turned off.\n"
writeIORef v_OptLevel 0
orig_ways <- readIORef v_Ways
- when (not (null orig_ways) && mode == DoInteractive) $
+ when (notNull orig_ways && mode == DoInteractive) $
do throwDyn (UsageError
"--interactive can't be used with -prof, -ticky, -unreg or -smp.")
@@ -338,7 +338,7 @@ checkOptions :: [String] -> IO ()
checkOptions srcs = do
-- complain about any unknown flags
let unknown_opts = [ f | f@('-':_) <- srcs ]
- when (not (null unknown_opts)) (unknownFlagsErr unknown_opts)
+ when (notNull unknown_opts) (unknownFlagsErr unknown_opts)
-- verify that output files point somewhere sensible.
verifyOutputFiles
-- and anything else that it might be worth checking for
diff --git a/ghc/compiler/main/SysTools.lhs b/ghc/compiler/main/SysTools.lhs
index f5af8c31d1..a108c9e106 100644
--- a/ghc/compiler/main/SysTools.lhs
+++ b/ghc/compiler/main/SysTools.lhs
@@ -65,7 +65,7 @@ import DriverUtil
import Config
import Outputable
import Panic ( progName, GhcException(..) )
-import Util ( global, dropList )
+import Util ( global, dropList, notNull )
import CmdLineOpts ( dynFlag, verbosity )
import Exception ( throwDyn )
@@ -475,7 +475,7 @@ findTopDir minusbs
}
where
-- get_proto returns a Unix-format path (relying on getExecDir to do so too)
- get_proto | not (null minusbs)
+ get_proto | notNull minusbs
= return (unDosifyPath (drop 2 (last minusbs))) -- 2 for "-B"
| otherwise
= do { maybe_exec_dir <- getExecDir -- Get directory of executable