Skip to content

Commit

Permalink
Can build without haskell98.
Browse files Browse the repository at this point in the history
  • Loading branch information
master-q committed Mar 28, 2013
1 parent 03e1d22 commit bc5d4d0
Show file tree
Hide file tree
Showing 18 changed files with 41 additions and 43 deletions.
2 changes: 1 addition & 1 deletion configure.ac
Expand Up @@ -16,7 +16,7 @@ AC_ARG_WITH(hcflags,

GHC=$HC
GHCFLAGS=
GHC_CHECK_MODULE([System],[],[],[],[HCFLAGS="$HCFLAGS -hide-all-packages -package haskell98"])
GHC_CHECK_MODULE([System.IO],[],[],[],[HCFLAGS="$HCFLAGS -hide-all-packages"])

AC_PROG_INSTALL
AC_PATH_PROGS(SH, sh)
Expand Down
6 changes: 3 additions & 3 deletions src/ChaseImports.hs
Expand Up @@ -24,10 +24,10 @@ import RuleUtils (Tag)
import DataP
import CommandP
import ParseLib2
import System
import List
import System.Environment
import Data.List
import qualified Unlit
import Monad
import Control.Monad
import GenUtil

try x = catch (x >>= return . Right) (return . Left)
Expand Down
6 changes: 2 additions & 4 deletions src/DataP.lhs
Expand Up @@ -10,10 +10,8 @@ needs to be fixed.
>where

>import ParseLib2
>import Char
>import List
>import Monad

>import Data.Char
>import Data.List

>data Statement = DataStmt | NewTypeStmt deriving (Eq,Show)
>data Data = D { name :: Name, -- type name
Expand Down
12 changes: 6 additions & 6 deletions src/DrIFT.hs
Expand Up @@ -7,17 +7,17 @@ import ChaseImports
import DataP
import GenUtil
import GetOpt
import Char
import IO hiding(try)
import List (partition,isSuffixOf,sort, groupBy, sortBy)
import Monad(unless)
import Data.List (partition,isSuffixOf,sort, groupBy, sortBy)
import Control.Monad(unless)
import PreludData(preludeData)
import Pretty
import RuleUtils (commentLine,texts)
import RuleUtils(Rule,Tag)
import Version
import qualified Rules(rules)
import qualified System
import System.IO
import System.Environment
import Data.Char

data Op = OpList | OpDerive | OpVersion

Expand Down Expand Up @@ -78,7 +78,7 @@ doList = do

header = "Usage: DrIFT [OPTION...] file"
main = do
argv <- System.getArgs
argv <- getArgs
(env,n) <- case (getOpt Permute options argv) of
(as,n,[]) -> return (foldr ($) env as ,n)
(_,_,errs) -> putErrDie (concat errs ++ usageInfo header options)
Expand Down
31 changes: 17 additions & 14 deletions src/GenUtil.hs
Expand Up @@ -39,7 +39,7 @@ module GenUtil(
-- ** Simple deconstruction
fromLeft,fromRight,fsts,snds,splitEither,rights,lefts,
-- ** System routines
exitSuccess, System.exitFailure, epoch, lookupEnv,endOfTime,
exitSuccess, exitFailure, epoch, lookupEnv,endOfTime,
-- ** Random routines
repMaybe,
liftT2, liftT3, liftT4,
Expand Down Expand Up @@ -91,14 +91,17 @@ module GenUtil(
UniqueProducer(..)
) where

import Char(isAlphaNum, isSpace, toLower, ord)
import List(group,sort)
import List(intersperse, sortBy, groupBy)
import Monad
import qualified IO
import qualified System
import Random(StdGen, newStdGen, Random(randomR))
import Time
import System.Time
import System.IO
import System.IO.Error
import System.Exit(exitFailure, exitWith, ExitCode(..))
import System.Environment
import Control.Monad(join, liftM, MonadPlus, mzero)
import System.Random(StdGen, newStdGen, Random(randomR))
import Data.Char(isAlphaNum, isSpace, toLower, ord)
import Data.List(group,sort)
import Data.List(intersperse, sortBy, groupBy)
-- import Random(StdGen, newStdGen, Random(randomR))

{-# SPECIALIZE snub :: [String] -> [String] #-}
{-# SPECIALIZE snub :: [Int] -> [Int] #-}
Expand Down Expand Up @@ -127,7 +130,7 @@ sortGroupUnderF f xs = [ (f x, xs) | xs@(x:_) <- sortGroupUnder f xs]

-- | write string to standard error
putErr :: String -> IO ()
putErr = IO.hPutStr IO.stderr
putErr = System.IO.hPutStr System.IO.stderr

-- | write string and newline to standard error
putErrLn :: String -> IO ()
Expand All @@ -137,13 +140,13 @@ putErrLn s = putErr (s ++ "\n")
-- | write string and newline to standard error,
-- then exit program with failure.
putErrDie :: String -> IO a
putErrDie s = putErrLn s >> System.exitFailure
putErrDie s = putErrLn s >> exitFailure


-- | exit program successfully. 'exitFailure' is
-- also exported from System.
exitSuccess :: IO a
exitSuccess = System.exitWith System.ExitSuccess
exitSuccess = exitWith ExitSuccess


{-# INLINE fromRight #-}
Expand Down Expand Up @@ -381,7 +384,7 @@ shellQuote ss = unwords (map f ss) where
-- | looks up an enviornment variable and returns it in a 'MonadPlus' rather
-- than raising an exception if the variable is not set.
lookupEnv :: MonadPlus m => String -> IO (m String)
lookupEnv s = catch (fmap return $ System.getEnv s) (\e -> if IO.isDoesNotExistError e then return mzero else ioError e)
lookupEnv s = catch (fmap return $ getEnv s) (\e -> if isDoesNotExistError e then return mzero else ioError e)

{-# SPECIALIZE fmapLeft :: (a -> c) -> [(Either a b)] -> [(Either c b)] #-}
fmapLeft :: Functor f => (a -> c) -> f (Either a b) -> f (Either c b)
Expand Down Expand Up @@ -495,7 +498,7 @@ showDuration x = st "d" dayI ++ st "h" hourI ++ st "m" minI ++ show secI ++ "s"
-- arguments are given, read stdin.

getArgContents = do
as <- System.getArgs
as <- getArgs
let f "-" = getContents
f fn = readFile fn
cs <- mapM f as
Expand Down
2 changes: 1 addition & 1 deletion src/GetOpt.hs
Expand Up @@ -21,7 +21,7 @@ module GetOpt (
ArgOrder(..), OptDescr(..), ArgDescr(..), usageInfo, getOpt
) where

import List(isPrefixOf)
import Data.List(isPrefixOf)

data ArgOrder a -- what to do with options following non-options:
= RequireOrder -- no option processing after first non-option
Expand Down
4 changes: 2 additions & 2 deletions src/ParseLib2.hs
Expand Up @@ -31,8 +31,8 @@ module ParseLib2
many1_offside,many_offside,off,
opt, skipUntil, skipUntilOff,skipUntilParse,skipNest) where

import Char
import Monad
import Data.Char
import Control.Monad

infixr 5 +++

Expand Down
2 changes: 1 addition & 1 deletion src/Rules/Arbitrary.hs
@@ -1,6 +1,6 @@
module Rules.Arbitrary(rules) where

import List
import Data.List
import RuleUtils

rules = [
Expand Down
2 changes: 1 addition & 1 deletion src/Rules/Binary.hs
@@ -1,6 +1,6 @@
module Rules.Binary(rules) where

import List (nub,intersperse)
import Data.List (nub,intersperse)
import RuleUtils

rules = [
Expand Down
2 changes: 1 addition & 1 deletion src/Rules/BitsBinary.hs
@@ -1,7 +1,7 @@
-- stub module to add your own rules.
module Rules.BitsBinary(rules) where

import List (nub,intersperse)
import Data.List (nub,intersperse)
import RuleUtils -- useful to have a look at this too

rules = [
Expand Down
2 changes: 1 addition & 1 deletion src/Rules/FunctorM.hs
@@ -1,7 +1,7 @@
-- stub module to add your own rules.
module Rules.FunctorM (rules) where

import List
import Data.List
import RuleUtils

rules = [
Expand Down
2 changes: 1 addition & 1 deletion src/Rules/Generic.hs
Expand Up @@ -3,7 +3,7 @@ module Rules.Generic(rules) where

-- import StandardRules
import RuleUtils
import List(intersperse)
import Data.List(intersperse)


rules :: [RuleDef]
Expand Down
2 changes: 1 addition & 1 deletion src/Rules/GhcBinary.hs
@@ -1,7 +1,7 @@
-- stub module to add your own rules.
module Rules.GhcBinary (rules) where

import List (nub,intersperse)
import Data.List (nub,intersperse)
import RuleUtils -- useful to have a look at this too

rules = [
Expand Down
1 change: 0 additions & 1 deletion src/Rules/Monoid.hs
@@ -1,7 +1,6 @@
-- stub module to add your own rules.
module Rules.Monoid (rules) where

import List
import RuleUtils

rules = [
Expand Down
2 changes: 1 addition & 1 deletion src/Rules/Standard.hs
@@ -1,7 +1,7 @@
module Rules.Standard(rules) where

import RuleUtils
import List
import Data.List
import GenUtil


Expand Down
1 change: 0 additions & 1 deletion src/Rules/Utility.hs
@@ -1,6 +1,5 @@
module Rules.Utility(rules) where
import RuleUtils
import List
import GenUtil

rules :: [RuleDef]
Expand Down
2 changes: 1 addition & 1 deletion src/Rules/Xml.hs
@@ -1,7 +1,7 @@
-- expanded from stub module to add new rules.
module Rules.Xml(rules) where

import List (nub,sortBy)
import Data.List (nub,sortBy)
import RuleUtils -- useful to have a look at this too

rules :: [RuleDef]
Expand Down
3 changes: 1 addition & 2 deletions src/Unlit.hs
Expand Up @@ -4,8 +4,7 @@ module Unlit(unlit) where
-- "Report on the Programming Language Haskell",
-- version 1.2, appendix C.


import Char
import Data.Char

data Classified = Program String | Blank | Comment
| Include Int String | Pre String
Expand Down

0 comments on commit bc5d4d0

Please sign in to comment.