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

[project @ 1998-01-30 16:57:33 by sof]

- NumExts: new hugs&ghc interface
- moved showOct and showHex from Numeric to NumExts
parent d2dafe12
No related branches found
No related tags found
No related merge requests found
%
% (c) The AQUA Project, Glasgow University, 1998
%
\section[NumExts]{Misc numeric bits}
\begin{code}
module NumExts
(
doubleToFloat -- :: Double -> Float
, floatToDouble -- :: Double -> Float
, showHex -- :: Integral a => a -> ShowS
, showOct -- :: Integral a => a -> ShowS
) where
import Char (ord, chr)
import PrelBase (ord_0)
import GlaExts
\end{code}
\begin{code}
doubleToFloat :: Double -> Float
doubleToFloat (D# d#) = F# (double2Float# d#)
floatToDouble :: Float -> Double
floatToDouble (F# f#) = D# (float2Double# f#)
showIntAtBase :: Integral a => a -> (a -> Char) -> a -> ShowS
showIntAtBase base toChr n r
| n < 0 = error ("NumExts.showIntAtBase: applied to negative number " ++ show n)
| otherwise =
case quotRem n base of { (n', d) ->
case toChr d of { C# c# -> -- stricter than necessary
let
r' = C# c# : r
in
if n' == 0 then r' else showIntAtBase base toChr n' r'
}}
showHex :: Integral a => a -> ShowS
showHex n r =
showString "0x" $
showIntAtBase 16 (toChrHex) n r
where
toChrHex d
| d < 10 = chr (ord_0 + fromIntegral d)
| otherwise = chr (ord 'a' + fromIntegral (d - 10))
showOct :: Integral a => a -> ShowS
showOct n r =
showString "0o" $
showIntAtBase 8 (toChrOct) n r
where toChrOct d = chr (ord_0 + fromIntegral d)
\end{code}
...@@ -18,7 +18,6 @@ module Numeric ...@@ -18,7 +18,6 @@ module Numeric
readInt, readInt,
readDec, readOct, readHex, readDec, readOct, readHex,
showDec, showOct, showHex,
showEFloat, showEFloat,
showFFloat, showFFloat,
...@@ -82,37 +81,6 @@ showInt n r ...@@ -82,37 +81,6 @@ showInt n r
if n' == 0 then r' else showInt n' r' if n' == 0 then r' else showInt n' r'
}} }}
showIntAtBase :: Integral a => a -> (a -> Char) -> a -> ShowS
showIntAtBase base toChr n r
= case quotRem n base of { (n', d) ->
case toChr d of { C# c# -> -- stricter than necessary
let
r' = C# c# : r
in
if n' == 0 then r' else showIntAtBase base toChr n' r'
}}
showDec :: Integral a => a -> ShowS
showDec n r =
showIntAtBase 10
(\ d -> chr (ord_0 + fromIntegral d))
n r
showHex :: Integral a => a -> ShowS
showHex n r =
showString "0x" $
showIntAtBase 16 (toChrHex) n r
where
toChrHex d
| d < 10 = chr (ord_0 + fromIntegral d)
| otherwise = chr (ord 'a' + fromIntegral (d - 10))
showOct :: Integral a => a -> ShowS
showOct n r =
showString "0o" $
showIntAtBase 8 (toChrOct) n r
where toChrOct d = chr (ord_0 + fromIntegral d)
\end{code} \end{code}
Controlling the format and precision of floats. The code that Controlling the format and precision of floats. The code that
......
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