import {-# SOURCE #-} Error
import STBase
import PrelTup
+import PrelMaybe
import Addr
import PackBase ( unpackCString )
import PrelBase
import IOBase
import Unsafe ( unsafePerformIO )
import PrelTup
+import PrelMaybe
import PrelBase
import GHC
import Addr
%*********************************************************
%* *
-\subsection{Type @Maybe@}
-%* *
-%*********************************************************
-
-\begin{code}
-data Maybe a = Nothing | Just a deriving (Eq, Ord, Show {- Read -})
-
-maybe :: b -> (a -> b) -> Maybe a -> b
-maybe n f Nothing = n
-maybe n f (Just x) = f x
-
-instance Functor Maybe where
- map f Nothing = Nothing
- map f (Just a) = Just (f a)
-
-instance Monad Maybe where
- (Just x) >>= k = k x
- Nothing >>= k = Nothing
-
- (Just x) >> k = k
- Nothing >> k = Nothing
-
- return = Just
-
-instance MonadZero Maybe where
- zero = Nothing
-
-instance MonadPlus Maybe where
- Nothing ++ ys = ys
- xs ++ ys = xs
-\end{code}
-
-
-%*********************************************************
-%* *
\subsection{The @()@ type}
%* *
%*********************************************************
%*********************************************************
%* *
-\subsection{Type @Either@}
-%* *
-%*********************************************************
-
-\begin{code}
-data Either a b = Left a | Right b deriving (Eq, Ord, Show {- Read -} )
-
-either :: (a -> c) -> (b -> c) -> Either a b -> c
-either f g (Left x) = f x
-either f g (Right y) = g y
-\end{code}
-
-
-%*********************************************************
-%* *
\subsection{Type @Ordering@}
%* *
%*********************************************************
--- /dev/null
+%
+% (c) The GRASP/AQUA Project, Glasgow University, 1992-1997
+%
+\section[PrelEither]{Module @PrelEither@}
+
+The @Either@ Type.
+
+\begin{code}
+{-# OPTIONS -fno-implicit-prelude #-}
+
+module PrelEither where
+
+import PrelBase
+
+data Either a b = Left a | Right b deriving (Eq, Ord, Show {- Read -} )
+
+either :: (a -> c) -> (b -> c) -> Either a b -> c
+either f g (Left x) = f x
+either f g (Right y) = g y
+\end{code}
import {-# SOURCE #-} Error ( error )
import PrelTup
+import PrelMaybe
import PrelBase
infix 4 `elem`, `notElem`
--- /dev/null
+%
+% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
+%
+\section[PrelMaybe]{Module @PrelMaybe@}
+
+The @Maybe@ type.
+
+\begin{code}
+{-# OPTIONS -fno-implicit-prelude #-}
+
+module PrelMaybe where
+
+import PrelBase
+
+data Maybe a = Nothing | Just a deriving (Eq, Ord, Show {- Read -})
+
+maybe :: b -> (a -> b) -> Maybe a -> b
+maybe n f Nothing = n
+maybe n f (Just x) = f x
+
+instance Functor Maybe where
+ map f Nothing = Nothing
+ map f (Just a) = Just (f a)
+
+instance Monad Maybe where
+ (Just x) >>= k = k x
+ Nothing >>= k = Nothing
+
+ (Just x) >> k = k
+ Nothing >> k = Nothing
+
+ return = Just
+
+instance MonadZero Maybe where
+ zero = Nothing
+
+instance MonadPlus Maybe where
+ Nothing ++ ys = ys
+ xs ++ ys = xs
+\end{code}
+
+
+
+
import GHC
import {-# SOURCE #-} Error ( error )
import PrelList
+import PrelMaybe
import ArrBase ( Array, array, (!) )
import Unsafe ( unsafePerformIO )
in doDiv (i `div` (b^l)) l
\end{code}
-
%*********************************************************
%* *
\subsection{Numeric primops}
import PrelNum
import PrelList
import PrelTup
+import PrelMaybe
+import PrelEither
import PrelBase
\end{code}
import IOHandle -- much of the real stuff is in here
import PackBase ( unpackNBytesST )
import PrelBase
+import PrelMaybe
+import PrelEither
import GHC
import Addr
import Error ( error )
import Monad ( filter )
import PrelList
+import PrelMaybe
import PrelBase
\end{code}
) where
import PrelBase
+import PrelMaybe
import ArrBase
import PrelNum
import PrelRead
import PrelRead
import PrelNum
import PrelTup
+import PrelMaybe
+import PrelEither
import Monad
import Maybe
import Error ( error )