{-# LANGUAGE GeneralizedNewtypeDeriving, OverloadedStrings #-} ----------------------------------------------------------------------------- -- | -- Module : Hasmin.Types.Numeric -- Copyright : (c) 2017 Cristian Adrián Ontivero -- License : BSD3 -- Stability : experimental -- Portability : non-portable -- -- CSS Numeric data types: \, \, and \. -- All Rational newtypes to ensure dimension conversion precision. -- ----------------------------------------------------------------------------- module Hasmin.Types.Numeric ( Percentage(..), toPercentage, Number(..), toNumber, fromNumber, Alphavalue(..), toAlphavalue, mkAlphavalue ) where import Data.Text (pack) import Hasmin.Types.Class import Hasmin.Utils import Text.PrettyPrint.Mainland (strictText, text, Pretty, ppr) import Text.Printf (printf) -- | The \ data type. Real numbers, possibly with a fractional component. -- When written literally, a number is either an integer, or zero or more -- decimal digits followed by a dot (.) followed by one or more decimal digits -- and optionally an exponent composed of "e" or "E" and an integer. It -- corresponds to the \ production in the CSS Syntax Module -- [CSS3SYN]. As with integers, the first character of a number may be -- immediately preceded by - or + to indicate the number’s sign. -- Specifications: -- -- 1. -- 2. -- 3. newtype Number = Number { getRational :: Rational } deriving (Eq, Show, Ord, Num, Fractional, Real, RealFrac) instance ToText Number where toText = pack . trimLeadingZeros . showRat . toRational -- check if scientific notation is shorter! instance Pretty Number where ppr = strictText . toText toNumber :: Real a => a -> Number toNumber = Number . toRational fromNumber :: Fractional a => Number -> a fromNumber = fromRational . toRational -- | The \ data type. Syntactically a \. It is the -- uniform opacity setting to be applied across an entire object. Any values -- outside the range 0.0 (fully transparent) to 1.0 (fully opaque) are clamped -- to this range. Specification: -- -- 1. a -> Alphavalue toAlphavalue = mkAlphavalue . toRational mkAlphavalue :: Rational -> Alphavalue mkAlphavalue = Alphavalue . restrict 0 1 -- | The \ data type. Many CSS properties can take percentage -- values, often to define sizes in terms of parent objects. Percentages are -- formed by a \ immediately followed by the percentage sign %. -- There is no space between the '%' and the number. Specification: -- -- 1. a -> Percentage toPercentage = Percentage . toRational -- Note: printf used instead of show to avoid scientific notation -- | Show a Rational in decimal notation, removing leading zeros, -- and not displaying fractional part if the number is an integer. showRat :: Rational -> String showRat r | abs (r - fromInteger x) < eps = printf "%d" x | otherwise = printf "%f" d where x = round r d = fromRational r :: Double trimLeadingZeros :: String -> String trimLeadingZeros l@(x:xs) | x == '-' = x : go xs | otherwise = go l where go ('0':y:ys) = go (y:ys) go z = z trimLeadingZeros [] = ""