Fix for hGetBufSome
[ghc-base.git] / Numeric.hs
1 {-# OPTIONS_GHC -XNoImplicitPrelude #-}
2 -----------------------------------------------------------------------------
3 -- |
4 -- Module      :  Numeric
5 -- Copyright   :  (c) The University of Glasgow 2002
6 -- License     :  BSD-style (see the file libraries/base/LICENSE)
7 -- 
8 -- Maintainer  :  libraries@haskell.org
9 -- Stability   :  provisional
10 -- Portability :  portable
11 --
12 -- Odds and ends, mostly functions for reading and showing
13 -- 'RealFloat'-like kind of values.
14 --
15 -----------------------------------------------------------------------------
16
17 module Numeric (
18
19         -- * Showing
20
21         showSigned,       -- :: (Real a) => (a -> ShowS) -> Int -> a -> ShowS
22
23         showIntAtBase,    -- :: Integral a => a -> (a -> Char) -> a -> ShowS
24         showInt,          -- :: Integral a => a -> ShowS
25         showHex,          -- :: Integral a => a -> ShowS
26         showOct,          -- :: Integral a => a -> ShowS
27
28         showEFloat,       -- :: (RealFloat a) => Maybe Int -> a -> ShowS
29         showFFloat,       -- :: (RealFloat a) => Maybe Int -> a -> ShowS
30         showGFloat,       -- :: (RealFloat a) => Maybe Int -> a -> ShowS
31         showFloat,        -- :: (RealFloat a) => a -> ShowS
32
33         floatToDigits,    -- :: (RealFloat a) => Integer -> a -> ([Int], Int)
34
35         -- * Reading
36
37         -- | /NB:/ 'readInt' is the \'dual\' of 'showIntAtBase',
38         -- and 'readDec' is the \`dual\' of 'showInt'.
39         -- The inconsistent naming is a historical accident.
40
41         readSigned,       -- :: (Real a) => ReadS a -> ReadS a
42
43         readInt,          -- :: (Integral a) => a -> (Char -> Bool)
44                           --         -> (Char -> Int) -> ReadS a
45         readDec,          -- :: (Integral a) => ReadS a
46         readOct,          -- :: (Integral a) => ReadS a
47         readHex,          -- :: (Integral a) => ReadS a
48
49         readFloat,        -- :: (RealFloat a) => ReadS a
50
51         lexDigits,        -- :: ReadS String
52
53         -- * Miscellaneous
54
55         fromRat,          -- :: (RealFloat a) => Rational -> a
56
57         ) where
58
59 #ifdef __GLASGOW_HASKELL__
60 import GHC.Base
61 import GHC.Read
62 import GHC.Real
63 import GHC.Float
64 import GHC.Num
65 import GHC.Show
66 import Data.Maybe
67 import Text.ParserCombinators.ReadP( ReadP, readP_to_S, pfail )
68 import qualified Text.Read.Lex as L
69 #else
70 import Data.Char
71 #endif
72
73 #ifdef __HUGS__
74 import Hugs.Prelude
75 import Hugs.Numeric
76 #endif
77
78 #ifdef __GLASGOW_HASKELL__
79 -- -----------------------------------------------------------------------------
80 -- Reading
81
82 -- | Reads an /unsigned/ 'Integral' value in an arbitrary base.
83 readInt :: Num a
84   => a                  -- ^ the base
85   -> (Char -> Bool)     -- ^ a predicate distinguishing valid digits in this base
86   -> (Char -> Int)      -- ^ a function converting a valid digit character to an 'Int'
87   -> ReadS a
88 readInt base isDigit valDigit = readP_to_S (L.readIntP base isDigit valDigit)
89
90 -- | Read an unsigned number in octal notation.
91 readOct :: Num a => ReadS a
92 readOct = readP_to_S L.readOctP
93
94 -- | Read an unsigned number in decimal notation.
95 readDec :: Num a => ReadS a
96 readDec = readP_to_S L.readDecP
97
98 -- | Read an unsigned number in hexadecimal notation.
99 -- Both upper or lower case letters are allowed.
100 readHex :: Num a => ReadS a
101 readHex = readP_to_S L.readHexP 
102
103 -- | Reads an /unsigned/ 'RealFrac' value,
104 -- expressed in decimal scientific notation.
105 readFloat :: RealFrac a => ReadS a
106 readFloat = readP_to_S readFloatP
107
108 readFloatP :: RealFrac a => ReadP a
109 readFloatP =
110   do tok <- L.lex
111      case tok of
112        L.Rat y  -> return (fromRational y)
113        L.Int i  -> return (fromInteger i)
114        _        -> pfail
115
116 -- It's turgid to have readSigned work using list comprehensions,
117 -- but it's specified as a ReadS to ReadS transformer
118 -- With a bit of luck no one will use it.
119
120 -- | Reads a /signed/ 'Real' value, given a reader for an unsigned value.
121 readSigned :: (Real a) => ReadS a -> ReadS a
122 readSigned readPos = readParen False read'
123                      where read' r  = read'' r ++
124                                       (do
125                                         ("-",s) <- lex r
126                                         (x,t)   <- read'' s
127                                         return (-x,t))
128                            read'' r = do
129                                (str,s) <- lex r
130                                (n,"")  <- readPos str
131                                return (n,s)
132
133 -- -----------------------------------------------------------------------------
134 -- Showing
135
136 -- | Show /non-negative/ 'Integral' numbers in base 10.
137 showInt :: Integral a => a -> ShowS
138 showInt n0 cs0
139     | n0 < 0    = error "Numeric.showInt: can't show negative numbers"
140     | otherwise = go n0 cs0
141     where
142     go n cs
143         | n < 10    = case unsafeChr (ord '0' + fromIntegral n) of
144             c@(C# _) -> c:cs
145         | otherwise = case unsafeChr (ord '0' + fromIntegral r) of
146             c@(C# _) -> go q (c:cs)
147         where
148         (q,r) = n `quotRem` 10
149
150 -- Controlling the format and precision of floats. The code that
151 -- implements the formatting itself is in @PrelNum@ to avoid
152 -- mutual module deps.
153
154 {-# SPECIALIZE showEFloat ::
155         Maybe Int -> Float  -> ShowS,
156         Maybe Int -> Double -> ShowS #-}
157 {-# SPECIALIZE showFFloat ::
158         Maybe Int -> Float  -> ShowS,
159         Maybe Int -> Double -> ShowS #-}
160 {-# SPECIALIZE showGFloat ::
161         Maybe Int -> Float  -> ShowS,
162         Maybe Int -> Double -> ShowS #-}
163
164 -- | Show a signed 'RealFloat' value
165 -- using scientific (exponential) notation (e.g. @2.45e2@, @1.5e-3@).
166 --
167 -- In the call @'showEFloat' digs val@, if @digs@ is 'Nothing',
168 -- the value is shown to full precision; if @digs@ is @'Just' d@,
169 -- then at most @d@ digits after the decimal point are shown.
170 showEFloat    :: (RealFloat a) => Maybe Int -> a -> ShowS
171
172 -- | Show a signed 'RealFloat' value
173 -- using standard decimal notation (e.g. @245000@, @0.0015@).
174 --
175 -- In the call @'showFFloat' digs val@, if @digs@ is 'Nothing',
176 -- the value is shown to full precision; if @digs@ is @'Just' d@,
177 -- then at most @d@ digits after the decimal point are shown.
178 showFFloat    :: (RealFloat a) => Maybe Int -> a -> ShowS
179
180 -- | Show a signed 'RealFloat' value
181 -- using standard decimal notation for arguments whose absolute value lies 
182 -- between @0.1@ and @9,999,999@, and scientific notation otherwise.
183 --
184 -- In the call @'showGFloat' digs val@, if @digs@ is 'Nothing',
185 -- the value is shown to full precision; if @digs@ is @'Just' d@,
186 -- then at most @d@ digits after the decimal point are shown.
187 showGFloat    :: (RealFloat a) => Maybe Int -> a -> ShowS
188
189 showEFloat d x =  showString (formatRealFloat FFExponent d x)
190 showFFloat d x =  showString (formatRealFloat FFFixed d x)
191 showGFloat d x =  showString (formatRealFloat FFGeneric d x)
192 #endif  /* __GLASGOW_HASKELL__ */
193
194 -- ---------------------------------------------------------------------------
195 -- Integer printing functions
196
197 -- | Shows a /non-negative/ 'Integral' number using the base specified by the
198 -- first argument, and the character representation specified by the second.
199 showIntAtBase :: Integral a => a -> (Int -> Char) -> a -> ShowS
200 showIntAtBase base toChr n0 r0
201   | base <= 1 = error ("Numeric.showIntAtBase: applied to unsupported base " ++ show base)
202   | n0 <  0   = error ("Numeric.showIntAtBase: applied to negative number " ++ show n0)
203   | otherwise = showIt (quotRem n0 base) r0
204    where
205     showIt (n,d) r = seq c $ -- stricter than necessary
206       case n of
207         0 -> r'
208         _ -> showIt (quotRem n base) r'
209      where
210       c  = toChr (fromIntegral d)
211       r' = c : r
212
213 -- | Show /non-negative/ 'Integral' numbers in base 16.
214 showHex :: Integral a => a -> ShowS
215 showHex = showIntAtBase 16 intToDigit
216
217 -- | Show /non-negative/ 'Integral' numbers in base 8.
218 showOct :: Integral a => a -> ShowS
219 showOct = showIntAtBase 8  intToDigit