{-# LANGUAGE DeriveGeneric #-}
module Ide.Plugin.Conversion (
alternateFormat
, hexRegex
, hexFloatRegex
, binaryRegex
, octalRegex
, decimalRegex
, numDecimalRegex
, matchLineRegex
, toFormatTypes
, FormatType
, generateNumDecimal
, toNumDecimal
, toBinary
, toOctal
, toHex
, toHexFloat
, toFloatDecimal
, toFloatExpDecimal
) where
import Data.Char (toUpper)
import Data.List (delete, dropWhileEnd)
import Data.Maybe (mapMaybe)
import Data.Ratio (denominator, numerator)
import Data.Text (Text)
import qualified Data.Text as T
import Development.IDE.Graph.Classes (NFData)
import GHC.Generics (Generic)
import GHC.LanguageExtensions.Type (Extension (..))
import GHC.Show (intToDigit)
import Ide.Plugin.Literals (Literal (..), getSrcText)
import Numeric
import Text.Regex.TDFA ((=~))
data FormatType = IntFormat IntFormatType
| FracFormat FracFormatType
| AnyFormat AnyFormatType
| NoFormat
deriving (Int -> FormatType -> ShowS
[FormatType] -> ShowS
FormatType -> String
(Int -> FormatType -> ShowS)
-> (FormatType -> String)
-> ([FormatType] -> ShowS)
-> Show FormatType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FormatType] -> ShowS
$cshowList :: [FormatType] -> ShowS
show :: FormatType -> String
$cshow :: FormatType -> String
showsPrec :: Int -> FormatType -> ShowS
$cshowsPrec :: Int -> FormatType -> ShowS
Show, FormatType -> FormatType -> Bool
(FormatType -> FormatType -> Bool)
-> (FormatType -> FormatType -> Bool) -> Eq FormatType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FormatType -> FormatType -> Bool
$c/= :: FormatType -> FormatType -> Bool
== :: FormatType -> FormatType -> Bool
$c== :: FormatType -> FormatType -> Bool
Eq, (forall x. FormatType -> Rep FormatType x)
-> (forall x. Rep FormatType x -> FormatType) -> Generic FormatType
forall x. Rep FormatType x -> FormatType
forall x. FormatType -> Rep FormatType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FormatType x -> FormatType
$cfrom :: forall x. FormatType -> Rep FormatType x
Generic)
instance NFData FormatType
data IntFormatType = HexFormat
| OctalFormat
| BinaryFormat
| NumDecimalFormat
deriving (Int -> IntFormatType -> ShowS
[IntFormatType] -> ShowS
IntFormatType -> String
(Int -> IntFormatType -> ShowS)
-> (IntFormatType -> String)
-> ([IntFormatType] -> ShowS)
-> Show IntFormatType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IntFormatType] -> ShowS
$cshowList :: [IntFormatType] -> ShowS
show :: IntFormatType -> String
$cshow :: IntFormatType -> String
showsPrec :: Int -> IntFormatType -> ShowS
$cshowsPrec :: Int -> IntFormatType -> ShowS
Show, IntFormatType -> IntFormatType -> Bool
(IntFormatType -> IntFormatType -> Bool)
-> (IntFormatType -> IntFormatType -> Bool) -> Eq IntFormatType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IntFormatType -> IntFormatType -> Bool
$c/= :: IntFormatType -> IntFormatType -> Bool
== :: IntFormatType -> IntFormatType -> Bool
$c== :: IntFormatType -> IntFormatType -> Bool
Eq, (forall x. IntFormatType -> Rep IntFormatType x)
-> (forall x. Rep IntFormatType x -> IntFormatType)
-> Generic IntFormatType
forall x. Rep IntFormatType x -> IntFormatType
forall x. IntFormatType -> Rep IntFormatType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IntFormatType x -> IntFormatType
$cfrom :: forall x. IntFormatType -> Rep IntFormatType x
Generic)
instance NFData IntFormatType
data FracFormatType = HexFloatFormat
| ExponentFormat
deriving (Int -> FracFormatType -> ShowS
[FracFormatType] -> ShowS
FracFormatType -> String
(Int -> FracFormatType -> ShowS)
-> (FracFormatType -> String)
-> ([FracFormatType] -> ShowS)
-> Show FracFormatType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FracFormatType] -> ShowS
$cshowList :: [FracFormatType] -> ShowS
show :: FracFormatType -> String
$cshow :: FracFormatType -> String
showsPrec :: Int -> FracFormatType -> ShowS
$cshowsPrec :: Int -> FracFormatType -> ShowS
Show, FracFormatType -> FracFormatType -> Bool
(FracFormatType -> FracFormatType -> Bool)
-> (FracFormatType -> FracFormatType -> Bool) -> Eq FracFormatType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FracFormatType -> FracFormatType -> Bool
$c/= :: FracFormatType -> FracFormatType -> Bool
== :: FracFormatType -> FracFormatType -> Bool
$c== :: FracFormatType -> FracFormatType -> Bool
Eq, (forall x. FracFormatType -> Rep FracFormatType x)
-> (forall x. Rep FracFormatType x -> FracFormatType)
-> Generic FracFormatType
forall x. Rep FracFormatType x -> FracFormatType
forall x. FracFormatType -> Rep FracFormatType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FracFormatType x -> FracFormatType
$cfrom :: forall x. FracFormatType -> Rep FracFormatType x
Generic)
instance NFData FracFormatType
data AnyFormatType = DecimalFormat
deriving (Int -> AnyFormatType -> ShowS
[AnyFormatType] -> ShowS
AnyFormatType -> String
(Int -> AnyFormatType -> ShowS)
-> (AnyFormatType -> String)
-> ([AnyFormatType] -> ShowS)
-> Show AnyFormatType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AnyFormatType] -> ShowS
$cshowList :: [AnyFormatType] -> ShowS
show :: AnyFormatType -> String
$cshow :: AnyFormatType -> String
showsPrec :: Int -> AnyFormatType -> ShowS
$cshowsPrec :: Int -> AnyFormatType -> ShowS
Show, AnyFormatType -> AnyFormatType -> Bool
(AnyFormatType -> AnyFormatType -> Bool)
-> (AnyFormatType -> AnyFormatType -> Bool) -> Eq AnyFormatType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnyFormatType -> AnyFormatType -> Bool
$c/= :: AnyFormatType -> AnyFormatType -> Bool
== :: AnyFormatType -> AnyFormatType -> Bool
$c== :: AnyFormatType -> AnyFormatType -> Bool
Eq, (forall x. AnyFormatType -> Rep AnyFormatType x)
-> (forall x. Rep AnyFormatType x -> AnyFormatType)
-> Generic AnyFormatType
forall x. Rep AnyFormatType x -> AnyFormatType
forall x. AnyFormatType -> Rep AnyFormatType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AnyFormatType x -> AnyFormatType
$cfrom :: forall x. AnyFormatType -> Rep AnyFormatType x
Generic)
instance NFData AnyFormatType
alternateFormat :: [FormatType] -> Literal -> [Text]
alternateFormat :: [FormatType] -> Literal -> [Text]
alternateFormat [FormatType]
fmts Literal
lit = case Literal
lit of
IntLiteral RealSrcSpan
_ Text
_ Integer
val -> (FormatType -> [Text]) -> [FormatType] -> [Text]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Integer -> FormatType -> [Text]
alternateIntFormat Integer
val) (Literal -> [FormatType] -> [FormatType]
removeCurrentFormat Literal
lit [FormatType]
fmts)
FracLiteral RealSrcSpan
_ Text
_ Rational
val -> if Rational -> Integer
forall a. Ratio a -> a
denominator Rational
val Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
1
then (FormatType -> [Text]) -> [FormatType] -> [Text]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Integer -> FormatType -> [Text]
alternateIntFormat (Rational -> Integer
forall a. Ratio a -> a
numerator Rational
val)) (Literal -> [FormatType] -> [FormatType]
removeCurrentFormat Literal
lit [FormatType]
fmts)
else (FormatType -> [Text]) -> [FormatType] -> [Text]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Rational -> FormatType -> [Text]
alternateFracFormat Rational
val) (Literal -> [FormatType] -> [FormatType]
removeCurrentFormat Literal
lit [FormatType]
fmts)
alternateIntFormat :: Integer -> FormatType -> [Text]
alternateIntFormat :: Integer -> FormatType -> [Text]
alternateIntFormat Integer
val FormatType
fmt = case FormatType
fmt of
IntFormat IntFormatType
ift -> case IntFormatType
ift of
IntFormatType
HexFormat -> [String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> String
forall a. (Integral a, Show a) => a -> String
toHex Integer
val]
IntFormatType
OctalFormat -> [String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> String
forall a. (Integral a, Show a) => a -> String
toOctal Integer
val]
IntFormatType
BinaryFormat -> [String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> String
forall a. (Integral a, Show a) => a -> String
toBinary Integer
val]
IntFormatType
NumDecimalFormat -> Integer -> [Text]
generateNumDecimal Integer
val
AnyFormat AnyFormatType
DecimalFormat -> [String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> String
forall a. Integral a => a -> String
toDecimal Integer
val]
FormatType
_ -> []
alternateFracFormat :: Rational -> FormatType -> [Text]
alternateFracFormat :: Rational -> FormatType -> [Text]
alternateFracFormat Rational
val FormatType
fmt = case FormatType
fmt of
AnyFormat AnyFormatType
DecimalFormat -> [String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Double -> String
forall a. RealFloat a => a -> String
toFloatDecimal (Rational -> Double
forall a. Fractional a => Rational -> a
fromRational Rational
val)]
FracFormat FracFormatType
ExponentFormat -> [String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Double -> String
forall a. RealFloat a => a -> String
toFloatExpDecimal (Rational -> Double
forall a. Fractional a => Rational -> a
fromRational Rational
val)]
FracFormat FracFormatType
HexFloatFormat -> [String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Double -> String
forall a. RealFloat a => a -> String
toHexFloat (Rational -> Double
forall a. Fractional a => Rational -> a
fromRational Rational
val)]
FormatType
_ -> []
removeCurrentFormat :: Literal -> [FormatType] -> [FormatType]
removeCurrentFormat :: Literal -> [FormatType] -> [FormatType]
removeCurrentFormat Literal
lit [FormatType]
fmts = let srcText :: Text
srcText = Literal -> Text
getSrcText Literal
lit
in ([FormatType] -> FormatType -> [FormatType])
-> [FormatType] -> [FormatType] -> [FormatType]
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl ((FormatType -> [FormatType] -> [FormatType])
-> [FormatType] -> FormatType -> [FormatType]
forall a b c. (a -> b -> c) -> b -> a -> c
flip FormatType -> [FormatType] -> [FormatType]
forall a. Eq a => a -> [a] -> [a]
delete) [FormatType]
fmts (Text -> [FormatType]
sourceToFormatType Text
srcText)
hexRegex :: Text
hexRegex :: Text
hexRegex = Text
"0[xX][a-fA-F0-9]+"
hexFloatRegex :: Text
hexFloatRegex :: Text
hexFloatRegex = Text
"0[xX][a-fA-F0-9]+(\\.)?[a-fA-F0-9]*(p[+-]?[0-9]+)?"
binaryRegex :: Text
binaryRegex :: Text
binaryRegex = Text
"0[bB][0|1]+"
octalRegex :: Text
octalRegex :: Text
octalRegex = Text
"0[oO][0-8]+"
decimalRegex :: Text
decimalRegex :: Text
decimalRegex = Text
"[0-9]+(\\.[0-9]+)?"
numDecimalRegex :: Text
numDecimalRegex :: Text
numDecimalRegex = Text
"[0-9]+\\.[0-9]+[eE][+-]?[0-9]+"
matchLineRegex :: Text -> Text
matchLineRegex :: Text -> Text
matchLineRegex Text
regex = Text
"^" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
regex Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"$"
sourceToFormatType :: Text -> [FormatType]
sourceToFormatType :: Text -> [FormatType]
sourceToFormatType Text
srcText
| Text
srcText Text -> Text -> Bool
forall source source1 target.
(RegexMaker Regex CompOption ExecOption source,
RegexContext Regex source1 target) =>
source1 -> source -> target
=~ Text -> Text
matchLineRegex Text
hexRegex = [IntFormatType -> FormatType
IntFormat IntFormatType
HexFormat]
| Text
srcText Text -> Text -> Bool
forall source source1 target.
(RegexMaker Regex CompOption ExecOption source,
RegexContext Regex source1 target) =>
source1 -> source -> target
=~ Text -> Text
matchLineRegex Text
hexFloatRegex = [FracFormatType -> FormatType
FracFormat FracFormatType
HexFloatFormat]
| Text
srcText Text -> Text -> Bool
forall source source1 target.
(RegexMaker Regex CompOption ExecOption source,
RegexContext Regex source1 target) =>
source1 -> source -> target
=~ Text -> Text
matchLineRegex Text
octalRegex = [IntFormatType -> FormatType
IntFormat IntFormatType
OctalFormat]
| Text
srcText Text -> Text -> Bool
forall source source1 target.
(RegexMaker Regex CompOption ExecOption source,
RegexContext Regex source1 target) =>
source1 -> source -> target
=~ Text -> Text
matchLineRegex Text
binaryRegex = [IntFormatType -> FormatType
IntFormat IntFormatType
BinaryFormat]
| Text
srcText Text -> Text -> Bool
forall source source1 target.
(RegexMaker Regex CompOption ExecOption source,
RegexContext Regex source1 target) =>
source1 -> source -> target
=~ Text -> Text
matchLineRegex Text
numDecimalRegex = [IntFormatType -> FormatType
IntFormat IntFormatType
NumDecimalFormat, FracFormatType -> FormatType
FracFormat FracFormatType
ExponentFormat]
| Bool
otherwise = [AnyFormatType -> FormatType
AnyFormat AnyFormatType
DecimalFormat]
toFormatTypes :: [Extension] -> [FormatType]
toFormatTypes :: [Extension] -> [FormatType]
toFormatTypes = [FormatType] -> [FormatType] -> [FormatType]
forall a. Semigroup a => a -> a -> a
(<>) [FormatType]
baseFormatTypes ([FormatType] -> [FormatType])
-> ([Extension] -> [FormatType]) -> [Extension] -> [FormatType]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Extension -> Maybe FormatType) -> [Extension] -> [FormatType]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Extension -> [(Extension, FormatType)] -> Maybe FormatType
forall a b. Eq a => a -> [(a, b)] -> Maybe b
`lookup` [(Extension, FormatType)]
numericPairs)
where
baseFormatTypes :: [FormatType]
baseFormatTypes = [IntFormatType -> FormatType
IntFormat IntFormatType
HexFormat, IntFormatType -> FormatType
IntFormat IntFormatType
OctalFormat, FracFormatType -> FormatType
FracFormat FracFormatType
ExponentFormat, AnyFormatType -> FormatType
AnyFormat AnyFormatType
DecimalFormat]
numericPairs :: [(Extension, FormatType)]
numericPairs :: [(Extension, FormatType)]
numericPairs = [(Extension
NumericUnderscores, FormatType
NoFormat), (Extension
NegativeLiterals, FormatType
NoFormat)] [(Extension, FormatType)]
-> [(Extension, FormatType)] -> [(Extension, FormatType)]
forall a. Semigroup a => a -> a -> a
<> [(Extension, FormatType)]
intPairs [(Extension, FormatType)]
-> [(Extension, FormatType)] -> [(Extension, FormatType)]
forall a. Semigroup a => a -> a -> a
<> [(Extension, FormatType)]
fracPairs
intPairs :: [(Extension, FormatType)]
intPairs :: [(Extension, FormatType)]
intPairs = [(Extension
BinaryLiterals, IntFormatType -> FormatType
IntFormat IntFormatType
BinaryFormat), (Extension
NumDecimals, IntFormatType -> FormatType
IntFormat IntFormatType
NumDecimalFormat)]
fracPairs :: [(Extension, FormatType)]
fracPairs :: [(Extension, FormatType)]
fracPairs = [(Extension
HexFloatLiterals, FracFormatType -> FormatType
FracFormat FracFormatType
HexFloatFormat)]
generateNumDecimal :: Integer -> [Text]
generateNumDecimal :: Integer -> [Text]
generateNumDecimal Integer
val = (Integer -> Text) -> [Integer] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Integer -> Integer -> Text
toNumDecimal Integer
val) ([Integer] -> [Text]) -> [Integer] -> [Text]
forall a b. (a -> b) -> a -> b
$ Int -> [Integer] -> [Integer]
forall a. Int -> [a] -> [a]
take Int
3 ([Integer] -> [Integer]) -> [Integer] -> [Integer]
forall a b. (a -> b) -> a -> b
$ (Integer -> Bool) -> [Integer] -> [Integer]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Integer
val Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= ) ([Integer] -> [Integer]) -> [Integer] -> [Integer]
forall a b. (a -> b) -> a -> b
$ (Integer -> Bool) -> [Integer] -> [Integer]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (\Integer
d -> (Integer
val Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`div` Integer
d) Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
1000) [Integer]
divisors
where
divisors :: [Integer]
divisors = Integer
10 Integer -> [Integer] -> [Integer]
forall a. a -> [a] -> [a]
: (Integer -> Integer) -> [Integer] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
map (Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
10) [Integer]
divisors
toNumDecimal :: Integer -> Integer -> Text
toNumDecimal :: Integer -> Integer -> Text
toNumDecimal Integer
val Integer
divisor = let (Integer
q, Integer
r) = Integer
val Integer -> Integer -> (Integer, Integer)
forall a. Integral a => a -> a -> (a, a)
`quotRem` Integer
divisor
numExponent :: Int
numExponent = String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (String -> Int) -> String -> Int
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
filter (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'0') ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Integer -> String
forall a. Show a => a -> String
show Integer
divisor
r' :: String
r' = (Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
dropWhileEnd (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'0') ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Integer -> String
forall a. Show a => a -> String
show Integer
r
r'' :: String
r'' = if String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
r' then String
"0" else String
r'
in String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> String
forall a. Show a => a -> String
show Integer
q String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"." String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
r'' String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"e" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show Int
numExponent
toBase :: (Num a, Ord a) => (a -> ShowS) -> String -> a -> String
toBase :: (a -> ShowS) -> String -> a -> String
toBase a -> ShowS
conv String
header a
n
| a
n a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0 = Char
'-' Char -> ShowS
forall a. a -> [a] -> [a]
: String
header String -> ShowS
forall a. Semigroup a => a -> a -> a
<> (Char -> Char) -> ShowS
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper (a -> ShowS
conv (a -> a
forall a. Num a => a -> a
abs a
n) String
"")
| Bool
otherwise = String
header String -> ShowS
forall a. Semigroup a => a -> a -> a
<> (Char -> Char) -> ShowS
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper (a -> ShowS
conv a
n String
"")
toOctal :: (Integral a, Show a) => a -> String
toOctal :: a -> String
toOctal = (a -> ShowS) -> String -> a -> String
forall a. (Num a, Ord a) => (a -> ShowS) -> String -> a -> String
toBase a -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showOct String
"0o"
toDecimal :: Integral a => a -> String
toDecimal :: a -> String
toDecimal = (a -> ShowS) -> String -> a -> String
forall a. (Num a, Ord a) => (a -> ShowS) -> String -> a -> String
toBase a -> ShowS
forall a. Integral a => a -> ShowS
showInt String
""
toBinary :: (Integral a, Show a) => a -> String
toBinary :: a -> String
toBinary = (a -> ShowS) -> String -> a -> String
forall a. (Num a, Ord a) => (a -> ShowS) -> String -> a -> String
toBase a -> ShowS
showBin String
"0b"
where
showBin :: a -> ShowS
showBin = a -> (Int -> Char) -> a -> ShowS
forall a. (Integral a, Show a) => a -> (Int -> Char) -> a -> ShowS
showIntAtBase a
2 Int -> Char
intToDigit
toHex :: (Integral a, Show a) => a -> String
toHex :: a -> String
toHex = (a -> ShowS) -> String -> a -> String
forall a. (Num a, Ord a) => (a -> ShowS) -> String -> a -> String
toBase a -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex String
"0x"
toFloatDecimal :: RealFloat a => a -> String
toFloatDecimal :: a -> String
toFloatDecimal a
val = Maybe Int -> a -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat Maybe Int
forall a. Maybe a
Nothing a
val String
""
toFloatExpDecimal :: RealFloat a => a -> String
toFloatExpDecimal :: a -> String
toFloatExpDecimal a
val = Maybe Int -> a -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showEFloat Maybe Int
forall a. Maybe a
Nothing a
val String
""
toHexFloat :: RealFloat a => a -> String
toHexFloat :: a -> String
toHexFloat a
val = a -> ShowS
forall a. RealFloat a => a -> ShowS
showHFloat a
val String
""