1 {-# OPTIONS -fno-implicit-prelude #-}
2 -----------------------------------------------------------------------------
5 -- Copyright : (c) The University of Glasgow 2002
6 -- License : BSD-style (see the file libraries/base/LICENSE)
8 -- Maintainer : libraries@haskell.org
9 -- Stability : provisional
10 -- Portability : portable
12 -- Odds and ends, mostly functions for reading and showing
13 -- RealFloat-like kind of values.
15 -----------------------------------------------------------------------------
19 fromRat, -- :: (RealFloat a) => Rational -> a
20 showSigned, -- :: (Real a) => (a -> ShowS) -> Int -> a -> ShowS
21 readSigned, -- :: (Real a) => ReadS a -> ReadS a
23 readInt, -- :: (Integral a) => a -> (Char -> Bool)
24 -- -> (Char -> Int) -> ReadS a
25 readDec, -- :: (Integral a) => ReadS a
26 readOct, -- :: (Integral a) => ReadS a
27 readHex, -- :: (Integral a) => ReadS a
29 showInt, -- :: Integral a => a -> ShowS
30 showIntAtBase
, -- :: Integral a => a -> (a -> Char) -> a -> ShowS
31 showHex
, -- :: Integral a => a -> ShowS
32 showOct
, -- :: Integral a => a -> ShowS
33 showBin
, -- :: Integral a => a -> ShowS
35 showEFloat, -- :: (RealFloat a) => Maybe Int -> a -> ShowS
36 showFFloat, -- :: (RealFloat a) => Maybe Int -> a -> ShowS
37 showGFloat, -- :: (RealFloat a) => Maybe Int -> a -> ShowS
38 showFloat, -- :: (RealFloat a) => a -> ShowS
39 readFloat, -- :: (RealFloat a) => ReadS a
41 floatToDigits, -- :: (RealFloat a) => Integer -> a -> ([Int], Int)
42 lexDigits, -- :: ReadS String
48 #ifdef __GLASGOW_HASKELL__
56 import Text
.ParserCombinators
.ReadP
( ReadP
, readP_to_S
, pfail
)
57 import qualified Text
.Read.Lex
as L
65 #ifdef __GLASGOW_HASKELL__
66 -- -----------------------------------------------------------------------------
69 readInt :: Num a
=> a
-> (Char -> Bool) -> (Char -> Int) -> ReadS a
70 readInt base
isDigit valDigit
= readP_to_S
(L
.readIntP base
isDigit valDigit
)
72 readOct, readDec, readHex :: Num a
=> ReadS a
73 readOct = readP_to_S L
.readOctP
74 readDec = readP_to_S L
.readDecP
75 readHex = readP_to_S L
.readHexP
77 readFloat :: RealFrac a
=> ReadS a
78 readFloat = readP_to_S readFloatP
80 readFloatP
:: RealFrac a
=> ReadP a
84 L
.Rat y
-> return (fromRational y
)
85 L
.Int i
-> return (fromInteger i
)
88 -- It's turgid to have readSigned work using list comprehensions,
89 -- but it's specified as a ReadS to ReadS transformer
90 -- With a bit of luck no one will use it.
91 readSigned :: (Real a
) => ReadS a
-> ReadS a
92 readSigned readPos
= readParen False read'
93 where read' r
= read'' r
++
100 (n
,"") <- readPos str
103 -- -----------------------------------------------------------------------------
106 showInt :: Integral a
=> a
-> ShowS
108 | n
< 0 = error "Numeric.showInt: can't show negative numbers"
109 |
otherwise = go n cs
112 | n
< 10 = case unsafeChr
(ord '0' + fromIntegral n
) of
114 |
otherwise = case unsafeChr
(ord '0' + fromIntegral r
) of
115 c
@(C
# _
) -> go q
(c
:cs
)
117 (q
,r
) = n `
quotRem`
10
119 -- Controlling the format and precision of floats. The code that
120 -- implements the formatting itself is in @PrelNum@ to avoid
121 -- mutual module deps.
123 {-# SPECIALIZE showEFloat ::
124 Maybe Int -> Float -> ShowS,
125 Maybe Int -> Double -> ShowS #-}
126 {-# SPECIALIZE showFFloat ::
127 Maybe Int -> Float -> ShowS,
128 Maybe Int -> Double -> ShowS #-}
129 {-# SPECIALIZE showGFloat ::
130 Maybe Int -> Float -> ShowS,
131 Maybe Int -> Double -> ShowS #-}
133 showEFloat :: (RealFloat a
) => Maybe Int -> a
-> ShowS
134 showFFloat :: (RealFloat a
) => Maybe Int -> a
-> ShowS
135 showGFloat :: (RealFloat a
) => Maybe Int -> a
-> ShowS
137 showEFloat d x
= showString (formatRealFloat FFExponent d x
)
138 showFFloat d x
= showString (formatRealFloat FFFixed d x
)
139 showGFloat d x
= showString (formatRealFloat FFGeneric d x
)
140 #endif
/* __GLASGOW_HASKELL__
*/
142 -- ---------------------------------------------------------------------------
143 -- Integer printing functions
145 showIntAtBase
:: Integral a
=> a
-> (a
-> Char) -> a
-> ShowS
146 showIntAtBase base toChr n r
147 | n
< 0 = error ("Numeric.showIntAtBase: applied to negative number " ++ show n
)
149 case quotRem n base
of { (n
', d
) ->
151 seq c
$ -- stricter than necessary
155 if n
' == 0 then r
' else showIntAtBase base toChr n
' r
'
158 showHex
:: Integral a
=> a
-> ShowS
161 showIntAtBase
16 (toChrHex
) n r
164 | d
< 10 = chr (ord '0' + fromIntegral d
)
165 |
otherwise = chr (ord 'a
' + fromIntegral (d
- 10))
167 showOct
:: Integral a
=> a
-> ShowS
170 showIntAtBase
8 (toChrOct
) n r
171 where toChrOct d
= chr (ord '0' + fromIntegral d
)
173 showBin
:: Integral a
=> a
-> ShowS
176 showIntAtBase
2 (toChrOct
) n r
177 where toChrOct d
= chr (ord '0' + fromIntegral d
)