Skip to content
Snippets Groups Projects
Commit 3dae85df authored by sof's avatar sof
Browse files

[project @ 1998-01-22 11:07:36 by sof]

Remove duplicates from export lists.
parent 169b432a
No related merge requests found
%
% (c) The AQUA Project, Glasgow University, 1997
% (c) The AQUA Project, Glasgow University, 1997-98
%
\section[Numeric]{Numeric interface}
......@@ -40,9 +40,9 @@ import PrelRead
\end{code}
%*********************************************************
%* *
\subsection{Signatures}
%* *
%* *
\subsection[Numeric-signatures]{Signatures}
%* *
%*********************************************************
Interface on offer:
......@@ -103,11 +103,9 @@ showHex n r =
showString "0x" $
showIntAtBase 16 (toChrHex) n r
where
toChrHex d =
if d < 10 then
chr (ord_0 + fromIntegral d)
else
chr (ord 'a' + fromIntegral (d - 10))
toChrHex d
| d < 10 = chr (ord_0 + fromIntegral d)
| otherwise = chr (ord 'a' + fromIntegral (d - 10))
showOct :: Integral a => a -> ShowS
showOct n r =
......@@ -117,6 +115,10 @@ showOct n r =
\end{code}
Controlling the format and precision of floats. The code that
implements the formatting itself is in @PrelNum@ to avoid
mutual module deps.
\begin{code}
showEFloat :: (RealFloat a) => Maybe Int -> a -> ShowS
showFFloat :: (RealFloat a) => Maybe Int -> a -> ShowS
......@@ -127,6 +129,3 @@ showFFloat d x = showString (formatRealFloat FFFixed d x)
showGFloat d x = showString (formatRealFloat FFGeneric d x)
\end{code}
......@@ -19,7 +19,6 @@ module Prelude (
Bounded(..),
Enum(..), succ, pred,
Show(..), ShowS, shows, show, showChar, showString, showParen,
Num(..),
Eval(..), seq, strict,
Bool(..), (&&), (||), not, otherwise,
Char, String, Int, Integer, Float, Double, Void,
......@@ -47,7 +46,7 @@ module Prelude (
Ratio, Rational,
(%), numerator, denominator, approxRational,
Num((+), (-), (*), negate, abs, signum, fromInteger),
Num((+), (-), (*), negate, abs, signum, fromInteger, fromInt{-glaExt-}),
Real(toRational),
Integral(quot, rem, div, mod, quotRem, divMod, toInteger, toInt{-partain-}),
Fractional((/), recip, fromRational),
......
......@@ -13,15 +13,21 @@ its use of Coordinated Universal Time (UTC).
module Time
(
CalendarTime(..),
Month,
Day,
CalendarTime(CalendarTime),
TimeDiff(TimeDiff),
ClockTime(..), -- non-standard, lib. report gives this as abstract
getClockTime, addToClockTime, diffClockTimes,
toCalendarTime, toUTCTime, toClockTime,
calendarTimeToString, formatCalendarTime
getClockTime,
addToClockTime,
diffClockTimes,
toCalendarTime,
toUTCTime,
toClockTime,
calendarTimeToString,
formatCalendarTime
) where
import PrelBase
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment