diff options
author | David Terei <davidterei@gmail.com> | 2011-10-25 20:43:23 -0700 |
---|---|---|
committer | David Terei <davidterei@gmail.com> | 2011-10-25 21:40:50 -0700 |
commit | 378dd2968d07b3780a2944bf91e3228671b51868 (patch) | |
tree | 1ee340dc24967b112afb7d7bf2a065d3b2753238 | |
parent | c9dceb6d3b3ac855d97db8957dcf181658eaf7ae (diff) | |
download | haskell-378dd2968d07b3780a2944bf91e3228671b51868.tar.gz |
Update base for latest Safe Haskell.
130 files changed, 231 insertions, 80 deletions
diff --git a/libraries/base/Control/Monad/Group.hs b/libraries/base/Control/Monad/Group.hs index 3516562814..a3c36a268b 100644 --- a/libraries/base/Control/Monad/Group.hs +++ b/libraries/base/Control/Monad/Group.hs @@ -1,4 +1,5 @@ {-# LANGUAGE Trustworthy #-} + ----------------------------------------------------------------------------- -- | -- Module : Control.Monad.Group @@ -32,3 +33,4 @@ class Monad m => MonadGroup m t where instance Ord t => MonadGroup [] t where mgroupWith = groupWith #endif + diff --git a/libraries/base/Control/Monad/Instances.hs b/libraries/base/Control/Monad/Instances.hs index 0cc1c53b06..3849e3b7bd 100644 --- a/libraries/base/Control/Monad/Instances.hs +++ b/libraries/base/Control/Monad/Instances.hs @@ -2,6 +2,7 @@ {-# OPTIONS_NHC98 --prelude #-} -- This module deliberately declares orphan instances: {-# OPTIONS_GHC -fno-warn-orphans #-} + ----------------------------------------------------------------------------- -- | -- Module : Control.Monad.Instances @@ -37,3 +38,4 @@ instance Monad (Either e) where return = Right Left l >>= _ = Left l Right r >>= k = k r + diff --git a/libraries/base/Control/Monad/ST.hs b/libraries/base/Control/Monad/ST.hs index 305e88f100..ca0ceb2d46 100644 --- a/libraries/base/Control/Monad/ST.hs +++ b/libraries/base/Control/Monad/ST.hs @@ -1,9 +1,4 @@ -{-# LANGUAGE CPP #-} -#if sh_SAFE_DEFAULT -{-# LANGUAGE Safe #-} -#else {-# LANGUAGE Unsafe #-} -#endif ----------------------------------------------------------------------------- -- | @@ -22,18 +17,22 @@ ----------------------------------------------------------------------------- module Control.Monad.ST ( - module Control.Monad.ST.Safe -#if !sh_SAFE_DEFAULT + -- * The 'ST' Monad + ST, -- abstract, instance of Functor, Monad, Typeable. + runST, -- :: (forall s. ST s a) -> a + fixST, -- :: (a -> ST s a) -> ST s a + + -- * Converting 'ST' to 'IO' + RealWorld, -- abstract + stToIO, -- :: ST RealWorld a -> IO a + -- * Unsafe Functions - , unsafeInterleaveST - , unsafeIOToST - , unsafeSTToIO -#endif + unsafeInterleaveST, + unsafeIOToST, + unsafeSTToIO ) where import Control.Monad.ST.Safe - -#if !sh_SAFE_DEFAULT import qualified Control.Monad.ST.Unsafe as U {-# DEPRECATED unsafeInterleaveST, unsafeIOToST, unsafeSTToIO @@ -51,5 +50,4 @@ unsafeIOToST = U.unsafeIOToST {-# INLINE unsafeSTToIO #-} unsafeSTToIO :: ST s a -> IO a unsafeSTToIO = U.unsafeSTToIO -#endif diff --git a/libraries/base/Control/Monad/ST/Lazy.hs b/libraries/base/Control/Monad/ST/Lazy.hs index e976ad5c1f..400addd696 100644 --- a/libraries/base/Control/Monad/ST/Lazy.hs +++ b/libraries/base/Control/Monad/ST/Lazy.hs @@ -1,9 +1,4 @@ -{-# LANGUAGE CPP #-} -#if sh_SAFE_DEFAULT -{-# LANGUAGE Safe #-} -#else {-# LANGUAGE Unsafe #-} -#endif ----------------------------------------------------------------------------- -- | @@ -22,16 +17,24 @@ ----------------------------------------------------------------------------- module Control.Monad.ST.Lazy ( - module Control.Monad.ST.Lazy.Safe -#if !sh_SAFE_DEFAULT + -- * The 'ST' monad + ST, + runST, + fixST, + + -- * Converting between strict and lazy 'ST' + strictToLazyST, lazyToStrictST, + + -- * Converting 'ST' To 'IO' + RealWorld, + stToIO, + -- * Unsafe Functions - , unsafeInterleaveST - , unsafeIOToST -#endif + unsafeInterleaveST, + unsafeIOToST ) where import Control.Monad.ST.Lazy.Safe -#if !sh_SAFE_DEFAULT import qualified Control.Monad.ST.Lazy.Unsafe as U {-# DEPRECATED unsafeInterleaveST, unsafeIOToST @@ -45,5 +48,4 @@ unsafeInterleaveST = U.unsafeInterleaveST {-# INLINE unsafeIOToST #-} unsafeIOToST :: IO a -> ST s a unsafeIOToST = U.unsafeIOToST -#endif diff --git a/libraries/base/Control/Monad/ST/Lazy/Imp.hs b/libraries/base/Control/Monad/ST/Lazy/Imp.hs index f311eb84f8..280723c95f 100644 --- a/libraries/base/Control/Monad/ST/Lazy/Imp.hs +++ b/libraries/base/Control/Monad/ST/Lazy/Imp.hs @@ -160,4 +160,3 @@ unsafeInterleaveST = strictToLazyST . ST.unsafeInterleaveST . lazyToStrictST unsafeIOToST :: IO a -> ST s a unsafeIOToST = strictToLazyST . ST.unsafeIOToST - diff --git a/libraries/base/Control/Monad/ST/Lazy/Unsafe.hs b/libraries/base/Control/Monad/ST/Lazy/Unsafe.hs index d46282824b..4a1b8c79a6 100644 --- a/libraries/base/Control/Monad/ST/Lazy/Unsafe.hs +++ b/libraries/base/Control/Monad/ST/Lazy/Unsafe.hs @@ -1,4 +1,5 @@ {-# LANGUAGE Unsafe #-} + ----------------------------------------------------------------------------- -- | -- Module : Control.Monad.ST.Lazy.Unsafe diff --git a/libraries/base/Control/Monad/ST/Strict.hs b/libraries/base/Control/Monad/ST/Strict.hs index df5c12191a..4e474d95ae 100644 --- a/libraries/base/Control/Monad/ST/Strict.hs +++ b/libraries/base/Control/Monad/ST/Strict.hs @@ -1,9 +1,3 @@ -{-# LANGUAGE CPP #-} -#if sh_SAFE_DEFAULT -{-# LANGUAGE Safe #-} -#else -{-# LANGUAGE Unsafe #-} -#endif ----------------------------------------------------------------------------- -- | -- Module : Control.Monad.ST.Strict @@ -22,9 +16,5 @@ module Control.Monad.ST.Strict ( module Control.Monad.ST ) where -#if sh_SAFE_DEFAULT -import safe Control.Monad.ST -#else import Control.Monad.ST -#endif diff --git a/libraries/base/Control/Monad/ST/Unsafe.hs b/libraries/base/Control/Monad/ST/Unsafe.hs index 6d730b0159..9fa4b739b1 100644 --- a/libraries/base/Control/Monad/ST/Unsafe.hs +++ b/libraries/base/Control/Monad/ST/Unsafe.hs @@ -1,4 +1,5 @@ {-# LANGUAGE Unsafe #-} + ----------------------------------------------------------------------------- -- | -- Module : Control.Monad.ST.Unsafe diff --git a/libraries/base/Control/Monad/Zip.hs b/libraries/base/Control/Monad/Zip.hs index bbc04ecd68..824e373f73 100644 --- a/libraries/base/Control/Monad/Zip.hs +++ b/libraries/base/Control/Monad/Zip.hs @@ -1,4 +1,5 @@ {-# LANGUAGE Safe #-} + ----------------------------------------------------------------------------- -- | -- Module : Control.Monad.Zip @@ -51,3 +52,4 @@ instance MonadZip [] where mzip = zip mzipWith = zipWith munzip = unzip + diff --git a/libraries/base/Data/Bits.hs b/libraries/base/Data/Bits.hs index 22a6e41a58..b14585498b 100644 --- a/libraries/base/Data/Bits.hs +++ b/libraries/base/Data/Bits.hs @@ -380,5 +380,4 @@ own to enable constant folding; for example 'shift': 10000000 -> ww_sOb } -} - diff --git a/libraries/base/Data/Bool.hs b/libraries/base/Data/Bool.hs index 8d80ec849d..1f53177aef 100644 --- a/libraries/base/Data/Bool.hs +++ b/libraries/base/Data/Bool.hs @@ -39,3 +39,4 @@ import Prelude , otherwise ) #endif + diff --git a/libraries/base/Data/Char.hs b/libraries/base/Data/Char.hs index f45f3696ca..e1afc44596 100644 --- a/libraries/base/Data/Char.hs +++ b/libraries/base/Data/Char.hs @@ -209,3 +209,4 @@ isSeparator c = case generalCategory c of toTitle :: Char -> Char toTitle = toUpper #endif + diff --git a/libraries/base/Data/Complex.hs b/libraries/base/Data/Complex.hs index b456055ee9..d78a6c9871 100644 --- a/libraries/base/Data/Complex.hs +++ b/libraries/base/Data/Complex.hs @@ -205,3 +205,4 @@ instance (RealFloat a) => Floating (Complex a) where asinh z = log (z + sqrt (1+z*z)) acosh z = log (z + (z+1) * sqrt ((z-1)/(z+1))) atanh z = 0.5 * log ((1.0+z) / (1.0-z)) + diff --git a/libraries/base/Data/Data.hs b/libraries/base/Data/Data.hs index 5de1eaff41..cd401675a4 100644 --- a/libraries/base/Data/Data.hs +++ b/libraries/base/Data/Data.hs @@ -23,7 +23,6 @@ -- For more information, please visit the new -- SYB wiki: <http://www.cs.uu.nl/wiki/bin/view/GenericProgramming/SYB>. -- --- ----------------------------------------------------------------------------- module Data.Data ( diff --git a/libraries/base/Data/Dynamic.hs b/libraries/base/Data/Dynamic.hs index b3f935080c..11501b8c98 100644 --- a/libraries/base/Data/Dynamic.hs +++ b/libraries/base/Data/Dynamic.hs @@ -168,3 +168,4 @@ dynApp f x = case dynApply f x of dynTypeRep :: Dynamic -> TypeRep dynTypeRep (Dynamic tr _) = tr + diff --git a/libraries/base/Data/Eq.hs b/libraries/base/Data/Eq.hs index 9386d60fec..0c45c78e1d 100644 --- a/libraries/base/Data/Eq.hs +++ b/libraries/base/Data/Eq.hs @@ -22,3 +22,4 @@ module Data.Eq ( #if __GLASGOW_HASKELL__ import GHC.Base #endif + diff --git a/libraries/base/Data/Fixed.hs b/libraries/base/Data/Fixed.hs index b1d7113c14..81e7c038b0 100644 --- a/libraries/base/Data/Fixed.hs +++ b/libraries/base/Data/Fixed.hs @@ -1,10 +1,10 @@ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE CPP #-} {-# OPTIONS -Wall -fno-warn-unused-binds #-} - #ifndef __NHC__ {-# LANGUAGE DeriveDataTypeable #-} #endif + ----------------------------------------------------------------------------- -- | -- Module : Data.Fixed @@ -246,3 +246,4 @@ instance HasResolution E12 where resolution _ = 1000000000000 -- | resolution of 10^-12 = .000000000001 type Pico = Fixed E12 + diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs index a925fca9d6..01ef297300 100644 --- a/libraries/base/Data/Foldable.hs +++ b/libraries/base/Data/Foldable.hs @@ -18,6 +18,8 @@ -- functor. To avoid ambiguity, either import those modules hiding -- these names or qualify uses of these function names with an alias -- for this module. +-- +----------------------------------------------------------------------------- module Data.Foldable ( -- * Folds @@ -320,3 +322,4 @@ notElem x = not . elem x -- 'Nothing' if there is no such element. find :: Foldable t => (a -> Bool) -> t a -> Maybe a find p = listToMaybe . concatMap (\ x -> if p x then [x] else []) + diff --git a/libraries/base/Data/Function.hs b/libraries/base/Data/Function.hs index ef6d9cf589..54eabbb6e7 100644 --- a/libraries/base/Data/Function.hs +++ b/libraries/base/Data/Function.hs @@ -1,4 +1,5 @@ {-# LANGUAGE Safe #-} + ----------------------------------------------------------------------------- -- | -- Module : Data.Function @@ -10,6 +11,8 @@ -- Portability : portable -- -- Simple combinators working solely on and with functions. +-- +----------------------------------------------------------------------------- module Data.Function ( -- * "Prelude" re-exports @@ -82,3 +85,4 @@ fix f = let x = f x in x on :: (b -> b -> c) -> (a -> b) -> a -> a -> c (.*.) `on` f = \x y -> f x .*. f y + diff --git a/libraries/base/Data/Functor.hs b/libraries/base/Data/Functor.hs index 2369cdb497..416768e325 100644 --- a/libraries/base/Data/Functor.hs +++ b/libraries/base/Data/Functor.hs @@ -33,3 +33,4 @@ infixl 4 <$> -- | An infix synonym for 'fmap'. (<$>) :: Functor f => (a -> b) -> f a -> f b (<$>) = fmap + diff --git a/libraries/base/Data/HashTable.hs b/libraries/base/Data/HashTable.hs index 9fe78991d7..b59486390c 100644 --- a/libraries/base/Data/HashTable.hs +++ b/libraries/base/Data/HashTable.hs @@ -531,3 +531,4 @@ longestChain = mapReduce id (maximumBy lengthCmp) lengthCmp [] [] = EQ lengthCmp [] _ = LT lengthCmp _ [] = GT + diff --git a/libraries/base/Data/IORef.hs b/libraries/base/Data/IORef.hs index 13eb9c9a48..1a3ddfd2df 100644 --- a/libraries/base/Data/IORef.hs +++ b/libraries/base/Data/IORef.hs @@ -138,3 +138,4 @@ atomicModifyIORef r f = 'IORef' operations. -} + diff --git a/libraries/base/Data/Int.hs b/libraries/base/Data/Int.hs index 1ff37bd51c..084bb0ef05 100644 --- a/libraries/base/Data/Int.hs +++ b/libraries/base/Data/Int.hs @@ -65,3 +65,4 @@ import NHC.SizedTypes (Int8, Int16, Int32, Int64) -- instances of Bits count to the width of the type, for example @1 \<\< 32 == 1@ in some C implementations. -} + diff --git a/libraries/base/Data/Ix.hs b/libraries/base/Data/Ix.hs index f1edf00907..fdfc33a1cd 100644 --- a/libraries/base/Data/Ix.hs +++ b/libraries/base/Data/Ix.hs @@ -16,6 +16,7 @@ -- (see the array package). -- ----------------------------------------------------------------------------- + module Data.Ix ( -- * The 'Ix' class diff --git a/libraries/base/Data/List.hs b/libraries/base/Data/List.hs index 4f76c83c22..4edd9ebde8 100644 --- a/libraries/base/Data/List.hs +++ b/libraries/base/Data/List.hs @@ -1105,3 +1105,4 @@ errorEmptyList fun = error ("Prelude." ++ fun ++ ": empty list") #endif /* !__GLASGOW_HASKELL__ */ + diff --git a/libraries/base/Data/Maybe.hs b/libraries/base/Data/Maybe.hs index a405bb4625..135040228c 100644 --- a/libraries/base/Data/Maybe.hs +++ b/libraries/base/Data/Maybe.hs @@ -149,3 +149,4 @@ mapMaybe f (x:xs) = Just r -> r:rs #endif /* else not __NHC__ */ + diff --git a/libraries/base/Data/Monoid.hs b/libraries/base/Data/Monoid.hs index beac4f70f7..228e25433e 100644 --- a/libraries/base/Data/Monoid.hs +++ b/libraries/base/Data/Monoid.hs @@ -14,6 +14,7 @@ -- -- A class for monoids (types with an associative binary operation that -- has an identity) with various general-purpose instances. +-- ----------------------------------------------------------------------------- module Data.Monoid ( @@ -276,3 +277,4 @@ prop_mconcatLast x = where listLastToMaybe [] = Nothing listLastToMaybe lst = Just (last lst) -- -} + diff --git a/libraries/base/Data/Ord.hs b/libraries/base/Data/Ord.hs index 250e797d2c..8180df23e6 100644 --- a/libraries/base/Data/Ord.hs +++ b/libraries/base/Data/Ord.hs @@ -34,3 +34,4 @@ import GHC.Base -- > ... sortBy (comparing fst) ... comparing :: (Ord a) => (b -> a) -> b -> b -> Ordering comparing p x y = compare (p x) (p y) + diff --git a/libraries/base/Data/Ratio.hs b/libraries/base/Data/Ratio.hs index 766fe41e82..d3d29c8bb9 100644 --- a/libraries/base/Data/Ratio.hs +++ b/libraries/base/Data/Ratio.hs @@ -95,3 +95,4 @@ approxRational rat eps = simplest (rat-eps) (rat+eps) n'' = numerator nd'' d'' = denominator nd'' #endif + diff --git a/libraries/base/Data/STRef.hs b/libraries/base/Data/STRef.hs index 851a20f9fc..c628bb6618 100644 --- a/libraries/base/Data/STRef.hs +++ b/libraries/base/Data/STRef.hs @@ -42,3 +42,4 @@ INSTANCE_TYPEABLE2(STRef,stRefTc,"STRef") -- |Mutate the contents of an 'STRef' modifySTRef :: STRef s a -> (a -> a) -> ST s () modifySTRef ref f = writeSTRef ref . f =<< readSTRef ref + diff --git a/libraries/base/Data/STRef/Lazy.hs b/libraries/base/Data/STRef/Lazy.hs index ccc19051de..7c9a74e9b5 100644 --- a/libraries/base/Data/STRef/Lazy.hs +++ b/libraries/base/Data/STRef/Lazy.hs @@ -1,4 +1,5 @@ {-# LANGUAGE Safe #-} + ----------------------------------------------------------------------------- -- | -- Module : Data.STRef.Lazy @@ -12,6 +13,7 @@ -- Mutable references in the lazy ST monad. -- ----------------------------------------------------------------------------- + module Data.STRef.Lazy ( -- * STRefs ST.STRef, -- abstract, instance Eq @@ -30,7 +32,8 @@ readSTRef :: ST.STRef s a -> ST s a writeSTRef :: ST.STRef s a -> a -> ST s () modifySTRef :: ST.STRef s a -> (a -> a) -> ST s () -newSTRef = strictToLazyST . ST.newSTRef -readSTRef = strictToLazyST . ST.readSTRef -writeSTRef r a = strictToLazyST (ST.writeSTRef r a) +newSTRef = strictToLazyST . ST.newSTRef +readSTRef = strictToLazyST . ST.readSTRef +writeSTRef r a = strictToLazyST (ST.writeSTRef r a) modifySTRef r f = strictToLazyST (ST.modifySTRef r f) + diff --git a/libraries/base/Data/STRef/Strict.hs b/libraries/base/Data/STRef/Strict.hs index 202df73450..ead6683f8a 100644 --- a/libraries/base/Data/STRef/Strict.hs +++ b/libraries/base/Data/STRef/Strict.hs @@ -1,4 +1,5 @@ {-# LANGUAGE Safe #-} + ----------------------------------------------------------------------------- -- | -- Module : Data.STRef.Strict @@ -18,3 +19,4 @@ module Data.STRef.Strict ( ) where import Data.STRef + diff --git a/libraries/base/Data/String.hs b/libraries/base/Data/String.hs index 27d61d5991..0124f13ab0 100644 --- a/libraries/base/Data/String.hs +++ b/libraries/base/Data/String.hs @@ -41,3 +41,4 @@ class IsString a where instance IsString [Char] where fromString xs = xs #endif + diff --git a/libraries/base/Data/Traversable.hs b/libraries/base/Data/Traversable.hs index 96ea010d8b..75356ec55a 100644 --- a/libraries/base/Data/Traversable.hs +++ b/libraries/base/Data/Traversable.hs @@ -29,6 +29,8 @@ -- functions of the same names from lists to any 'Traversable' functor. -- To avoid ambiguity, either import the "Prelude" hiding these names -- or qualify uses of these function names with an alias for this module. +-- +----------------------------------------------------------------------------- module Data.Traversable ( Traversable(..), @@ -194,3 +196,4 @@ instance Functor Id where instance Applicative Id where pure = Id Id f <*> Id x = Id (f x) + diff --git a/libraries/base/Data/Tuple.hs b/libraries/base/Data/Tuple.hs index 0029fb976f..30f93c5e63 100644 --- a/libraries/base/Data/Tuple.hs +++ b/libraries/base/Data/Tuple.hs @@ -2,6 +2,7 @@ {-# LANGUAGE CPP, NoImplicitPrelude #-} {-# OPTIONS_GHC -fno-warn-unused-imports #-} -- XXX -fno-warn-unused-imports needed for the GHC.Tuple import below. Sigh. + ----------------------------------------------------------------------------- -- | -- Module : Data.Tuple diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 16b303d68c..93218a87f1 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -1,4 +1,5 @@ {-# LANGUAGE Unsafe #-} + ----------------------------------------------------------------------------- -- | -- Module : Data.Typeable.Internal diff --git a/libraries/base/Data/Typeable/Internal.hs-boot b/libraries/base/Data/Typeable/Internal.hs-boot index f314abe570..c83c77e1a0 100644 --- a/libraries/base/Data/Typeable/Internal.hs-boot +++ b/libraries/base/Data/Typeable/Internal.hs-boot @@ -1,5 +1,6 @@ {-# LANGUAGE Unsafe #-} {-# LANGUAGE CPP, NoImplicitPrelude, MagicHash #-} + module Data.Typeable.Internal ( Typeable(typeOf), TypeRep, diff --git a/libraries/base/Data/Word.hs b/libraries/base/Data/Word.hs index 1540999df4..84a4d0721c 100644 --- a/libraries/base/Data/Word.hs +++ b/libraries/base/Data/Word.hs @@ -68,3 +68,4 @@ type Word = Word32 truncate the shift count to the width of the type, for example @1 \<\< 32 == 1@ in some C implementations. -} + diff --git a/libraries/base/Debug/Trace.hs b/libraries/base/Debug/Trace.hs index 728b938887..8242b15471 100644 --- a/libraries/base/Debug/Trace.hs +++ b/libraries/base/Debug/Trace.hs @@ -71,3 +71,4 @@ Like 'trace', but uses 'show' on the argument to convert it to a 'String'. -} traceShow :: (Show a) => a -> b -> b traceShow = trace . show + diff --git a/libraries/base/Foreign.hs b/libraries/base/Foreign.hs index 5896b1e76a..fc32835d56 100644 --- a/libraries/base/Foreign.hs +++ b/libraries/base/Foreign.hs @@ -1,8 +1,4 @@ -#if sh_SAFE_DEFAULT -{-# LANGUAGE Trustworthy #-} -#else {-# LANGUAGE Unsafe #-} -#endif {-# LANGUAGE NoImplicitPrelude #-} ----------------------------------------------------------------------------- @@ -30,7 +26,6 @@ module Foreign , module Foreign.Storable , module Foreign.Marshal -#if !sh_SAFE_DEFAULT -- * Unsafe Functions -- | 'unsafePerformIO' is exported here for backwards @@ -38,7 +33,6 @@ module Foreign -- the FFI, use 'unsafeLocalState'. For other uses, see -- 'System.IO.Unsafe.unsafePerformIO'. , unsafePerformIO -#endif ) where import Data.Bits @@ -50,7 +44,6 @@ import Foreign.StablePtr import Foreign.Storable import Foreign.Marshal -#if !sh_SAFE_DEFAULT import GHC.IO (IO) import qualified System.IO.Unsafe (unsafePerformIO) @@ -59,5 +52,4 @@ import qualified System.IO.Unsafe (unsafePerformIO) {-# INLINE unsafePerformIO #-} unsafePerformIO :: IO a -> a unsafePerformIO = System.IO.Unsafe.unsafePerformIO -#endif diff --git a/libraries/base/Foreign/C.hs b/libraries/base/Foreign/C.hs index 2e925ccc04..83ab6b883a 100644 --- a/libraries/base/Foreign/C.hs +++ b/libraries/base/Foreign/C.hs @@ -24,3 +24,4 @@ module Foreign.C import Foreign.C.Types import Foreign.C.String import Foreign.C.Error + diff --git a/libraries/base/Foreign/C/Error.hs b/libraries/base/Foreign/C/Error.hs index 76ebe272ce..020f08e6a4 100644 --- a/libraries/base/Foreign/C/Error.hs +++ b/libraries/base/Foreign/C/Error.hs @@ -616,3 +616,4 @@ errnoToIOError loc errno maybeHdl maybeName = unsafePerformIO $ do #endif foreign import ccall unsafe "string.h" strerror :: Errno -> IO (Ptr CChar) + diff --git a/libraries/base/Foreign/C/String.hs b/libraries/base/Foreign/C/String.hs index 09dd27aca5..7582752605 100644 --- a/libraries/base/Foreign/C/String.hs +++ b/libraries/base/Foreign/C/String.hs @@ -541,3 +541,4 @@ castCharToCWchar :: Char -> CWchar castCharToCWchar ch = fromIntegral (ord ch) #endif /* !mingw32_HOST_OS */ + diff --git a/libraries/base/Foreign/C/Types.hs b/libraries/base/Foreign/C/Types.hs index fb53b52721..9da95a9605 100644 --- a/libraries/base/Foreign/C/Types.hs +++ b/libraries/base/Foreign/C/Types.hs @@ -331,3 +331,4 @@ INSTANCE_BITS(CIntMax) INSTANCE_BITS(CUIntMax) #endif + diff --git a/libraries/base/Foreign/ForeignPtr.hs b/libraries/base/Foreign/ForeignPtr.hs index 43d3dbd9eb..5288ce7718 100644 --- a/libraries/base/Foreign/ForeignPtr.hs +++ b/libraries/base/Foreign/ForeignPtr.hs @@ -1,9 +1,5 @@ -{-# LANGUAGE CPP, NoImplicitPrelude #-} -#if sh_SAFE_DEFAULT -{-# LANGUAGE Trustworthy #-} -#else {-# LANGUAGE Unsafe #-} -#endif +{-# LANGUAGE CPP, NoImplicitPrelude #-} {-# OPTIONS_HADDOCK hide #-} ----------------------------------------------------------------------------- @@ -23,16 +19,41 @@ ----------------------------------------------------------------------------- module Foreign.ForeignPtr ( - module Foreign.ForeignPtr.Safe -#if !sh_SAFE_DEFAULT + -- * Finalised data pointers + ForeignPtr + , FinalizerPtr +#if defined(__HUGS__) || defined(__GLASGOW_HASKELL__) + , FinalizerEnvPtr +#endif + -- ** Basic operations + , newForeignPtr + , newForeignPtr_ + , addForeignPtrFinalizer +#if defined(__HUGS__) || defined(__GLASGOW_HASKELL__) + , newForeignPtrEnv + , addForeignPtrFinalizerEnv +#endif + , withForeignPtr + +#ifdef __GLASGOW_HASKELL__ + , finalizeForeignPtr +#endif + + -- ** Low-level operations + , touchForeignPtr + , castForeignPtr + + -- ** Allocating managed memory + , mallocForeignPtr + , mallocForeignPtrBytes + , mallocForeignPtrArray + , mallocForeignPtrArray0 -- ** Unsafe low-level operations , unsafeForeignPtrToPtr -#endif ) where import Foreign.ForeignPtr.Safe -#if !sh_SAFE_DEFAULT import Foreign.Ptr ( Ptr ) import qualified Foreign.ForeignPtr.Unsafe as U @@ -40,5 +61,4 @@ import qualified Foreign.ForeignPtr.Unsafe as U {-# INLINE unsafeForeignPtrToPtr #-} unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr a unsafeForeignPtrToPtr = U.unsafeForeignPtrToPtr -#endif diff --git a/libraries/base/Foreign/ForeignPtr/Imp.hs b/libraries/base/Foreign/ForeignPtr/Imp.hs index a1a321c963..336f0321b1 100644 --- a/libraries/base/Foreign/ForeignPtr/Imp.hs +++ b/libraries/base/Foreign/ForeignPtr/Imp.hs @@ -179,3 +179,4 @@ mallocForeignPtrArray = doMalloc undefined -- the block of memory was allocated by 'Foreign.Marshal.Alloc.malloc'. mallocForeignPtrArray0 :: Storable a => Int -> IO (ForeignPtr a) mallocForeignPtrArray0 size = mallocForeignPtrArray (size + 1) + diff --git a/libraries/base/Foreign/Marshal/Alloc.hs b/libraries/base/Foreign/Marshal/Alloc.hs index e404580882..515af4a83b 100644 --- a/libraries/base/Foreign/Marshal/Alloc.hs +++ b/libraries/base/Foreign/Marshal/Alloc.hs @@ -245,3 +245,4 @@ foreign import ccall unsafe "stdlib.h free" _free :: Ptr a -> IO () -- used as a finalizer (cf 'Foreign.ForeignPtr.ForeignPtr') for storage -- allocated with 'malloc', 'mallocBytes', 'realloc' or 'reallocBytes'. foreign import ccall unsafe "stdlib.h &free" finalizerFree :: FinalizerPtr a + diff --git a/libraries/base/Foreign/Marshal/Array.hs b/libraries/base/Foreign/Marshal/Array.hs index e284ec47bb..04825aa22d 100644 --- a/libraries/base/Foreign/Marshal/Array.hs +++ b/libraries/base/Foreign/Marshal/Array.hs @@ -277,3 +277,4 @@ advancePtr = doAdvance undefined where doAdvance :: Storable a' => a' -> Ptr a' -> Int -> Ptr a' doAdvance dummy ptr i = ptr `plusPtr` (i * sizeOf dummy) + diff --git a/libraries/base/Foreign/Marshal/Error.hs b/libraries/base/Foreign/Marshal/Error.hs index 9e3ad3b5ba..5fe9a7ea42 100644 --- a/libraries/base/Foreign/Marshal/Error.hs +++ b/libraries/base/Foreign/Marshal/Error.hs @@ -83,3 +83,4 @@ throwIfNull = throwIf (== nullPtr) . const -- void :: IO a -> IO () void act = act >> return () + diff --git a/libraries/base/Foreign/Marshal/Pool.hs b/libraries/base/Foreign/Marshal/Pool.hs index 8ca160d990..6953c0b285 100644 --- a/libraries/base/Foreign/Marshal/Pool.hs +++ b/libraries/base/Foreign/Marshal/Pool.hs @@ -209,3 +209,4 @@ pooledNewArray0 pool marker vals = do ptr <- pooledMallocArray0 pool (length vals) pokeArray0 marker ptr vals return ptr + diff --git a/libraries/base/Foreign/Marshal/Utils.hs b/libraries/base/Foreign/Marshal/Utils.hs index 7fec1bf4ec..c9e1fd6e4d 100644 --- a/libraries/base/Foreign/Marshal/Utils.hs +++ b/libraries/base/Foreign/Marshal/Utils.hs @@ -178,3 +178,4 @@ moveBytes dest src size = do _ <- memmove dest src (fromIntegral size) -- foreign import ccall unsafe "string.h" memcpy :: Ptr a -> Ptr a -> CSize -> IO (Ptr a) foreign import ccall unsafe "string.h" memmove :: Ptr a -> Ptr a -> CSize -> IO (Ptr a) + diff --git a/libraries/base/Foreign/Ptr.hs b/libraries/base/Foreign/Ptr.hs index d6588f5dee..56a369241a 100644 --- a/libraries/base/Foreign/Ptr.hs +++ b/libraries/base/Foreign/Ptr.hs @@ -162,3 +162,4 @@ foreign import ccall unsafe "__hscore_from_intptr" # endif /* !__GLASGOW_HASKELL__ */ #endif /* !__NHC_ */ + diff --git a/libraries/base/Foreign/StablePtr.hs b/libraries/base/Foreign/StablePtr.hs index 68b205694f..d0b6625e50 100644 --- a/libraries/base/Foreign/StablePtr.hs +++ b/libraries/base/Foreign/StablePtr.hs @@ -61,3 +61,4 @@ import NHC.FFI -- guarantee provided is that if they are passed back to Haskell land, the -- function 'deRefStablePtr' will be able to reconstruct the -- Haskell value referred to by the stable pointer. + diff --git a/libraries/base/Foreign/Storable.hs b/libraries/base/Foreign/Storable.hs index 62c1151e24..9ba6bb9630 100644 --- a/libraries/base/Foreign/Storable.hs +++ b/libraries/base/Foreign/Storable.hs @@ -284,3 +284,4 @@ pokeFingerprint p0 (Fingerprint high low) = do pokeW64 (castPtr p0) 8 high pokeW64 (castPtr p0 `plusPtr` 8) 8 low #endif + diff --git a/libraries/base/GHC/Conc/IO.hs b/libraries/base/GHC/Conc/IO.hs index dc205cc98c..64a479e7c1 100644 --- a/libraries/base/GHC/Conc/IO.hs +++ b/libraries/base/GHC/Conc/IO.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE Unsafe #-} +{-# LANGUAGE Trustworthy #-} {-# LANGUAGE CPP , NoImplicitPrelude , MagicHash diff --git a/libraries/base/GHC/Conc/Windows.hs b/libraries/base/GHC/Conc/Windows.hs index be28bc679c..6ea147ceec 100644 --- a/libraries/base/GHC/Conc/Windows.hs +++ b/libraries/base/GHC/Conc/Windows.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE Unsafe #-} +{-# LANGUAGE Trustworthy #-} {-# LANGUAGE NoImplicitPrelude, MagicHash, UnboxedTuples, ForeignFunctionInterface, DeriveDataTypeable #-} {-# OPTIONS_GHC -fno-warn-missing-signatures #-} @@ -324,3 +324,4 @@ foreign import ccall unsafe "sendIOManagerEvent" -- in the RTS (ThrIOManager.c) foreign import stdcall "WaitForSingleObject" c_WaitForSingleObject :: HANDLE -> DWORD -> IO DWORD + diff --git a/libraries/base/GHC/Constants.hs b/libraries/base/GHC/Constants.hs index 99abba55cc..ca631848f8 100644 --- a/libraries/base/GHC/Constants.hs +++ b/libraries/base/GHC/Constants.hs @@ -9,3 +9,4 @@ import Prelude #include "../../../compiler/stage1/ghc_boot_platform.h" #include "../../../includes/HaskellConstants.hs" + diff --git a/libraries/base/GHC/Desugar.hs b/libraries/base/GHC/Desugar.hs index 3d1d740f2e..6a5562f7fe 100644 --- a/libraries/base/GHC/Desugar.hs +++ b/libraries/base/GHC/Desugar.hs @@ -41,3 +41,4 @@ data AnnotationWrapper = forall a. (Data a) => AnnotationWrapper a toAnnotationWrapper :: (Data a) => a -> AnnotationWrapper toAnnotationWrapper what = AnnotationWrapper what + diff --git a/libraries/base/GHC/Enum.lhs b/libraries/base/GHC/Enum.lhs index f99e20852f..b3491f2d9d 100644 --- a/libraries/base/GHC/Enum.lhs +++ b/libraries/base/GHC/Enum.lhs @@ -2,6 +2,7 @@ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE NoImplicitPrelude, BangPatterns, MagicHash #-} {-# OPTIONS_HADDOCK hide #-} + ----------------------------------------------------------------------------- -- | -- Module : GHC.Enum diff --git a/libraries/base/GHC/Event.hs b/libraries/base/GHC/Event.hs index 850e036a12..fd421dd153 100644 --- a/libraries/base/GHC/Event.hs +++ b/libraries/base/GHC/Event.hs @@ -1,8 +1,13 @@ {-# LANGUAGE Trustworthy #-} + +-- ---------------------------------------------------------------------------- -- | This module provides scalable event notification for file -- descriptors and timeouts. -- -- This module should be considered GHC internal. +-- +-- ---------------------------------------------------------------------------- + module GHC.Event ( -- * Types EventManager @@ -40,3 +45,4 @@ module GHC.Event import GHC.Event.Manager import GHC.Event.Thread (getSystemEventManager) + diff --git a/libraries/base/GHC/Event/Array.hs b/libraries/base/GHC/Event/Array.hs index 142414473f..5b811ef7a9 100644 --- a/libraries/base/GHC/Event/Array.hs +++ b/libraries/base/GHC/Event/Array.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE Unsafe #-} +{-# LANGUAGE Trustworthy #-} {-# LANGUAGE BangPatterns, CPP, ForeignFunctionInterface, NoImplicitPrelude #-} module GHC.Event.Array @@ -312,3 +312,4 @@ foreign import ccall unsafe "string.h memcpy" foreign import ccall unsafe "string.h memmove" memmove :: Ptr a -> Ptr a -> CSize -> IO (Ptr a) + diff --git a/libraries/base/GHC/Event/Clock.hsc b/libraries/base/GHC/Event/Clock.hsc index f306a67953..ac4480533c 100644 --- a/libraries/base/GHC/Event/Clock.hsc +++ b/libraries/base/GHC/Event/Clock.hsc @@ -1,4 +1,4 @@ -{-# LANGUAGE Unsafe #-} +{-# LANGUAGE Trustworthy #-} {-# LANGUAGE NoImplicitPrelude, BangPatterns, ForeignFunctionInterface #-} module GHC.Event.Clock (getCurrentTime) where @@ -47,3 +47,4 @@ instance Storable CTimeval where foreign import ccall unsafe "sys/time.h gettimeofday" gettimeofday :: Ptr CTimeval -> Ptr () -> IO CInt + diff --git a/libraries/base/GHC/Event/Control.hs b/libraries/base/GHC/Event/Control.hs index b86694ed8e..ab0636bb7b 100644 --- a/libraries/base/GHC/Event/Control.hs +++ b/libraries/base/GHC/Event/Control.hs @@ -213,3 +213,4 @@ foreign import ccall "setIOManagerControlFd" foreign import ccall "setIOManagerWakeupFd" c_setIOManagerWakeupFd :: CInt -> IO () + diff --git a/libraries/base/GHC/Event/EPoll.hsc b/libraries/base/GHC/Event/EPoll.hsc index 922ebf6252..dafb68f55e 100644 --- a/libraries/base/GHC/Event/EPoll.hsc +++ b/libraries/base/GHC/Event/EPoll.hsc @@ -1,4 +1,4 @@ -{-# LANGUAGE Unsafe #-} +{-# LANGUAGE Trustworthy #-} {-# LANGUAGE CPP , ForeignFunctionInterface , GeneralizedNewtypeDeriving @@ -6,8 +6,9 @@ , BangPatterns #-} --- --- | A binding to the epoll I/O event notification facility +----------------------------------------------------------------------------- +-- | +-- A binding to the epoll I/O event notification facility -- -- epoll is a variant of poll that can be used either as an edge-triggered or -- a level-triggered interface and scales well to large numbers of watched file @@ -15,6 +16,8 @@ -- -- epoll decouples monitor an fd from the process of registering it. -- +----------------------------------------------------------------------------- + module GHC.Event.EPoll ( new @@ -205,3 +208,4 @@ foreign import ccall safe "sys/epoll.h epoll_wait" c_epoll_wait :: CInt -> Ptr Event -> CInt -> CInt -> IO CInt #endif /* defined(HAVE_EPOLL) */ + diff --git a/libraries/base/GHC/Event/IntMap.hs b/libraries/base/GHC/Event/IntMap.hs index e85377910a..eee0cc5fa9 100644 --- a/libraries/base/GHC/Event/IntMap.hs +++ b/libraries/base/GHC/Event/IntMap.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE Unsafe #-} +{-# LANGUAGE Trustworthy #-} {-# LANGUAGE CPP, MagicHash, NoImplicitPrelude #-} ----------------------------------------------------------------------------- @@ -39,6 +39,7 @@ -- This means that the operation can become linear in the number of -- elements with a maximum of /W/ -- the number of bits in an 'Int' -- (32 or 64). +-- ----------------------------------------------------------------------------- module GHC.Event.IntMap @@ -374,3 +375,4 @@ highestBitMask x0 x4 -> case (x4 .|. shiftRL x4 16) of x5 -> case (x5 .|. shiftRL x5 32) of -- for 64 bit platforms x6 -> (x6 `xor` (shiftRL x6 1)) + diff --git a/libraries/base/GHC/Event/KQueue.hsc b/libraries/base/GHC/Event/KQueue.hsc index a10c3900b5..68aade3e39 100644 --- a/libraries/base/GHC/Event/KQueue.hsc +++ b/libraries/base/GHC/Event/KQueue.hsc @@ -1,4 +1,4 @@ -{-# LANGUAGE Unsafe #-} +{-# LANGUAGE Trustworthy #-} {-# LANGUAGE CPP , ForeignFunctionInterface , GeneralizedNewtypeDeriving @@ -299,3 +299,4 @@ foreign import ccall safe "kevent" #endif #endif /* defined(HAVE_KQUEUE) */ + diff --git a/libraries/base/GHC/Event/Manager.hs b/libraries/base/GHC/Event/Manager.hs index 1714104464..089532cafb 100644 --- a/libraries/base/GHC/Event/Manager.hs +++ b/libraries/base/GHC/Event/Manager.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE Unsafe #-} +{-# LANGUAGE Trustworthy #-} {-# LANGUAGE BangPatterns , CPP , ExistentialQuantification diff --git a/libraries/base/GHC/Event/PSQ.hs b/libraries/base/GHC/Event/PSQ.hs index 4e098e48c0..853958bc29 100644 --- a/libraries/base/GHC/Event/PSQ.hs +++ b/libraries/base/GHC/Event/PSQ.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE Unsafe #-} +{-# LANGUAGE Trustworthy #-} {-# LANGUAGE BangPatterns, NoImplicitPrelude #-} -- Copyright (c) 2008, Ralf Hinze @@ -482,3 +482,4 @@ seqToList (Sequ x) = x [] instance Show a => Show (Sequ a) where showsPrec d a = showsPrec d (seqToList a) + diff --git a/libraries/base/GHC/Event/Poll.hsc b/libraries/base/GHC/Event/Poll.hsc index fb9068225a..e62296b386 100644 --- a/libraries/base/GHC/Event/Poll.hsc +++ b/libraries/base/GHC/Event/Poll.hsc @@ -1,4 +1,4 @@ -{-# LANGUAGE Unsafe #-} +{-# LANGUAGE Trustworthy #-} {-# LANGUAGE CPP , ForeignFunctionInterface , GeneralizedNewtypeDeriving diff --git a/libraries/base/GHC/Event/Thread.hs b/libraries/base/GHC/Event/Thread.hs index 7649319db9..2643950b7d 100644 --- a/libraries/base/GHC/Event/Thread.hs +++ b/libraries/base/GHC/Event/Thread.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE Unsafe #-} +{-# LANGUAGE Trustworthy #-} {-# LANGUAGE BangPatterns, ForeignFunctionInterface, NoImplicitPrelude #-} module GHC.Event.Thread diff --git a/libraries/base/GHC/Event/Unique.hs b/libraries/base/GHC/Event/Unique.hs index 643251995e..9137450793 100644 --- a/libraries/base/GHC/Event/Unique.hs +++ b/libraries/base/GHC/Event/Unique.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE Unsafe #-} +{-# LANGUAGE Trustworthy #-} {-# LANGUAGE BangPatterns, GeneralizedNewtypeDeriving, NoImplicitPrelude #-} module GHC.Event.Unique ( @@ -39,3 +39,4 @@ newUnique (US ref) = atomically $ do writeTVar ref u' return $ Unique u' {-# INLINE newUnique #-} + diff --git a/libraries/base/GHC/Exception.lhs b/libraries/base/GHC/Exception.lhs index bffc35cd47..74f8fea3bc 100644 --- a/libraries/base/GHC/Exception.lhs +++ b/libraries/base/GHC/Exception.lhs @@ -6,6 +6,7 @@ , DeriveDataTypeable #-} {-# OPTIONS_HADDOCK hide #-} + ----------------------------------------------------------------------------- -- | -- Module : GHC.Exception diff --git a/libraries/base/GHC/Fingerprint.hs b/libraries/base/GHC/Fingerprint.hs index 1a05e52dff..d1b3831ccd 100644 --- a/libraries/base/GHC/Fingerprint.hs +++ b/libraries/base/GHC/Fingerprint.hs @@ -1,9 +1,10 @@ -{-# LANGUAGE Unsafe #-} +{-# LANGUAGE Trustworthy #-} {-# LANGUAGE NoImplicitPrelude , BangPatterns , ForeignFunctionInterface , EmptyDataDecls #-} + -- ---------------------------------------------------------------------------- -- -- (c) The University of Glasgow 2006 @@ -74,3 +75,4 @@ foreign import ccall unsafe "MD5Update" c_MD5Update :: Ptr MD5Context -> Ptr Word8 -> CInt -> IO () foreign import ccall unsafe "MD5Final" c_MD5Final :: Ptr Word8 -> Ptr MD5Context -> IO () + diff --git a/libraries/base/GHC/Fingerprint/Type.hs b/libraries/base/GHC/Fingerprint/Type.hs index 1730317daa..91d7250d49 100644 --- a/libraries/base/GHC/Fingerprint/Type.hs +++ b/libraries/base/GHC/Fingerprint/Type.hs @@ -18,3 +18,4 @@ import GHC.Word data Fingerprint = Fingerprint {-# UNPACK #-} !Word64 {-# UNPACK #-} !Word64 deriving (Eq, Ord) + diff --git a/libraries/base/GHC/Float/ConversionUtils.hs b/libraries/base/GHC/Float/ConversionUtils.hs index ddfc4e5b33..ec2233c741 100644 --- a/libraries/base/GHC/Float/ConversionUtils.hs +++ b/libraries/base/GHC/Float/ConversionUtils.hs @@ -2,6 +2,7 @@ {-# LANGUAGE CPP, MagicHash, UnboxedTuples, NoImplicitPrelude #-} {-# OPTIONS_GHC -O2 #-} {-# OPTIONS_HADDOCK hide #-} + ----------------------------------------------------------------------------- -- | -- Module : GHC.Float.ConversionUtils @@ -95,3 +96,4 @@ zeroCountArr = (# _, ba #) -> ba in case mkArr realWorld# of b -> BA b + diff --git a/libraries/base/GHC/Float/RealFracMethods.hs b/libraries/base/GHC/Float/RealFracMethods.hs index 765b0ca1f2..57ec1e820e 100644 --- a/libraries/base/GHC/Float/RealFracMethods.hs +++ b/libraries/base/GHC/Float/RealFracMethods.hs @@ -2,6 +2,7 @@ {-# LANGUAGE CPP, MagicHash, UnboxedTuples, ForeignFunctionInterface, NoImplicitPrelude #-} {-# OPTIONS_HADDOCK hide #-} + ----------------------------------------------------------------------------- -- | -- Module : GHC.Float.RealFracMethods @@ -340,3 +341,4 @@ foreign import ccall unsafe "rintDouble" foreign import ccall unsafe "rintFloat" c_rintFloat :: Float -> Float + diff --git a/libraries/base/GHC/Foreign.hs b/libraries/base/GHC/Foreign.hs index 904a81965a..f6f0272164 100644 --- a/libraries/base/GHC/Foreign.hs +++ b/libraries/base/GHC/Foreign.hs @@ -255,3 +255,4 @@ tryFillBufferAndCall encoder null_terminate from0 to_p to_sz_bytes act = do InputUnderflow -> recover encoder from' to' >>= go (iteration + 1) -- These conditions are equally bad InvalidSequence -> recover encoder from' to' >>= go (iteration + 1) -- since the input was truncated/invalid OutputUnderflow -> return Nothing -- Oops, out of buffer during decoding: ask the caller for more + diff --git a/libraries/base/GHC/Handle.hs b/libraries/base/GHC/Handle.hs index 8cc81f8043..bb744a0fab 100644 --- a/libraries/base/GHC/Handle.hs +++ b/libraries/base/GHC/Handle.hs @@ -1,5 +1,6 @@ {-# LANGUAGE Trustworthy #-} {-# OPTIONS_HADDOCK hide #-} + ----------------------------------------------------------------------------- -- | -- Module : GHC.Handle @@ -15,7 +16,6 @@ ----------------------------------------------------------------------------- -- #hide - module GHC.Handle {-# DEPRECATED "use GHC.IO.Handle instead" #-} ( withHandle, withHandle', withHandle_, wantWritableHandle, wantReadableHandle, wantSeekableHandle, diff --git a/libraries/base/GHC/IO.hs b/libraries/base/GHC/IO.hs index 345b68dd16..f30f768d5e 100644 --- a/libraries/base/GHC/IO.hs +++ b/libraries/base/GHC/IO.hs @@ -7,6 +7,7 @@ #-} {-# OPTIONS_GHC -funbox-strict-fields #-} {-# OPTIONS_HADDOCK hide #-} + ----------------------------------------------------------------------------- -- | -- Module : GHC.IO @@ -471,3 +472,4 @@ a `finally` sequel = -- evaluate :: a -> IO a evaluate a = IO $ \s -> seq# a s -- NB. see #2273, #5129 + diff --git a/libraries/base/GHC/IO.hs-boot b/libraries/base/GHC/IO.hs-boot index c7974601bc..fb0dd963b3 100644 --- a/libraries/base/GHC/IO.hs-boot +++ b/libraries/base/GHC/IO.hs-boot @@ -6,3 +6,4 @@ module GHC.IO where import GHC.Types failIO :: [Char] -> IO a + diff --git a/libraries/base/GHC/IO/Buffer.hs b/libraries/base/GHC/IO/Buffer.hs index 456b1e1919..8f677f0efd 100644 --- a/libraries/base/GHC/IO/Buffer.hs +++ b/libraries/base/GHC/IO/Buffer.hs @@ -288,3 +288,4 @@ checkBuffer buf@Buffer{ bufState = state, bufL=r, bufR=w, bufSize=size } = do check :: Buffer a -> Bool -> IO () check _ True = return () check buf False = error ("buffer invariant violation: " ++ summaryBuffer buf) + diff --git a/libraries/base/GHC/IO/BufferedIO.hs b/libraries/base/GHC/IO/BufferedIO.hs index 7690fc7341..ef78d90b46 100644 --- a/libraries/base/GHC/IO/BufferedIO.hs +++ b/libraries/base/GHC/IO/BufferedIO.hs @@ -124,3 +124,4 @@ writeBufNonBlocking dev bbuf = do res <- withBuffer bbuf $ \ptr -> IODevice.writeNonBlocking dev (ptr `plusPtr` bufL bbuf) bytes return (res, bufferAdjustL res bbuf) + diff --git a/libraries/base/GHC/IO/Device.hs b/libraries/base/GHC/IO/Device.hs index 903c0412aa..f3f330bbcf 100644 --- a/libraries/base/GHC/IO/Device.hs +++ b/libraries/base/GHC/IO/Device.hs @@ -176,3 +176,4 @@ data SeekMode | SeekFromEnd -- ^ the position of @hdl@ is set to offset @i@ -- from the end of the file. deriving (Eq, Ord, Ix, Enum, Read, Show) + diff --git a/libraries/base/GHC/IO/Encoding.hs b/libraries/base/GHC/IO/Encoding.hs index 4f8d6b120c..8d98d94336 100644 --- a/libraries/base/GHC/IO/Encoding.hs +++ b/libraries/base/GHC/IO/Encoding.hs @@ -200,3 +200,4 @@ latin1_encode input output = fmap (\(_why,input',output') -> (input',output')) $ latin1_decode :: Buffer Word8 -> CharBuffer -> IO (Buffer Word8, CharBuffer) latin1_decode input output = fmap (\(_why,input',output') -> (input',output')) $ Latin1.latin1_decode input output --latin1_decode = unsafePerformIO $ do mkTextDecoder Iconv.latin1 >>= return.encode + diff --git a/libraries/base/GHC/IO/Encoding.hs-boot b/libraries/base/GHC/IO/Encoding.hs-boot index 48c7825747..7dae9c11a4 100644 --- a/libraries/base/GHC/IO/Encoding.hs-boot +++ b/libraries/base/GHC/IO/Encoding.hs-boot @@ -1,7 +1,9 @@ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE NoImplicitPrelude #-} + module GHC.IO.Encoding where import GHC.IO.Encoding.Types localeEncoding, fileSystemEncoding, foreignEncoding :: TextEncoding + diff --git a/libraries/base/GHC/IO/Encoding/CodePage.hs b/libraries/base/GHC/IO/Encoding/CodePage.hs index 724b8ae408..0af89d76f3 100644 --- a/libraries/base/GHC/IO/Encoding/CodePage.hs +++ b/libraries/base/GHC/IO/Encoding/CodePage.hs @@ -1,6 +1,7 @@ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE CPP, BangPatterns, ForeignFunctionInterface, NoImplicitPrelude, NondecreasingIndentation, MagicHash #-} + module GHC.IO.Encoding.CodePage( #if !defined(mingw32_HOST_OS) ) where @@ -168,3 +169,4 @@ indexChar :: ConvArray Char -> Int -> Char indexChar (ConvArray p) (I# i) = C# (chr# (indexInt16OffAddr# p i)) #endif + diff --git a/libraries/base/GHC/IO/Encoding/Failure.hs b/libraries/base/GHC/IO/Encoding/Failure.hs index 8cee4b3ff7..6cd475aca3 100644 --- a/libraries/base/GHC/IO/Encoding/Failure.hs +++ b/libraries/base/GHC/IO/Encoding/Failure.hs @@ -1,5 +1,6 @@ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE NoImplicitPrelude, PatternGuards #-} + ----------------------------------------------------------------------------- -- | -- Module : GHC.IO.Encoding.Failure @@ -212,3 +213,4 @@ ioe_encodingError :: IO a ioe_encodingError = ioException (IOError Nothing InvalidArgument "recoverEncode" "invalid character" Nothing Nothing) + diff --git a/libraries/base/GHC/IO/Encoding/Iconv.hs b/libraries/base/GHC/IO/Encoding/Iconv.hs index f8dfb88ae7..2c3ad14621 100644 --- a/libraries/base/GHC/IO/Encoding/Iconv.hs +++ b/libraries/base/GHC/IO/Encoding/Iconv.hs @@ -190,3 +190,4 @@ iconvRecode iconv_t throwErrno "iconvRecoder" #endif /* !mingw32_HOST_OS */ + diff --git a/libraries/base/GHC/IO/Encoding/Latin1.hs b/libraries/base/GHC/IO/Encoding/Latin1.hs index 0e3de3922e..aba66adbb5 100644 --- a/libraries/base/GHC/IO/Encoding/Latin1.hs +++ b/libraries/base/GHC/IO/Encoding/Latin1.hs @@ -150,3 +150,4 @@ latin1_checked_encode invalid = done InvalidSequence ir ow in loop ir0 ow0 + diff --git a/libraries/base/GHC/IO/Encoding/Types.hs b/libraries/base/GHC/IO/Encoding/Types.hs index d0ff3537dd..6147d01fa1 100644 --- a/libraries/base/GHC/IO/Encoding/Types.hs +++ b/libraries/base/GHC/IO/Encoding/Types.hs @@ -131,3 +131,4 @@ data CodingProgress = InputUnderflow -- ^ Stopped because the input contains in -- to output at least one encoded ASCII character, but the input contains -- an invalid or unrepresentable sequence deriving (Eq, Show) + diff --git a/libraries/base/GHC/IO/Encoding/UTF16.hs b/libraries/base/GHC/IO/Encoding/UTF16.hs index af3cae057d..ca231caddb 100644 --- a/libraries/base/GHC/IO/Encoding/UTF16.hs +++ b/libraries/base/GHC/IO/Encoding/UTF16.hs @@ -355,3 +355,4 @@ validate2 :: Word16 -> Word16 -> Bool validate2 x1 x2 = x1 >= 0xD800 && x1 <= 0xDBFF && x2 >= 0xDC00 && x2 <= 0xDFFF {-# INLINE validate2 #-} + diff --git a/libraries/base/GHC/IO/Encoding/UTF32.hs b/libraries/base/GHC/IO/Encoding/UTF32.hs index 815f36ca19..ce3aa522c4 100644 --- a/libraries/base/GHC/IO/Encoding/UTF32.hs +++ b/libraries/base/GHC/IO/Encoding/UTF32.hs @@ -331,3 +331,4 @@ validate :: Char -> Bool validate c = (x1 >= 0x0 && x1 < 0xD800) || (x1 > 0xDFFF && x1 <= 0x10FFFF) where x1 = ord c {-# INLINE validate #-} + diff --git a/libraries/base/GHC/IO/Encoding/UTF8.hs b/libraries/base/GHC/IO/Encoding/UTF8.hs index df3e67b889..0d821139d0 100644 --- a/libraries/base/GHC/IO/Encoding/UTF8.hs +++ b/libraries/base/GHC/IO/Encoding/UTF8.hs @@ -357,3 +357,4 @@ validate4 x1 x2 x3 x4 = validate4_1 || between x2 0x80 0x8F && between x3 0x80 0xBF && between x4 0x80 0xBF + diff --git a/libraries/base/GHC/IO/Exception.hs b/libraries/base/GHC/IO/Exception.hs index 1c78e11faf..3f386ce0fc 100644 --- a/libraries/base/GHC/IO/Exception.hs +++ b/libraries/base/GHC/IO/Exception.hs @@ -2,6 +2,7 @@ {-# LANGUAGE NoImplicitPrelude, DeriveDataTypeable, MagicHash #-} {-# OPTIONS_GHC -funbox-strict-fields #-} {-# OPTIONS_HADDOCK hide #-} + ----------------------------------------------------------------------------- -- | -- Module : GHC.IO.Exception @@ -339,3 +340,4 @@ untangle coded message _ -> (loc, "") } not_bar c = c /= '|' + diff --git a/libraries/base/GHC/IO/Exception.hs-boot b/libraries/base/GHC/IO/Exception.hs-boot index fa3abe7a19..3506c1e271 100644 --- a/libraries/base/GHC/IO/Exception.hs-boot +++ b/libraries/base/GHC/IO/Exception.hs-boot @@ -1,5 +1,6 @@ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE NoImplicitPrelude #-} + module GHC.IO.Exception where import GHC.Base @@ -11,3 +12,4 @@ instance Exception IOException type IOError = IOException userError :: String -> IOError unsupportedOperation :: IOError + diff --git a/libraries/base/GHC/IO/FD.hs b/libraries/base/GHC/IO/FD.hs index 070161e671..9422ddfdc5 100644 --- a/libraries/base/GHC/IO/FD.hs +++ b/libraries/base/GHC/IO/FD.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE Unsafe #-} +{-# LANGUAGE Trustworthy #-} {-# LANGUAGE CPP , NoImplicitPrelude , BangPatterns @@ -664,3 +664,4 @@ foreign import ccall unsafe "lockFile" foreign import ccall unsafe "unlockFile" unlockFile :: CInt -> IO CInt #endif + diff --git a/libraries/base/GHC/IO/Handle.hs b/libraries/base/GHC/IO/Handle.hs index cb6f6502a1..74bf4b6072 100644 --- a/libraries/base/GHC/IO/Handle.hs +++ b/libraries/base/GHC/IO/Handle.hs @@ -741,3 +741,4 @@ showHandle' filepath is_duplex h = where def :: Int def = bufSize buf + diff --git a/libraries/base/GHC/IO/Handle.hs-boot b/libraries/base/GHC/IO/Handle.hs-boot index 935bf5e4e9..02cd1bf610 100644 --- a/libraries/base/GHC/IO/Handle.hs-boot +++ b/libraries/base/GHC/IO/Handle.hs-boot @@ -7,3 +7,4 @@ import GHC.IO import GHC.IO.Handle.Types hFlush :: Handle -> IO () + diff --git a/libraries/base/GHC/IO/Handle/FD.hs-boot b/libraries/base/GHC/IO/Handle/FD.hs-boot index fb8ee973fc..b592a05015 100644 --- a/libraries/base/GHC/IO/Handle/FD.hs-boot +++ b/libraries/base/GHC/IO/Handle/FD.hs-boot @@ -1,8 +1,10 @@ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE NoImplicitPrelude #-} + module GHC.IO.Handle.FD where import GHC.IO.Handle.Types -- used in GHC.Conc, which is below GHC.IO.Handle.FD stdout :: Handle + diff --git a/libraries/base/GHC/IO/Handle/Internals.hs b/libraries/base/GHC/IO/Handle/Internals.hs index ce59e97a72..b77de47ab7 100644 --- a/libraries/base/GHC/IO/Handle/Internals.hs +++ b/libraries/base/GHC/IO/Handle/Internals.hs @@ -912,3 +912,4 @@ decodeByteBuf h_@Handle__{..} cbuf = do writeIORef haByteBuffer bbuf2 return cbuf' + diff --git a/libraries/base/GHC/IO/Handle/Text.hs b/libraries/base/GHC/IO/Handle/Text.hs index 86689d73a3..7162dc28c5 100644 --- a/libraries/base/GHC/IO/Handle/Text.hs +++ b/libraries/base/GHC/IO/Handle/Text.hs @@ -1010,3 +1010,4 @@ illegalBufferSize handle fn sz = InvalidArgument fn ("illegal buffer size " ++ showsPrec 9 sz []) Nothing Nothing) + diff --git a/libraries/base/GHC/IO/Handle/Types.hs b/libraries/base/GHC/IO/Handle/Types.hs index 40c557a840..ec8f453cb6 100644 --- a/libraries/base/GHC/IO/Handle/Types.hs +++ b/libraries/base/GHC/IO/Handle/Types.hs @@ -428,3 +428,4 @@ instance Show Handle where showHandle :: FilePath -> String -> String showHandle file = showString "{handle: " . showString file . showString "}" + diff --git a/libraries/base/GHC/IO/IOMode.hs b/libraries/base/GHC/IO/IOMode.hs index b649ac1c0b..42cc9f31b1 100644 --- a/libraries/base/GHC/IO/IOMode.hs +++ b/libraries/base/GHC/IO/IOMode.hs @@ -1,6 +1,7 @@ {-# LANGUAGE Trustworthy #-} {-# LANGUAGE NoImplicitPrelude #-} {-# OPTIONS_HADDOCK hide #-} + ----------------------------------------------------------------------------- -- | -- Module : GHC.IO.IOMode @@ -26,3 +27,4 @@ import GHC.Enum -- | See 'System.IO.openFile' data IOMode = ReadMode | WriteMode | AppendMode | ReadWriteMode deriving (Eq, Ord, Ix, Enum, Read, Show) + diff --git a/libraries/base/GHC/IOArray.hs b/libraries/base/GHC/IOArray.hs index e052deb6ff..800b596923 100644 --- a/libraries/base/GHC/IOArray.hs +++ b/libraries/base/GHC/IOArray.hs @@ -2,6 +2,7 @@ {-# LANGUAGE NoImplicitPrelude #-} {-# OPTIONS_GHC -funbox-strict-fields #-} {-# OPTIONS_HADDOCK hide #-} + ----------------------------------------------------------------------------- -- | -- Module : GHC.IOArray diff --git a/libraries/base/GHC/IOBase.hs b/libraries/base/GHC/IOBase.hs index cf05c78744..60fb943462 100644 --- a/libraries/base/GHC/IOBase.hs +++ b/libraries/base/GHC/IOBase.hs @@ -16,7 +16,6 @@ -- ----------------------------------------------------------------------------- - module GHC.IOBase {-# DEPRECATED "use GHC.IO instead" #-} ( IO(..), unIO, failIO, liftIO, bindIO, thenIO, returnIO, unsafePerformIO, unsafeInterleaveIO, @@ -91,3 +90,4 @@ instance Show BlockedIndefinitely where blockedIndefinitely :: SomeException -- for the RTS blockedIndefinitely = toException BlockedIndefinitely + diff --git a/libraries/base/GHC/IORef.hs b/libraries/base/GHC/IORef.hs index f6b2b660bd..a0ed0823ed 100644 --- a/libraries/base/GHC/IORef.hs +++ b/libraries/base/GHC/IORef.hs @@ -16,6 +16,7 @@ -- The IORef type -- ----------------------------------------------------------------------------- + module GHC.IORef ( IORef(..), newIORef, readIORef, writeIORef, atomicModifyIORef diff --git a/libraries/base/GHC/Int.hs b/libraries/base/GHC/Int.hs index d29c10b457..f1fa3043cf 100644 --- a/libraries/base/GHC/Int.hs +++ b/libraries/base/GHC/Int.hs @@ -2,6 +2,7 @@ {-# LANGUAGE CPP, NoImplicitPrelude, BangPatterns, MagicHash, StandaloneDeriving #-} {-# OPTIONS_HADDOCK hide #-} + ----------------------------------------------------------------------------- -- | -- Module : GHC.Int diff --git a/libraries/base/GHC/PArr.hs b/libraries/base/GHC/PArr.hs index ee7eea8b27..5852625d50 100644 --- a/libraries/base/GHC/PArr.hs +++ b/libraries/base/GHC/PArr.hs @@ -27,3 +27,4 @@ import GHC.Base -- NB: This definition *must* be kept in sync with `TysWiredIn.parrTyCon'! -- data [::] e = PArr !Int (Array# e) + diff --git a/libraries/base/GHC/Unicode.hs-boot b/libraries/base/GHC/Unicode.hs-boot index 1e01a1ce29..51bf87ddcf 100644 --- a/libraries/base/GHC/Unicode.hs-boot +++ b/libraries/base/GHC/Unicode.hs-boot @@ -17,3 +17,4 @@ isDigit :: Char -> Bool isOctDigit :: Char -> Bool isHexDigit :: Char -> Bool isAlphaNum :: Char -> Bool + diff --git a/libraries/base/GHC/Word.hs b/libraries/base/GHC/Word.hs index 6dd308abb4..42daf07138 100644 --- a/libraries/base/GHC/Word.hs +++ b/libraries/base/GHC/Word.hs @@ -838,3 +838,4 @@ instance Ix Word64 where instance Read Word64 where readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s] + diff --git a/libraries/base/System/CPUTime.hsc b/libraries/base/System/CPUTime.hsc index 61ce09fd05..0b56329f38 100644 --- a/libraries/base/System/CPUTime.hsc +++ b/libraries/base/System/CPUTime.hsc @@ -185,3 +185,4 @@ clockTicks = foreign import ccall unsafe sysconf :: CInt -> IO CLong #endif #endif /* __GLASGOW_HASKELL__ */ + diff --git a/libraries/base/System/Console/GetOpt.hs b/libraries/base/System/Console/GetOpt.hs index d5a32f395f..1ea082963d 100644 --- a/libraries/base/System/Console/GetOpt.hs +++ b/libraries/base/System/Console/GetOpt.hs @@ -1,4 +1,5 @@ {-# LANGUAGE Safe #-} + ----------------------------------------------------------------------------- -- | -- Module : System.Console.GetOpt @@ -392,3 +393,4 @@ processing to perform actions of the chosen monad, e.g. printing help or version messages, checking that file arguments exist, etc. -} + diff --git a/libraries/base/System/Environment.hs b/libraries/base/System/Environment.hs index e185575147..a9413d1416 100644 --- a/libraries/base/System/Environment.hs +++ b/libraries/base/System/Environment.hs @@ -336,3 +336,4 @@ divvy str = (xs,[]) -> (xs,[]) -- don't barf (like Posix.getEnvironment) (name,_:value) -> (name,value) #endif /* __GLASGOW_HASKELL__ */ + diff --git a/libraries/base/System/Exit.hs b/libraries/base/System/Exit.hs index 9a9ed00045..2f63024b18 100644 --- a/libraries/base/System/Exit.hs +++ b/libraries/base/System/Exit.hs @@ -92,3 +92,4 @@ exitFailure = exitWith (ExitFailure 1) -- successfully. exitSuccess :: IO a exitSuccess = exitWith ExitSuccess + diff --git a/libraries/base/System/IO.hs b/libraries/base/System/IO.hs index 768d557653..9cd96eb0ea 100644 --- a/libraries/base/System/IO.hs +++ b/libraries/base/System/IO.hs @@ -634,3 +634,4 @@ foreign import ccall "getpid" c_getpid :: IO Int -- It follows that an attempt to write to a file (using 'writeFile', for -- example) that was earlier opened by 'readFile' will usually result in -- failure with 'System.IO.Error.isAlreadyInUseError'. + diff --git a/libraries/base/System/IO/Error.hs b/libraries/base/System/IO/Error.hs index 1458d60bed..b1fb5ffbfa 100644 --- a/libraries/base/System/IO/Error.hs +++ b/libraries/base/System/IO/Error.hs @@ -475,3 +475,4 @@ catchIOError = New.catch catch :: IO a -> (IOError -> IO a) -> IO a catch = New.catch #endif /* !__HUGS__ */ + diff --git a/libraries/base/System/Info.hs b/libraries/base/System/Info.hs index 5fc816c080..c9f623d1ff 100644 --- a/libraries/base/System/Info.hs +++ b/libraries/base/System/Info.hs @@ -67,3 +67,4 @@ compilerVersionRaw = 0 -- ToDo #else #error Unknown compiler name #endif + diff --git a/libraries/base/System/Mem.hs b/libraries/base/System/Mem.hs index 67b80cc320..8e8a1bc2e0 100644 --- a/libraries/base/System/Mem.hs +++ b/libraries/base/System/Mem.hs @@ -1,6 +1,5 @@ {-# LANGUAGE Safe #-} {-# LANGUAGE CPP #-} - #ifdef __GLASGOW_HASKELL__ {-# LANGUAGE ForeignFunctionInterface #-} #endif @@ -37,3 +36,4 @@ foreign import ccall {-safe-} "performMajorGC" performGC :: IO () #ifdef __NHC__ import NHC.IOExtras (performGC) #endif + diff --git a/libraries/base/System/Mem/StableName.hs b/libraries/base/System/Mem/StableName.hs index 7d688e9aa8..8b8d690d8f 100644 --- a/libraries/base/System/Mem/StableName.hs +++ b/libraries/base/System/Mem/StableName.hs @@ -124,3 +124,4 @@ instance Eq (StableName a) where #include "Typeable.h" INSTANCE_TYPEABLE1(StableName,stableNameTc,"StableName") + diff --git a/libraries/base/System/Mem/Weak.hs b/libraries/base/System/Mem/Weak.hs index 8980a51b55..a2e6f72063 100644 --- a/libraries/base/System/Mem/Weak.hs +++ b/libraries/base/System/Mem/Weak.hs @@ -151,3 +151,4 @@ reachable if: * It is the value or finalizer of an object whose key is reachable. -} + diff --git a/libraries/base/System/Posix/Internals.hs b/libraries/base/System/Posix/Internals.hs index 632e69eb27..0f94c386e6 100644 --- a/libraries/base/System/Posix/Internals.hs +++ b/libraries/base/System/Posix/Internals.hs @@ -578,3 +578,4 @@ foreign import ccall unsafe "__hscore_bufsiz" dEFAULT_BUFFER_SIZE :: Int foreign import ccall unsafe "__hscore_seek_cur" sEEK_CUR :: CInt foreign import ccall unsafe "__hscore_seek_set" sEEK_SET :: CInt foreign import ccall unsafe "__hscore_seek_end" sEEK_END :: CInt + diff --git a/libraries/base/System/Posix/Internals.hs-boot b/libraries/base/System/Posix/Internals.hs-boot index ff4c4e8427..612269b844 100644 --- a/libraries/base/System/Posix/Internals.hs-boot +++ b/libraries/base/System/Posix/Internals.hs-boot @@ -6,3 +6,4 @@ import GHC.IO import GHC.Base puts :: String -> IO () + diff --git a/libraries/base/System/Timeout.hs b/libraries/base/System/Timeout.hs index d1cbbffc91..4114852694 100644 --- a/libraries/base/System/Timeout.hs +++ b/libraries/base/System/Timeout.hs @@ -92,3 +92,4 @@ timeout n f #else timeout n f = fmap Just f #endif /* !__GLASGOW_HASKELL__ */ + diff --git a/libraries/base/Text/ParserCombinators/ReadP.hs b/libraries/base/Text/ParserCombinators/ReadP.hs index 2bb93639bb..34247120f1 100644 --- a/libraries/base/Text/ParserCombinators/ReadP.hs +++ b/libraries/base/Text/ParserCombinators/ReadP.hs @@ -543,3 +543,4 @@ Here follow the properties: > prop_ReadS r s = > readP_to_S (readS_to_P r) s =~. r s -} + diff --git a/libraries/base/Text/ParserCombinators/ReadPrec.hs b/libraries/base/Text/ParserCombinators/ReadPrec.hs index 8a200b956e..faf53a9a4b 100644 --- a/libraries/base/Text/ParserCombinators/ReadPrec.hs +++ b/libraries/base/Text/ParserCombinators/ReadPrec.hs @@ -162,3 +162,4 @@ readPrec_to_S (P f) n = readP_to_S (f n) readS_to_Prec :: (Int -> ReadS a) -> ReadPrec a readS_to_Prec f = P (\n -> readS_to_P (f n)) + diff --git a/libraries/base/Text/Printf.hs b/libraries/base/Text/Printf.hs index 0ef936480d..1369cfe312 100644 --- a/libraries/base/Text/Printf.hs +++ b/libraries/base/Text/Printf.hs @@ -328,3 +328,4 @@ fmterr, argerr, baderr :: a fmterr = perror "formatting string ended prematurely" argerr = perror "argument list ended prematurely" baderr = perror "bad argument" + diff --git a/libraries/base/Text/Read/Lex.hs b/libraries/base/Text/Read/Lex.hs index 199aa9b173..e4563b6e98 100644 --- a/libraries/base/Text/Read/Lex.hs +++ b/libraries/base/Text/Read/Lex.hs @@ -451,3 +451,4 @@ readOctP, readDecP, readHexP :: (Eq a, Num a) => ReadP a readOctP = readIntP' 8 readDecP = readIntP' 10 readHexP = readIntP' 16 + diff --git a/libraries/base/Text/Show.hs b/libraries/base/Text/Show.hs index 3662d124c2..0ee9e50fba 100644 --- a/libraries/base/Text/Show.hs +++ b/libraries/base/Text/Show.hs @@ -47,3 +47,4 @@ showList__ showx (x:xs) s = '[' : showx x (showl xs) showl [] = ']' : s showl (y:ys) = ',' : showx y (showl ys) #endif + diff --git a/libraries/base/Text/Show/Functions.hs b/libraries/base/Text/Show/Functions.hs index fa202f7edd..104f9535e7 100644 --- a/libraries/base/Text/Show/Functions.hs +++ b/libraries/base/Text/Show/Functions.hs @@ -36,3 +36,4 @@ instance (Show a,Show b) => Show (a->b) where where (value,result) = getTypes undefined getTypes x = (x,a x) #endif + diff --git a/libraries/base/Unsafe/Coerce.hs b/libraries/base/Unsafe/Coerce.hs index 5cf004b282..72f35b2ce3 100644 --- a/libraries/base/Unsafe/Coerce.hs +++ b/libraries/base/Unsafe/Coerce.hs @@ -26,6 +26,8 @@ -- * In nhc98, the only representation-safe coercions are between Enum -- types with the same range (e.g. Int, Int32, Char, Word32), -- or between a newtype and the type that it wraps. +-- +----------------------------------------------------------------------------- module Unsafe.Coerce (unsafeCoerce) where @@ -42,3 +44,4 @@ import NonStdUnsafeCoerce (unsafeCoerce) #if defined(__HUGS__) import Hugs.IOExts (unsafeCoerce) #endif + |