diff --git a/Control/Monad.hs b/Control/Monad.hs index 7af5a647215713d9043237ccab0a25953f584920..6c1647457b659812ea2e943998f937bbbe0dec79 100644 --- a/Control/Monad.hs +++ b/Control/Monad.hs @@ -44,7 +44,7 @@ module Control.Monad ( , mapAndUnzipM -- :: (Monad m) => (a -> m (b,c)) -> [a] -> m ([b], [c]) , zipWithM -- :: (Monad m) => (a -> b -> m c) -> [a] -> [b] -> m [c] , zipWithM_ -- :: (Monad m) => (a -> b -> m c) -> [a] -> [b] -> m () - , foldM -- :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m a + , foldM -- :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m a , foldM_ -- :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m () , replicateM -- :: (Monad m) => Int -> m a -> m [a] , replicateM_ -- :: (Monad m) => Int -> m a -> m () @@ -70,23 +70,23 @@ import "base" Control.Monad {- $naming -The functions in this library use the following naming conventions: +The functions in this library use the following naming conventions: * A postfix \'@M@\' always stands for a function in the Kleisli category: The monad type constructor @m@ is added to function results - (modulo currying) and nowhere else. So, for example, + (modulo currying) and nowhere else. So, for example, > filter :: (a -> Bool) -> [a] -> [a] > filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a] * A postfix \'@_@\' changes the result type from @(m a)@ to @(m ())@. - Thus, for example: + Thus, for example: -> sequence :: Monad m => [m a] -> m [a] -> sequence_ :: Monad m => [m a] -> m () +> sequence :: Monad m => [m a] -> m [a] +> sequence_ :: Monad m => [m a] -> m () * A prefix \'@m@\' generalizes an existing function to a monadic form. - Thus, for example: + Thus, for example: > sum :: Num a => [a] -> a > msum :: MonadPlus m => [m a] -> m a diff --git a/Data/Array.hs b/Data/Array.hs index 90ba1e75b9c6f9db097c1f69835727e8c1bd1b9a..100674d25a2f741a62bb6165f1bbbad156b01727 100644 --- a/Data/Array.hs +++ b/Data/Array.hs @@ -6,7 +6,7 @@ module Data.Array ( -- * Immutable non-strict arrays -- $intro - module Data.Ix -- export all of Ix + module Data.Ix -- export all of Ix , Array -- Array type is abstract -- * Array construction @@ -102,18 +102,18 @@ array = Array.array (//) = (Array.//) {- $code -> module Array ( +> module Array ( > module Data.Ix, -- export all of Data.Ix -> Array, array, listArray, (!), bounds, indices, elems, assocs, +> Array, array, listArray, (!), bounds, indices, elems, assocs, > accumArray, (//), accum, ixmap ) where -> +> > import Data.Ix > import Data.List( (\\) ) -> +> > infixl 9 !, // -> +> > data (Ix a) => Array a b = MkArray (a,a) (a -> b) deriving () -> +> > array :: (Ix a) => (a,a) -> [(a,b)] -> Array a b > array b ivs > | any (not . inRange b. fst) ivs @@ -125,66 +125,66 @@ array = Array.array > [v] -> v > [] -> error "Data.Array.!: undefined array element" > _ -> error "Data.Array.!: multiply defined array element" -> +> > listArray :: (Ix a) => (a,a) -> [b] -> Array a b > listArray b vs = array b (zipWith (\ a b -> (a,b)) (range b) vs) -> +> > (!) :: (Ix a) => Array a b -> a -> b > (!) (MkArray _ f) = f -> +> > bounds :: (Ix a) => Array a b -> (a,a) > bounds (MkArray b _) = b -> +> > indices :: (Ix a) => Array a b -> [a] > indices = range . bounds -> +> > elems :: (Ix a) => Array a b -> [b] > elems a = [a!i | i <- indices a] -> +> > assocs :: (Ix a) => Array a b -> [(a,b)] > assocs a = [(i, a!i) | i <- indices a] -> +> > (//) :: (Ix a) => Array a b -> [(a,b)] -> Array a b > a // new_ivs = array (bounds a) (old_ivs ++ new_ivs) > where > old_ivs = [(i,a!i) | i <- indices a, > i `notElem` new_is] > new_is = [i | (i,_) <- new_ivs] -> +> > accum :: (Ix a) => (b -> c -> b) -> Array a b -> [(a,c)] > -> Array a b > accum f = foldl (\a (i,v) -> a // [(i,f (a!i) v)]) -> +> > accumArray :: (Ix a) => (b -> c -> b) -> b -> (a,a) -> [(a,c)] > -> Array a b > accumArray f z b = accum f (array b [(i,z) | i <- range b]) -> +> > ixmap :: (Ix a, Ix b) => (a,a) -> (a -> b) -> Array b c > -> Array a c > ixmap b f a = array b [(i, a ! f i) | i <- range b] -> +> > instance (Ix a) => Functor (Array a) where -> fmap fn (MkArray b f) = MkArray b (fn . f) -> +> fmap fn (MkArray b f) = MkArray b (fn . f) +> > instance (Ix a, Eq b) => Eq (Array a b) where > a == a' = assocs a == assocs a' -> +> > instance (Ix a, Ord b) => Ord (Array a b) where > a <= a' = assocs a <= assocs a' -> +> > instance (Ix a, Show a, Show b) => Show (Array a b) where > showsPrec p a = showParen (p > arrPrec) ( > showString "array " . > showsPrec (arrPrec+1) (bounds a) . showChar ' ' . > showsPrec (arrPrec+1) (assocs a) ) -> +> > instance (Ix a, Read a, Read b) => Read (Array a b) where > readsPrec p = readParen (p > arrPrec) -> (\r -> [ (array b as, u) +> (\r -> [ (array b as, u) > | ("array",s) <- lex r, > (b,t) <- readsPrec (arrPrec+1) s, > (as,u) <- readsPrec (arrPrec+1) t ]) -> +> > -- Precedence of the 'array' function is that of application itself > arrPrec = 10 -} diff --git a/Data/Char.hs b/Data/Char.hs index a2147f59fdeefb45943787e45b17045c9cda8d72..a651e787b6b11d61025eb0115a99f14e519d481a 100644 --- a/Data/Char.hs +++ b/Data/Char.hs @@ -39,6 +39,6 @@ module Data.Char ( -- * String representations , showLitChar -- :: Char -> ShowS , lexLitChar -- :: ReadS String - , readLitChar -- :: ReadS Char + , readLitChar -- :: ReadS Char ) where import "base" Data.Char diff --git a/Data/Complex.hs b/Data/Complex.hs index 2b575fb4ed95648fd0c01c86d970433c0753d2a0..abc84fc4c790e679a45300c6c7f2e9597b3a792f 100644 --- a/Data/Complex.hs +++ b/Data/Complex.hs @@ -27,39 +27,39 @@ import "base" Data.Complex {- $code > module Data.Complex(Complex((:+)), realPart, imagPart, conjugate, mkPolar, > cis, polar, magnitude, phase) where -> +> > infix 6 :+ -> +> > data (RealFloat a) => Complex a = !a :+ !a deriving (Eq,Read,Show) -> -> +> +> > realPart, imagPart :: (RealFloat a) => Complex a -> a > realPart (x:+y) = x > imagPart (x:+y) = y -> +> > conjugate :: (RealFloat a) => Complex a -> Complex a > conjugate (x:+y) = x :+ (-y) -> +> > mkPolar :: (RealFloat a) => a -> a -> Complex a > mkPolar r theta = r * cos theta :+ r * sin theta -> +> > cis :: (RealFloat a) => a -> Complex a > cis theta = cos theta :+ sin theta -> +> > polar :: (RealFloat a) => Complex a -> (a,a) > polar z = (magnitude z, phase z) -> +> > magnitude :: (RealFloat a) => Complex a -> a > magnitude (x:+y) = scaleFloat k > (sqrt ((scaleFloat mk x)^2 + (scaleFloat mk y)^2)) > where k = max (exponent x) (exponent y) > mk = - k -> +> > phase :: (RealFloat a) => Complex a -> a > phase (0 :+ 0) = 0 > phase (x :+ y) = atan2 y x -> -> +> +> > instance (RealFloat a) => Num (Complex a) where > (x:+y) + (x':+y') = (x+x') :+ (y+y') > (x:+y) - (x':+y') = (x-x') :+ (y-y') @@ -69,7 +69,7 @@ import "base" Data.Complex > signum 0 = 0 > signum z@(x:+y) = x/r :+ y/r where r = magnitude z > fromInteger n = fromInteger n :+ 0 -> +> > instance (RealFloat a) => Fractional (Complex a) where > (x:+y) / (x':+y') = (x*x''+y*y'') / d :+ (y*x''-x*y'') / d > where x'' = scaleFloat k x' @@ -78,19 +78,19 @@ import "base" Data.Complex > d = x'*x'' + y'*y'' > > fromRational a = fromRational a :+ 0 -> +> > instance (RealFloat a) => Floating (Complex a) where > pi = pi :+ 0 > exp (x:+y) = expx * cos y :+ expx * sin y > where expx = exp x > log z = log (magnitude z) :+ phase z -> +> > sqrt 0 = 0 > sqrt z@(x:+y) = u :+ (if y < 0 then -v else v) > where (u,v) = if x < 0 then (v',u') else (u',v') > v' = abs y / (u'*2) > u' = sqrt ((magnitude z + abs x) / 2) -> +> > sin (x:+y) = sin x * cosh y :+ cos x * sinh y > cos (x:+y) = cos x * cosh y :+ (- sin x * sinh y) > tan (x:+y) = (sinx*coshy:+cosx*sinhy)/(cosx*coshy:+(-sinx*sinhy)) @@ -98,7 +98,7 @@ import "base" Data.Complex > cosx = cos x > sinhy = sinh y > coshy = cosh y -> +> > sinh (x:+y) = cos y * sinh x :+ sin y * cosh x > cosh (x:+y) = cos y * cosh x :+ sin y * sinh x > tanh (x:+y) = (cosy*sinhx:+siny*coshx)/(cosy*coshx:+siny*sinhx) @@ -106,7 +106,7 @@ import "base" Data.Complex > cosy = cos y > sinhx = sinh x > coshx = cosh x -> +> > asin z@(x:+y) = y':+(-x') > where (x':+y') = log (((-y):+x) + sqrt (1 - z*z)) > acos z@(x:+y) = y'':+(-x'') @@ -114,7 +114,7 @@ import "base" Data.Complex > (x':+y') = sqrt (1 - z*z) > atan z@(x:+y) = y':+(-x') > where (x':+y') = log (((1-y):+x) / sqrt (1+z*z)) -> +> > asinh z = log (z + sqrt (1+z*z)) > acosh z = log (z + (z+1) * sqrt ((z-1)/(z+1))) > atanh z = log ((1+z) / sqrt (1-z*z)) diff --git a/Data/Ix.hs b/Data/Ix.hs index e1add07d6710c53ef1974aee559d10b705fb55fc..b0c0066ec90739bf1149c4fa6f0016b0d6ef47ae 100644 --- a/Data/Ix.hs +++ b/Data/Ix.hs @@ -13,7 +13,7 @@ module Data.Ix ( ) -- * Deriving Instances of @Ix@ - + -- $derived ) where import "base" Data.Ix @@ -50,7 +50,7 @@ are as shown for tuples: > = index (l,u) i * rangeSize (l',u') + index (l',u') i' > inRange ((l,l'),(u,u')) (i,i') > = inRange (l,u) i && inRange (l',u') i' -> +> > -- Instances for other tuples are obtained from this scheme: > -- > -- instance (Ix a1, Ix a2, ... , Ix ak) => Ix (a1,a2,...,ak) where diff --git a/Data/List.hs b/Data/List.hs index 156edf472c5fdec1598d77dda75aa5eef0eb8e4a..b498db8a91c70085c719ecf34bd81dad287b81e7 100644 --- a/Data/List.hs +++ b/Data/List.hs @@ -21,7 +21,7 @@ module Data.List ( , intersperse -- :: a -> [a] -> [a] , intercalate -- :: [a] -> [[a]] -> [a] , transpose -- :: [[a]] -> [[a]] - + , subsequences -- :: [a] -> [[a]] , permutations -- :: [a] -> [[a]] diff --git a/Data/Maybe.hs b/Data/Maybe.hs index 41a086b980bfa1d4d5064e6d8d8812a5176fd571..90fb5f86a9a0cbbeb8947a02c874f7706ff9b656 100644 --- a/Data/Maybe.hs +++ b/Data/Maybe.hs @@ -21,7 +21,7 @@ module Data.Maybe ( , mapMaybe -- :: (a -> Maybe b) -> [a] -> [b] -- * Specification - + -- $code ) where @@ -35,37 +35,37 @@ import "base" Data.Maybe > catMaybes, mapMaybe, > maybe > ) where -> +> > maybe :: b -> (a -> b) -> Maybe a -> b > maybe n _ Nothing = n > maybe _ f (Just x) = f x -> +> > isJust :: Maybe a -> Bool > isJust (Just a) = True > isJust Nothing = False -> +> > isNothing :: Maybe a -> Bool > isNothing = not . isJust -> +> > fromJust :: Maybe a -> a > fromJust (Just a) = a > fromJust Nothing = error "Maybe.fromJust: Nothing" -> +> > fromMaybe :: a -> Maybe a -> a > fromMaybe d Nothing = d > fromMaybe d (Just a) = a -> +> > maybeToList :: Maybe a -> [a] > maybeToList Nothing = [] > maybeToList (Just a) = [a] -> +> > listToMaybe :: [a] -> Maybe a > listToMaybe [] = Nothing > listToMaybe (a:_) = Just a -> +> > catMaybes :: [Maybe a] -> [a] > catMaybes ms = [ m | Just m <- ms ] -> +> > mapMaybe :: (a -> Maybe b) -> [a] -> [b] > mapMaybe f = catMaybes . map f -} diff --git a/Data/Ratio.hs b/Data/Ratio.hs index 99cb4a7b1c2375ae47ec04e3e9f21697b45abde8..1c96cb37ff68aa20addeff7edf6eae02a80fca6e 100644 --- a/Data/Ratio.hs +++ b/Data/Ratio.hs @@ -20,41 +20,41 @@ import "base" Data.Ratio {- $code > module Data.Ratio ( > Ratio, Rational, (%), numerator, denominator, approxRational ) where -> +> > infixl 7 % -> +> > ratPrec = 7 :: Int -> +> > data (Integral a) => Ratio a = !a :% !a deriving (Eq) > type Rational = Ratio Integer -> +> > (%) :: (Integral a) => a -> a -> Ratio a > numerator, denominator :: (Integral a) => Ratio a -> a > approxRational :: (RealFrac a) => a -> a -> Rational -> -> +> +> > -- "reduce" is a subsidiary function used only in this module. > -- It normalises a ratio by dividing both numerator > -- and denominator by their greatest common divisor. > -- > -- E.g., 12 `reduce` 8 == 3 :% 2 > -- 12 `reduce` (-8) == 3 :% (-2) -> +> > reduce _ 0 = error "Data.Ratio.% : zero denominator" > reduce x y = (x `quot` d) :% (y `quot` d) > where d = gcd x y -> +> > x % y = reduce (x * signum y) (abs y) -> +> > numerator (x :% _) = x -> +> > denominator (_ :% y) = y -> -> +> +> > instance (Integral a) => Ord (Ratio a) where > (x:%y) <= (x':%y') = x * y' <= x' * y > (x:%y) < (x':%y') = x * y' < x' * y -> +> > instance (Integral a) => Num (Ratio a) where > (x:%y) + (x':%y') = reduce (x*y' + x'*y) (y*y') > (x:%y) * (x':%y') = reduce (x * x') (y * y') @@ -62,19 +62,19 @@ import "base" Data.Ratio > abs (x:%y) = abs x :% y > signum (x:%y) = signum x :% 1 > fromInteger x = fromInteger x :% 1 -> +> > instance (Integral a) => Real (Ratio a) where > toRational (x:%y) = toInteger x :% toInteger y -> +> > instance (Integral a) => Fractional (Ratio a) where > (x:%y) / (x':%y') = (x*y') % (y*x') > recip (x:%y) = y % x > fromRational (x:%y) = fromInteger x :% fromInteger y -> +> > instance (Integral a) => RealFrac (Ratio a) where > properFraction (x:%y) = (fromIntegral q, r:%y) > where (q,r) = quotRem x y -> +> > instance (Integral a) => Enum (Ratio a) where > succ x = x+1 > pred x = x-1 @@ -84,21 +84,21 @@ import "base" Data.Ratio > enumFromThen = numericEnumFromThen -- are as defined in Prelude.hs > enumFromTo = numericEnumFromTo -- but not exported from it! > enumFromThenTo = numericEnumFromThenTo -> +> > instance (Read a, Integral a) => Read (Ratio a) where > readsPrec p = readParen (p > ratPrec) > (\r -> [(x%y,u) | (x,s) <- readsPrec (ratPrec+1) r, > ("%",t) <- lex s, > (y,u) <- readsPrec (ratPrec+1) t ]) -> +> > instance (Integral a) => Show (Ratio a) where > showsPrec p (x:%y) = showParen (p > ratPrec) -> showsPrec (ratPrec+1) x . -> showString " % " . +> showsPrec (ratPrec+1) x . +> showString " % " . > showsPrec (ratPrec+1) y) -> -> -> +> +> +> > approxRational x eps = simplest (x-eps) (x+eps) > where simplest x y | y < x = simplest y x > | x == y = xr @@ -107,7 +107,7 @@ import "base" Data.Ratio > | otherwise = 0 :% 1 > where xr@(n:%d) = toRational x > (n':%d') = toRational y -> +> > simplest' n d n' d' -- assumes 0 < n%d < n'%d' > | r == 0 = q :% 1 > | q /= q' = (q+1) :% 1 diff --git a/Foreign/C/Error.hs b/Foreign/C/Error.hs index 25ef77c10cee66f237ea5874859ee92ec4bded02..83c204d663f257eea3e5387ab641eb2d568a7a91 100644 --- a/Foreign/C/Error.hs +++ b/Foreign/C/Error.hs @@ -16,19 +16,19 @@ module Foreign.C.Error ( -- different values of @errno@. This module defines the common values, -- but due to the open definition of 'Errno' users may add definitions -- which are not predefined. - eOK, e2BIG, eACCES, eADDRINUSE, eADDRNOTAVAIL, eADV, eAFNOSUPPORT, eAGAIN, - eALREADY, eBADF, eBADMSG, eBADRPC, eBUSY, eCHILD, eCOMM, eCONNABORTED, - eCONNREFUSED, eCONNRESET, eDEADLK, eDESTADDRREQ, eDIRTY, eDOM, eDQUOT, - eEXIST, eFAULT, eFBIG, eFTYPE, eHOSTDOWN, eHOSTUNREACH, eIDRM, eILSEQ, - eINPROGRESS, eINTR, eINVAL, eIO, eISCONN, eISDIR, eLOOP, eMFILE, eMLINK, - eMSGSIZE, eMULTIHOP, eNAMETOOLONG, eNETDOWN, eNETRESET, eNETUNREACH, - eNFILE, eNOBUFS, eNODATA, eNODEV, eNOENT, eNOEXEC, eNOLCK, eNOLINK, - eNOMEM, eNOMSG, eNONET, eNOPROTOOPT, eNOSPC, eNOSR, eNOSTR, eNOSYS, - eNOTBLK, eNOTCONN, eNOTDIR, eNOTEMPTY, eNOTSOCK, eNOTTY, eNXIO, - eOPNOTSUPP, ePERM, ePFNOSUPPORT, ePIPE, ePROCLIM, ePROCUNAVAIL, - ePROGMISMATCH, ePROGUNAVAIL, ePROTO, ePROTONOSUPPORT, ePROTOTYPE, - eRANGE, eREMCHG, eREMOTE, eROFS, eRPCMISMATCH, eRREMOTE, eSHUTDOWN, - eSOCKTNOSUPPORT, eSPIPE, eSRCH, eSRMNT, eSTALE, eTIME, eTIMEDOUT, + eOK, e2BIG, eACCES, eADDRINUSE, eADDRNOTAVAIL, eADV, eAFNOSUPPORT, eAGAIN, + eALREADY, eBADF, eBADMSG, eBADRPC, eBUSY, eCHILD, eCOMM, eCONNABORTED, + eCONNREFUSED, eCONNRESET, eDEADLK, eDESTADDRREQ, eDIRTY, eDOM, eDQUOT, + eEXIST, eFAULT, eFBIG, eFTYPE, eHOSTDOWN, eHOSTUNREACH, eIDRM, eILSEQ, + eINPROGRESS, eINTR, eINVAL, eIO, eISCONN, eISDIR, eLOOP, eMFILE, eMLINK, + eMSGSIZE, eMULTIHOP, eNAMETOOLONG, eNETDOWN, eNETRESET, eNETUNREACH, + eNFILE, eNOBUFS, eNODATA, eNODEV, eNOENT, eNOEXEC, eNOLCK, eNOLINK, + eNOMEM, eNOMSG, eNONET, eNOPROTOOPT, eNOSPC, eNOSR, eNOSTR, eNOSYS, + eNOTBLK, eNOTCONN, eNOTDIR, eNOTEMPTY, eNOTSOCK, eNOTTY, eNXIO, + eOPNOTSUPP, ePERM, ePFNOSUPPORT, ePIPE, ePROCLIM, ePROCUNAVAIL, + ePROGMISMATCH, ePROGUNAVAIL, ePROTO, ePROTONOSUPPORT, ePROTOTYPE, + eRANGE, eREMCHG, eREMOTE, eROFS, eRPCMISMATCH, eRREMOTE, eSHUTDOWN, + eSOCKTNOSUPPORT, eSPIPE, eSRCH, eSRMNT, eSTALE, eTIME, eTIMEDOUT, eTOOMANYREFS, eTXTBSY, eUSERS, eWOULDBLOCK, eXDEV, -- ** 'Errno' functions @@ -58,23 +58,23 @@ module Foreign.C.Error ( throwErrnoIf_, -- :: (a -> Bool) -> String -> IO a -> IO () throwErrnoIfRetry, -- :: (a -> Bool) -> String -> IO a -> IO a throwErrnoIfRetry_, -- :: (a -> Bool) -> String -> IO a -> IO () - throwErrnoIfMinus1, -- :: Num a + throwErrnoIfMinus1, -- :: Num a -- => String -> IO a -> IO a - throwErrnoIfMinus1_, -- :: Num a + throwErrnoIfMinus1_, -- :: Num a -- => String -> IO a -> IO () throwErrnoIfMinus1Retry, - -- :: Num a + -- :: Num a -- => String -> IO a -> IO a - throwErrnoIfMinus1Retry_, - -- :: Num a + throwErrnoIfMinus1Retry_, + -- :: Num a -- => String -> IO a -> IO () throwErrnoIfNull, -- :: String -> IO (Ptr a) -> IO (Ptr a) throwErrnoIfNullRetry,-- :: String -> IO (Ptr a) -> IO (Ptr a) - throwErrnoIfRetryMayBlock, + throwErrnoIfRetryMayBlock, throwErrnoIfRetryMayBlock_, throwErrnoIfMinus1RetryMayBlock, - throwErrnoIfMinus1RetryMayBlock_, + throwErrnoIfMinus1RetryMayBlock_, throwErrnoIfNullRetryMayBlock, throwErrnoPath, diff --git a/Foreign/ForeignPtr.hs b/Foreign/ForeignPtr.hs index 1fd58652f9e0f86313b576daa917cc55a4340b49..d04eccadee8137e115c698b9fc886e1eed4d02eb 100644 --- a/Foreign/ForeignPtr.hs +++ b/Foreign/ForeignPtr.hs @@ -42,7 +42,7 @@ mallocForeignPtr :: Storable a => IO (ForeignPtr a) -- 'mallocForeignPtr' is equivalent to -- -- > do { p <- malloc; newForeignPtr finalizerFree p } --- +-- -- although it may be implemented differently internally: you may not -- assume that the memory returned by 'mallocForeignPtr' has been -- allocated with 'Foreign.Marshal.Alloc.malloc'. @@ -57,7 +57,7 @@ touchForeignPtr :: ForeignPtr a -> IO () -- actions. In particular 'Foreign.ForeignPtr.withForeignPtr' -- does a 'touchForeignPtr' after it -- executes the user action. --- +-- -- Note that this function should not be used to express dependencies -- between finalizers on 'ForeignPtr's. For example, if the finalizer -- for a 'ForeignPtr' @F1@ calls 'touchForeignPtr' on a second diff --git a/Foreign/Marshal.hs b/Foreign/Marshal.hs index deb19babb70c54f211149e717b4f2b08903f4f47..042907861c9723edd54b19f6ebebf36e969f3f44 100644 --- a/Foreign/Marshal.hs +++ b/Foreign/Marshal.hs @@ -27,7 +27,7 @@ import "base" System.IO.Unsafe Sometimes an external entity is a pure function, except that it passes arguments and/or results via pointers. The function @unsafeLocalState@ permits the packaging of such entities as pure -functions. +functions. The only IO operations allowed in the IO action passed to @unsafeLocalState@ are (a) local allocation (@alloca@, @allocaBytes@ diff --git a/Foreign/Marshal/Error.hs b/Foreign/Marshal/Error.hs index d65ae5693b856523ed4c55e6bb3d3789f7a2a820..c5467606b208c50d28b6474f1a258d600358c22f 100644 --- a/Foreign/Marshal/Error.hs +++ b/Foreign/Marshal/Error.hs @@ -6,7 +6,7 @@ module Foreign.Marshal.Error ( throwIf, -- :: (a -> Bool) -> (a -> String) -> IO a -> IO a throwIf_, -- :: (a -> Bool) -> (a -> String) -> IO a -> IO () - throwIfNeg, -- :: (Ord a, Num a) + throwIfNeg, -- :: (Ord a, Num a) -- => (a -> String) -> IO a -> IO a throwIfNeg_, -- :: (Ord a, Num a) -- => (a -> String) -> IO a -> IO () diff --git a/System/Exit.hs b/System/Exit.hs index 8dba29ffdb5d9d0046b3df9c47a96b20d47f647f..81bb75ca4fbd502658ace4ac67a2b67c6282fe6d 100644 --- a/System/Exit.hs +++ b/System/Exit.hs @@ -31,7 +31,7 @@ import qualified "base" System.Exit as Base {- | Computation @'exitWith' code@ terminates the program, returning @code@ -to the program's caller. +to the program's caller. The caller may interpret the return code as it wishes, but the program should return 'ExitSuccess' to mean normal completion, and @'ExitFailure' n@ to mean that the program encountered a problem from diff --git a/System/IO.hs b/System/IO.hs index c09559b752e5be2bd96a403a392b1bfb0e580289..2ef2a8e2102cf077e5640b17f78be965ac7081b8 100644 --- a/System/IO.hs +++ b/System/IO.hs @@ -118,7 +118,7 @@ module System.IO ( interact, -- :: (String -> String) -> IO () putChar, -- :: Char -> IO () - putStr, -- :: String -> IO () + putStr, -- :: String -> IO () putStrLn, -- :: String -> IO () print, -- :: Show a => a -> IO () getChar, -- :: IO Char diff --git a/System/IO/Error.hs b/System/IO/Error.hs index afa9eb71ca7b49577bd344d1ba68fb2b62a16482..d3b3d5141c18757051a9099c6756356ecc335ed5 100644 --- a/System/IO/Error.hs +++ b/System/IO/Error.hs @@ -19,9 +19,9 @@ module System.IO.Error ( isAlreadyExistsError, -- :: IOError -> Bool isDoesNotExistError, isAlreadyInUseError, - isFullError, + isFullError, isEOFError, - isIllegalOperation, + isIllegalOperation, isPermissionError, isUserError, @@ -38,7 +38,7 @@ module System.IO.Error ( alreadyInUseErrorType, fullErrorType, eofErrorType, - illegalOperationErrorType, + illegalOperationErrorType, permissionErrorType, userErrorType,