{-# LANGUAGE CPP #-}
{-# LANGUAGE ViewPatterns #-}
module Ide.Plugin.Conversion (
alternateFormat
, hexRegex
, hexFloatRegex
, binaryRegex
, octalRegex
, decimalRegex
, numDecimalRegex
, matchLineRegex
, toOctal
, toDecimal
, toBinary
, toHex
, toFloatDecimal
, toFloatExpDecimal
, toHexFloat
, AlternateFormat
, ExtensionNeeded(..)
) where
import Data.List (delete)
import Data.List.Extra (enumerate, upper)
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
| 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
$cshowsPrec :: Int -> FormatType -> ShowS
showsPrec :: Int -> FormatType -> ShowS
$cshow :: FormatType -> String
show :: FormatType -> String
$cshowList :: [FormatType] -> ShowS
showList :: [FormatType] -> ShowS
Show, FormatType -> FormatType -> Bool
(FormatType -> FormatType -> Bool)
-> (FormatType -> FormatType -> Bool) -> Eq FormatType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormatType -> FormatType -> Bool
== :: FormatType -> FormatType -> Bool
$c/= :: FormatType -> FormatType -> Bool
/= :: 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
$cfrom :: forall x. FormatType -> Rep FormatType x
from :: forall x. FormatType -> Rep FormatType x
$cto :: forall x. Rep FormatType x -> FormatType
to :: forall x. Rep FormatType x -> FormatType
Generic)
instance NFData FormatType
data IntFormatType = IntDecimalFormat
| 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
$cshowsPrec :: Int -> IntFormatType -> ShowS
showsPrec :: Int -> IntFormatType -> ShowS
$cshow :: IntFormatType -> String
show :: IntFormatType -> String
$cshowList :: [IntFormatType] -> ShowS
showList :: [IntFormatType] -> ShowS
Show, IntFormatType -> IntFormatType -> Bool
(IntFormatType -> IntFormatType -> Bool)
-> (IntFormatType -> IntFormatType -> Bool) -> Eq IntFormatType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IntFormatType -> IntFormatType -> Bool
== :: IntFormatType -> IntFormatType -> Bool
$c/= :: IntFormatType -> IntFormatType -> Bool
/= :: 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
$cfrom :: forall x. IntFormatType -> Rep IntFormatType x
from :: forall x. IntFormatType -> Rep IntFormatType x
$cto :: forall x. Rep IntFormatType x -> IntFormatType
to :: forall x. Rep IntFormatType x -> IntFormatType
Generic, IntFormatType
IntFormatType -> IntFormatType -> Bounded IntFormatType
forall a. a -> a -> Bounded a
$cminBound :: IntFormatType
minBound :: IntFormatType
$cmaxBound :: IntFormatType
maxBound :: IntFormatType
Bounded, Int -> IntFormatType
IntFormatType -> Int
IntFormatType -> [IntFormatType]
IntFormatType -> IntFormatType
IntFormatType -> IntFormatType -> [IntFormatType]
IntFormatType -> IntFormatType -> IntFormatType -> [IntFormatType]
(IntFormatType -> IntFormatType)
-> (IntFormatType -> IntFormatType)
-> (Int -> IntFormatType)
-> (IntFormatType -> Int)
-> (IntFormatType -> [IntFormatType])
-> (IntFormatType -> IntFormatType -> [IntFormatType])
-> (IntFormatType -> IntFormatType -> [IntFormatType])
-> (IntFormatType
-> IntFormatType -> IntFormatType -> [IntFormatType])
-> Enum IntFormatType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: IntFormatType -> IntFormatType
succ :: IntFormatType -> IntFormatType
$cpred :: IntFormatType -> IntFormatType
pred :: IntFormatType -> IntFormatType
$ctoEnum :: Int -> IntFormatType
toEnum :: Int -> IntFormatType
$cfromEnum :: IntFormatType -> Int
fromEnum :: IntFormatType -> Int
$cenumFrom :: IntFormatType -> [IntFormatType]
enumFrom :: IntFormatType -> [IntFormatType]
$cenumFromThen :: IntFormatType -> IntFormatType -> [IntFormatType]
enumFromThen :: IntFormatType -> IntFormatType -> [IntFormatType]
$cenumFromTo :: IntFormatType -> IntFormatType -> [IntFormatType]
enumFromTo :: IntFormatType -> IntFormatType -> [IntFormatType]
$cenumFromThenTo :: IntFormatType -> IntFormatType -> IntFormatType -> [IntFormatType]
enumFromThenTo :: IntFormatType -> IntFormatType -> IntFormatType -> [IntFormatType]
Enum)
instance NFData IntFormatType
data FracFormatType = FracDecimalFormat
| 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
$cshowsPrec :: Int -> FracFormatType -> ShowS
showsPrec :: Int -> FracFormatType -> ShowS
$cshow :: FracFormatType -> String
show :: FracFormatType -> String
$cshowList :: [FracFormatType] -> ShowS
showList :: [FracFormatType] -> ShowS
Show, FracFormatType -> FracFormatType -> Bool
(FracFormatType -> FracFormatType -> Bool)
-> (FracFormatType -> FracFormatType -> Bool) -> Eq FracFormatType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FracFormatType -> FracFormatType -> Bool
== :: FracFormatType -> FracFormatType -> Bool
$c/= :: FracFormatType -> FracFormatType -> Bool
/= :: 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
$cfrom :: forall x. FracFormatType -> Rep FracFormatType x
from :: forall x. FracFormatType -> Rep FracFormatType x
$cto :: forall x. Rep FracFormatType x -> FracFormatType
to :: forall x. Rep FracFormatType x -> FracFormatType
Generic, FracFormatType
FracFormatType -> FracFormatType -> Bounded FracFormatType
forall a. a -> a -> Bounded a
$cminBound :: FracFormatType
minBound :: FracFormatType
$cmaxBound :: FracFormatType
maxBound :: FracFormatType
Bounded, Int -> FracFormatType
FracFormatType -> Int
FracFormatType -> [FracFormatType]
FracFormatType -> FracFormatType
FracFormatType -> FracFormatType -> [FracFormatType]
FracFormatType
-> FracFormatType -> FracFormatType -> [FracFormatType]
(FracFormatType -> FracFormatType)
-> (FracFormatType -> FracFormatType)
-> (Int -> FracFormatType)
-> (FracFormatType -> Int)
-> (FracFormatType -> [FracFormatType])
-> (FracFormatType -> FracFormatType -> [FracFormatType])
-> (FracFormatType -> FracFormatType -> [FracFormatType])
-> (FracFormatType
-> FracFormatType -> FracFormatType -> [FracFormatType])
-> Enum FracFormatType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FracFormatType -> FracFormatType
succ :: FracFormatType -> FracFormatType
$cpred :: FracFormatType -> FracFormatType
pred :: FracFormatType -> FracFormatType
$ctoEnum :: Int -> FracFormatType
toEnum :: Int -> FracFormatType
$cfromEnum :: FracFormatType -> Int
fromEnum :: FracFormatType -> Int
$cenumFrom :: FracFormatType -> [FracFormatType]
enumFrom :: FracFormatType -> [FracFormatType]
$cenumFromThen :: FracFormatType -> FracFormatType -> [FracFormatType]
enumFromThen :: FracFormatType -> FracFormatType -> [FracFormatType]
$cenumFromTo :: FracFormatType -> FracFormatType -> [FracFormatType]
enumFromTo :: FracFormatType -> FracFormatType -> [FracFormatType]
$cenumFromThenTo :: FracFormatType
-> FracFormatType -> FracFormatType -> [FracFormatType]
enumFromThenTo :: FracFormatType
-> FracFormatType -> FracFormatType -> [FracFormatType]
Enum)
instance NFData FracFormatType
data ExtensionNeeded = NoExtension
| NeedsExtension Extension
type AlternateFormat = (Text, ExtensionNeeded)
alternateFormat :: Literal -> [AlternateFormat]
alternateFormat :: Literal -> [AlternateFormat]
alternateFormat Literal
lit = case Literal
lit of
IntLiteral LiteralSrcSpan
_ Text
_ Integer
val -> (IntFormatType -> AlternateFormat)
-> [IntFormatType] -> [AlternateFormat]
forall a b. (a -> b) -> [a] -> [b]
map (Integer -> IntFormatType -> AlternateFormat
alternateIntFormat Integer
val) (Literal -> [IntFormatType]
removeCurrentFormatInt Literal
lit)
FracLiteral LiteralSrcSpan
_ 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 (IntFormatType -> AlternateFormat)
-> [IntFormatType] -> [AlternateFormat]
forall a b. (a -> b) -> [a] -> [b]
map (Integer -> IntFormatType -> AlternateFormat
alternateIntFormat (Rational -> Integer
forall a. Ratio a -> a
numerator Rational
val)) (Literal -> [IntFormatType]
removeCurrentFormatInt Literal
lit)
else (FracFormatType -> AlternateFormat)
-> [FracFormatType] -> [AlternateFormat]
forall a b. (a -> b) -> [a] -> [b]
map (Rational -> FracFormatType -> AlternateFormat
alternateFracFormat Rational
val) (Literal -> [FracFormatType]
removeCurrentFormatFrac Literal
lit)
alternateIntFormat :: Integer -> IntFormatType -> AlternateFormat
alternateIntFormat :: Integer -> IntFormatType -> AlternateFormat
alternateIntFormat Integer
val = \case
IntFormatType
IntDecimalFormat -> (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, ExtensionNeeded
NoExtension)
IntFormatType
HexFormat -> (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> String
forall a. Integral a => a -> String
toHex Integer
val, ExtensionNeeded
NoExtension)
IntFormatType
OctalFormat -> (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> String
forall a. Integral a => a -> String
toOctal Integer
val, ExtensionNeeded
NoExtension)
IntFormatType
BinaryFormat -> (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> String
forall a. Integral a => a -> String
toBinary Integer
val, Extension -> ExtensionNeeded
NeedsExtension Extension
BinaryLiterals)
IntFormatType
NumDecimalFormat -> (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Double -> String
forall a. RealFloat a => a -> String
toFloatExpDecimal (forall a. Num a => Integer -> a
fromInteger @Double Integer
val), Extension -> ExtensionNeeded
NeedsExtension Extension
NumDecimals)
alternateFracFormat :: Rational -> FracFormatType -> AlternateFormat
alternateFracFormat :: Rational -> FracFormatType -> AlternateFormat
alternateFracFormat Rational
val = \case
FracFormatType
FracDecimalFormat -> (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Double -> String
forall a. RealFloat a => a -> String
toFloatDecimal (forall a. Fractional a => Rational -> a
fromRational @Double Rational
val), ExtensionNeeded
NoExtension)
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 (forall a. Fractional a => Rational -> a
fromRational @Double Rational
val), ExtensionNeeded
NoExtension)
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 (forall a. Fractional a => Rational -> a
fromRational @Double Rational
val), Extension -> ExtensionNeeded
NeedsExtension Extension
HexFloatLiterals)
removeCurrentFormat :: (Foldable t, Eq a) => [a] -> t a -> [a]
removeCurrentFormat :: forall (t :: * -> *) a. (Foldable t, Eq a) => [a] -> t a -> [a]
removeCurrentFormat [a]
fmts t a
toRemove = ([a] -> a -> [a]) -> [a] -> t a -> [a]
forall b a. (b -> a -> b) -> b -> t a -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl ((a -> [a] -> [a]) -> [a] -> a -> [a]
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> [a] -> [a]
forall a. Eq a => a -> [a] -> [a]
delete) [a]
fmts t a
toRemove
removeCurrentFormatInt :: Literal -> [IntFormatType]
removeCurrentFormatInt :: Literal -> [IntFormatType]
removeCurrentFormatInt (Literal -> Text
getSrcText -> Text
srcText) = [IntFormatType] -> [IntFormatType] -> [IntFormatType]
forall (t :: * -> *) a. (Foldable t, Eq a) => [a] -> t a -> [a]
removeCurrentFormat [IntFormatType]
intFormats ([FormatType] -> [IntFormatType]
filterIntFormats ([FormatType] -> [IntFormatType])
-> [FormatType] -> [IntFormatType]
forall a b. (a -> b) -> a -> b
$ Text -> [FormatType]
sourceToFormatType Text
srcText)
removeCurrentFormatFrac :: Literal -> [FracFormatType]
removeCurrentFormatFrac :: Literal -> [FracFormatType]
removeCurrentFormatFrac (Literal -> Text
getSrcText -> Text
srcText) = [FracFormatType] -> [FracFormatType] -> [FracFormatType]
forall (t :: * -> *) a. (Foldable t, Eq a) => [a] -> t a -> [a]
removeCurrentFormat [FracFormatType]
fracFormats ([FormatType] -> [FracFormatType]
filterFracFormats ([FormatType] -> [FracFormatType])
-> [FormatType] -> [FracFormatType]
forall a b. (a -> b) -> a -> b
$ Text -> [FormatType]
sourceToFormatType Text
srcText)
filterIntFormats :: [FormatType] -> [IntFormatType]
filterIntFormats :: [FormatType] -> [IntFormatType]
filterIntFormats = (FormatType -> Maybe IntFormatType)
-> [FormatType] -> [IntFormatType]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe FormatType -> Maybe IntFormatType
getIntFormat
where
getIntFormat :: FormatType -> Maybe IntFormatType
getIntFormat (IntFormat IntFormatType
f) = IntFormatType -> Maybe IntFormatType
forall a. a -> Maybe a
Just IntFormatType
f
getIntFormat FormatType
_ = Maybe IntFormatType
forall a. Maybe a
Nothing
filterFracFormats :: [FormatType] -> [FracFormatType]
filterFracFormats :: [FormatType] -> [FracFormatType]
filterFracFormats = (FormatType -> Maybe FracFormatType)
-> [FormatType] -> [FracFormatType]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe FormatType -> Maybe FracFormatType
getFracFormat
where
getFracFormat :: FormatType -> Maybe FracFormatType
getFracFormat (FracFormat FracFormatType
f) = FracFormatType -> Maybe FracFormatType
forall a. a -> Maybe a
Just FracFormatType
f
getFracFormat FormatType
_ = Maybe FracFormatType
forall a. Maybe a
Nothing
intFormats :: [IntFormatType]
intFormats :: [IntFormatType]
intFormats = [IntFormatType]
forall a. (Enum a, Bounded a) => [a]
enumerate
fracFormats :: [FracFormatType]
fracFormats :: [FracFormatType]
fracFormats = [FracFormatType]
forall a. (Enum a, Bounded a) => [a]
enumerate
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 = [IntFormatType -> FormatType
IntFormat IntFormatType
IntDecimalFormat, FracFormatType -> FormatType
FracFormat FracFormatType
FracDecimalFormat]
toBase :: (Num a, Ord a) => (a -> ShowS) -> String -> a -> String
toBase :: forall a. (Num a, Ord a) => (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
<> ShowS
upper (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
<> ShowS
upper (a -> ShowS
conv a
n String
"")
#if MIN_VERSION_base(4,17,0)
toOctal, toDecimal, toBinary, toHex :: Integral a => a -> String
#else
toOctal, toDecimal, toBinary, toHex:: (Integral a, Show a) => a -> String
#endif
toBinary :: forall a. Integral a => 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 => a -> (Int -> Char) -> a -> ShowS
showIntAtBase a
2 Int -> Char
intToDigit
toOctal :: forall a. Integral a => 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 => a -> ShowS
showOct String
"0o"
toDecimal :: forall a. Integral a => 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
""
toHex :: forall a. Integral a => 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 => a -> ShowS
showHex String
"0x"
toFloatDecimal :: RealFloat a => a -> String
toFloatDecimal :: forall a. RealFloat a => 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 :: forall a. RealFloat a => 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 :: forall a. RealFloat a => a -> String
toHexFloat a
val = a -> ShowS
forall a. RealFloat a => a -> ShowS
showHFloat a
val String
""