[project @ 2002-10-09 17:08:18 by malcolm]
authormalcolm <unknown>
Wed, 9 Oct 2002 17:08:19 +0000 (17:08 +0000)
committermalcolm <unknown>
Wed, 9 Oct 2002 17:08:19 +0000 (17:08 +0000)
Add #ifdefs for nhc98.

Data/Bool.hs
Data/Char.hs
Data/Complex.hs
Data/IORef.hs
Data/Int.hs
Data/Ix.hs
Data/List.hs
Data/Maybe.hs
Data/PackedString.hs
Data/Tuple.hs
Data/Word.hs

index 66b804a..2232aa3 100644 (file)
@@ -26,3 +26,14 @@ module Data.Bool (
 #ifdef __GLASGOW_HASKELL__
 import GHC.Base
 #endif
+
+#ifdef __NHC__
+import Prelude
+import Prelude
+  ( Bool(..)
+  , (&&)
+  , (||)
+  , not
+  , otherwise
+  )
+#endif
index 8694f44..2800684 100644 (file)
@@ -48,3 +48,8 @@ import GHC.Read (readLitChar, lexLitChar)
 import Hugs.Char
 #endif
 
+#ifdef __NHC__
+import Prelude
+import Prelude(Char,String)
+import Char
+#endif
index 8ad4c2e..c9f8334 100644 (file)
@@ -39,7 +39,9 @@ module Data.Complex
 
 import Prelude
 
+#ifndef __NHC__
 import Data.Dynamic
+#endif
 
 infix  6  :+
 
@@ -88,8 +90,10 @@ phase (x:+y)  = atan2 y x
 -- -----------------------------------------------------------------------------
 -- Instances of Complex
 
+#ifndef __NHC__
 #include "Dynamic.h"
 INSTANCE_TYPEABLE1(Complex,complexTc,"Complex")
+#endif
 
 instance  (RealFloat a) => Num (Complex a)  where
     {-# SPECIALISE instance Num (Complex Float) #-}
index 3607734..284c2bf 100644 (file)
@@ -41,7 +41,18 @@ import GHC.Weak
 #endif
 #endif /* __GLASGOW_HASKELL__ */
 
+#ifdef __NHC__
+import NHC.IOExtras
+    ( IORef
+    , newIORef
+    , readIORef
+    , writeIORef
+    )
+#endif
+
+#ifndef __NHC__
 import Data.Dynamic
+#endif
 
 #if defined(__GLASGOW_HASKELL__) && !defined(__PARALLEL_HASKELL__)
 -- |Make a 'Weak' pointer to an 'IORef'
@@ -54,5 +65,7 @@ mkWeakIORef r@(IORef (STRef r#)) f = IO $ \s ->
 modifyIORef :: IORef a -> (a -> a) -> IO ()
 modifyIORef ref f = writeIORef ref . f =<< readIORef ref
 
+#ifndef __NHC__
 #include "Dynamic.h"
 INSTANCE_TYPEABLE1(IORef,ioRefTc,"IORef")
+#endif
index 93d84b6..8e0e8bd 100644 (file)
@@ -33,6 +33,12 @@ import GHC.Int       ( Int8, Int16, Int32, Int64 )
 import Hugs.Int ( Int8, Int16, Int32, Int64 )
 #endif
 
+#ifdef __NHC__
+import Prelude
+import Prelude (Int)
+import NHC.FFI (Int8, Int16, Int32, Int64)
+#endif
+
 {- $notes
 
 * All arithmetic is performed modulo 2^n, where @n@ is the number of
index b947466..44e113a 100644 (file)
@@ -82,3 +82,8 @@ import GHC.Arr
 #ifdef __HUGS__
 import Hugs.Prelude( Ix(..) )
 #endif
+
+#ifdef __NHC__
+import Ix (Ix(..))
+#endif
+
index 63277f3..398e8b2 100644 (file)
 
 module Data.List
    ( 
+#ifdef __NHC__
+     [] (..)
+   ,
+#endif
      elemIndex        -- :: (Eq a) => a -> [a] -> Maybe Int
    , elemIndices       -- :: (Eq a) => a -> [a] -> [Int]
 
@@ -132,6 +136,7 @@ module Data.List
 
    ) where
 
+import Prelude hiding (Maybe(..))
 import Data.Maybe
 
 #ifdef __GLASGOW_HASKELL__
index 1a1467f..195daab 100644 (file)
@@ -35,6 +35,21 @@ import {-# SOURCE #-} GHC.Err ( error )
 import GHC.Base
 #endif
 
+#ifdef __NHC__
+import Prelude
+import Prelude (Maybe(..), maybe)
+import Maybe
+    ( isJust
+    , isNothing
+    , fromJust
+    , fromMaybe
+    , listToMaybe
+    , maybeToList 
+    , catMaybes
+    , mapMaybe
+    )
+#else
+
 #ifndef __HUGS__
 -- ---------------------------------------------------------------------------
 -- The Maybe type, and instances
@@ -108,3 +123,4 @@ mapMaybe f (x:xs) =
   Nothing -> rs
   Just r  -> r:rs
 
+#endif /* else not __NHC__ */
index f276d14..da0206a 100644 (file)
@@ -23,9 +23,11 @@ module Data.PackedString (
        packString,  -- :: String -> PackedString
        unpackPS,    -- :: PackedString -> String
 
+#ifndef __NHC__
        -- * I\/O with @PackedString@s  
        hPutPS,      -- :: Handle -> PackedString -> IO ()
        hGetPS,      -- :: Handle -> Int -> IO PackedString
+#endif
 
        -- * List-like manipulation functions
        nilPS,       -- :: PackedString
@@ -64,6 +66,8 @@ module Data.PackedString (
 
 import Prelude
 
+#ifndef __NHC__
+
 import Data.Array.Unboxed
 import Data.Array.IO
 import Data.Dynamic
@@ -287,3 +291,75 @@ hGetPS h i = do
   l <- hGetArray h arr i
   chars <- mapM (\i -> readArray arr i >>= return.chr.fromIntegral) [0..l-1]
   return (packString chars)
+
+#else  /* __NHC__ */
+
+--import Prelude hiding (append, break, concat, cons, drop, dropWhile,
+--                       filter, foldl, foldr, head, length, lines, map,
+--                       nil, null, reverse, span, splitAt, subst, tail,
+--                       take, takeWhile, unlines, unwords, words)
+-- also hiding: Ix(..), Functor(..)
+import NHC.PackedString
+
+
+nilPS       :: PackedString
+consPS      :: Char -> PackedString -> PackedString
+headPS      :: PackedString -> Char
+tailPS      :: PackedString -> PackedString
+nullPS      :: PackedString -> Bool
+appendPS    :: PackedString -> PackedString -> PackedString
+lengthPS    :: PackedString -> Int
+indexPS     :: PackedString -> Int -> Char
+mapPS       :: (Char -> Char) -> PackedString -> PackedString
+filterPS    :: (Char -> Bool) -> PackedString -> PackedString
+reversePS   :: PackedString -> PackedString
+concatPS    :: [PackedString] -> PackedString
+elemPS      :: Char -> PackedString -> Bool
+substrPS    :: PackedString -> Int -> Int -> PackedString
+takePS      :: Int -> PackedString -> PackedString
+dropPS      :: Int -> PackedString -> PackedString
+splitAtPS   :: Int -> PackedString -> (PackedString, PackedString)
+
+foldlPS     :: (a -> Char -> a) -> a -> PackedString -> a
+foldrPS     :: (Char -> a -> a) -> a -> PackedString -> a
+takeWhilePS :: (Char -> Bool) -> PackedString -> PackedString
+dropWhilePS :: (Char -> Bool) -> PackedString -> PackedString
+spanPS      :: (Char -> Bool) -> PackedString -> (PackedString, PackedString)
+breakPS     :: (Char -> Bool) -> PackedString -> (PackedString, PackedString)
+linesPS     :: PackedString -> [PackedString]
+
+wordsPS     :: PackedString -> [PackedString]
+splitPS     :: Char -> PackedString -> [PackedString]
+splitWithPS :: (Char -> Bool) -> PackedString -> [PackedString]
+
+nilPS       = NHC.PackedString.nil
+consPS      = NHC.PackedString.cons
+headPS      = NHC.PackedString.head
+tailPS      = NHC.PackedString.tail
+nullPS      = NHC.PackedString.null
+appendPS    = NHC.PackedString.append
+lengthPS    = NHC.PackedString.length
+indexPS p i = (unpackPS p) !! i
+mapPS       = NHC.PackedString.map
+filterPS    = NHC.PackedString.filter
+reversePS   = NHC.PackedString.reverse
+concatPS    = NHC.PackedString.concat
+elemPS c p  = c `elem` unpackPS p
+substrPS    = NHC.PackedString.substr
+takePS      = NHC.PackedString.take
+dropPS      = NHC.PackedString.drop
+splitAtPS   = NHC.PackedString.splitAt
+
+foldlPS     = NHC.PackedString.foldl
+foldrPS     = NHC.PackedString.foldr
+takeWhilePS = NHC.PackedString.takeWhile
+dropWhilePS = NHC.PackedString.dropWhile
+spanPS      = NHC.PackedString.span
+breakPS     = NHC.PackedString.break
+linesPS     = NHC.PackedString.lines
+
+wordsPS     = NHC.PackedString.words
+splitPS c   = splitWithPS (==c)
+splitWithPS = error "Data.PackedString: splitWithPS not implemented"
+
+#endif
index 88d2c67..4e88a74 100644 (file)
 --
 -----------------------------------------------------------------------------
 
-module Data.Tuple (
-         fst           -- :: (a,b) -> a
-       , snd           -- :: (a,b) -> a
-       , curry         -- :: ((a, b) -> c) -> a -> b -> c
-       , uncurry       -- :: (a -> b -> c) -> ((a, b) -> c)
-  ) where
+module Data.Tuple
+  ( fst                -- :: (a,b) -> a
+  , snd                -- :: (a,b) -> a
+  , curry      -- :: ((a, b) -> c) -> a -> b -> c
+  , uncurry    -- :: (a -> b -> c) -> ((a, b) -> c)
+#ifdef __NHC__
+  , (,)(..)
+  , (,,)(..)
+  , (,,,)(..)
+  , (,,,,)(..)
+  , (,,,,,)(..)
+  , (,,,,,,)(..)
+  , (,,,,,,,)(..)
+  , (,,,,,,,,)(..)
+  , (,,,,,,,,,)(..)
+  , (,,,,,,,,,,)(..)
+  , (,,,,,,,,,,,)(..)
+  , (,,,,,,,,,,,,)(..)
+  , (,,,,,,,,,,,,,)(..)
+  , (,,,,,,,,,,,,,,)(..)
+#endif
+  )
+    where
 
 #ifdef __GLASGOW_HASKELL__
 import GHC.Base
+#endif  /* __GLASGOW_HASKELL__ */
+
+#ifdef __NHC__
+import Prelude
+import Prelude
+  ( (,)(..)
+  , (,,)(..)
+  , (,,,)(..)
+  , (,,,,)(..)
+  , (,,,,,)(..)
+  , (,,,,,,)(..)
+  , (,,,,,,,)(..)
+  , (,,,,,,,,)(..)
+  , (,,,,,,,,,)(..)
+  , (,,,,,,,,,,)(..)
+  , (,,,,,,,,,,,)(..)
+  , (,,,,,,,,,,,,)(..)
+  , (,,,,,,,,,,,,,)(..)
+  , (,,,,,,,,,,,,,,)(..)
+  -- nhc98's prelude only supplies tuple instances up to size 15
+  , fst, snd
+  , curry, uncurry
+  )
+#endif
 
 default ()             -- Double isn't available yet
 
+#if !defined(__HUGS__) && !defined(__NHC__)
 data (,) a b = (,) a b deriving (Eq, Ord)
 data (,,) a b c = (,,) a b c deriving (Eq, Ord)
 data (,,,) a b c d = (,,,) a b c d deriving (Eq, Ord)
@@ -210,12 +252,12 @@ data (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,
 data (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_ d_ e_ f_ g_ h_ i_ j_ k_ l_ m_ n_ o_ p_ q_ r_ s_ t_ u_ v_ w_ x_ y_ z_ a__ b__ c__ d__ e__ f__ g__ h__ i__ j__ k__ l__ m__ n__ o__ p__ q__ r__ s__ t__ u__ v__ w__ x__ y__ z__ a___ b___ c___ d___ e___ f___ g___ h___ i___ j___ k___ l___ m___ n___ o___ p___ q___ r___ s___ t___  u___ v___
  = (,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,) a b c d e f g h i j k l m n o p q r s t u v w x y z a_ b_ c_ d_ e_ f_ g_ h_ i_ j_ k_ l_ m_ n_ o_ p_ q_ r_ s_ t_ u_ v_ w_ x_ y_ z_ a__ b__ c__ d__ e__ f__ g__ h__ i__ j__ k__ l__ m__ n__ o__ p__ q__ r__ s__ t__ u__ v__ w__ x__ y__ z__ a___ b___ c___ d___ e___ f___ g___ h___ i___ j___ k___ l___ m___ n___ o___ p___ q___ r___ s___ t___ u___ v___
 -}
-#endif  /* __GLASGOW_HASKELL__ */
+#endif  /* neither __HUGS__  nor __NHC__ */
 
 -- ---------------------------------------------------------------------------
 -- Standard functions over tuples
 
-#ifndef __HUGS__
+#if !defined(__HUGS__) && !defined(__NHC__)
 fst                    :: (a,b) -> a
 fst (x,_)              =  x
 
@@ -229,4 +271,4 @@ curry f x y             =  f (x, y)
 
 uncurry                 :: (a -> b -> c) -> ((a, b) -> c)
 uncurry f p             =  f (fst p) (snd p)
-#endif  /* __HUGS__ */
+#endif  /* neither __HUGS__ nor __NHC__ */
index 3bcc8a7..23a1b57 100644 (file)
@@ -33,6 +33,11 @@ import GHC.Word
 import Hugs.Word
 #endif
 
+#ifdef __NHC__
+import NHC.FFI (Word8, Word16, Word32, Word64)
+type Word = Word32
+#endif
+
 {- $notes
 
 * All arithmetic is performed modulo 2^n, where n is the number of