{-# LANGUAGE CPP #-} module Graphics.SvgTree.Misc ( ppD , ppF ) where #if defined(ASTERIUS) || defined(ghcjs_HOST_OS) import Numeric #else import Data.Double.Conversion.Text import qualified Data.Text as T #endif precision :: Int precision :: Int precision = Int 6 ppD :: Double -> String #if defined(ASTERIUS) || defined(ghcjs_HOST_OS) ppD v = showFFloat (Just precision) v "" #else ppD :: Double -> String ppD = Text -> String T.unpack (Text -> String) -> (Double -> Text) -> Double -> String forall b c a. (b -> c) -> (a -> b) -> a -> c . (Char -> Bool) -> Text -> Text T.dropWhileEnd (Char -> Char -> Bool forall a. Eq a => a -> a -> Bool == Char '.') (Text -> Text) -> (Double -> Text) -> Double -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . (Char -> Bool) -> Text -> Text T.dropWhileEnd (Char -> Char -> Bool forall a. Eq a => a -> a -> Bool == Char '0') (Text -> Text) -> (Double -> Text) -> Double -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> Double -> Text toFixed Int precision #endif ppF :: Float -> String ppF :: Float -> String ppF = Double -> String ppD (Double -> String) -> (Float -> Double) -> Float -> String forall b c a. (b -> c) -> (a -> b) -> a -> c . Float -> Double forall a b. (Real a, Fractional b) => a -> b realToFrac