{-
	Copyright (C) 2018 Dr. Alistair Ward

	This file is part of BishBosh.

	BishBosh is free software: you can redistribute it and/or modify
	it under the terms of the GNU General Public License as published by
	the Free Software Foundation, either version 3 of the License, or
	(at your option) any later version.

	BishBosh is distributed in the hope that it will be useful,
	but WITHOUT ANY WARRANTY; without even the implied warranty of
	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
	GNU General Public License for more details.

	You should have received a copy of the GNU General Public License
	along with BishBosh.  If not, see <http://www.gnu.org/licenses/>.
-}
{- |
 [@AUTHOR@]	Dr. Alistair Ward

 [@DESCRIPTION@]	An interface for floating-point data, which provides an alterative to 'Show'.
-}

module BishBosh.Property.ShowFloat(
-- * Type-classes
	ShowFloat(..),
-- * Functions
	showsFloatToN',
	showsFloatToN
) where

import qualified	BishBosh.Type.Count	as Type.Count
import qualified	Data.Ratio
import qualified	Numeric

-- | Render the specified data to the specified number of decimal digits.
showsFloatToN' :: RealFloat a => Type.Count.NDecimalDigits -> a -> ShowS
showsFloatToN' :: NDecimalDigits -> a -> ShowS
showsFloatToN' NDecimalDigits
nDecimalDigits	= Maybe NDecimalDigits -> a -> ShowS
forall a. RealFloat a => Maybe NDecimalDigits -> a -> ShowS
Numeric.showFFloat (NDecimalDigits -> Maybe NDecimalDigits
forall a. a -> Maybe a
Just (NDecimalDigits -> Maybe NDecimalDigits)
-> NDecimalDigits -> Maybe NDecimalDigits
forall a b. (a -> b) -> a -> b
$ NDecimalDigits -> NDecimalDigits
forall a b. (Integral a, Num b) => a -> b
fromIntegral NDecimalDigits
nDecimalDigits)

-- | An alternative to 'Show', for floating-point data.
class ShowFloat a where
	showsFloat	:: (Double -> ShowS) -> a -> ShowS

instance ShowFloat Double where
	showsFloat :: (Double -> ShowS) -> Double -> ShowS
showsFloat	= (Double -> ShowS) -> Double -> ShowS
forall a. a -> a
id

instance ShowFloat Float where
	showsFloat :: (Double -> ShowS) -> Float -> ShowS
showsFloat Double -> ShowS
fromDouble	= Double -> ShowS
fromDouble (Double -> ShowS) -> (Float -> Double) -> Float -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac

instance Integral r => ShowFloat (Data.Ratio.Ratio r) where
	showsFloat :: (Double -> ShowS) -> Ratio r -> ShowS
showsFloat Double -> ShowS
fromDouble	= Double -> ShowS
fromDouble (Double -> ShowS) -> (Ratio r -> Double) -> Ratio r -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio r -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac

-- | Render the specified data to the specified number of decimal digits.
showsFloatToN :: ShowFloat a => Type.Count.NDecimalDigits -> a -> ShowS
showsFloatToN :: NDecimalDigits -> a -> ShowS
showsFloatToN NDecimalDigits
nDecimalDigits	= (Double -> ShowS) -> a -> ShowS
forall a. ShowFloat a => (Double -> ShowS) -> a -> ShowS
showsFloat ((Double -> ShowS) -> a -> ShowS)
-> (Double -> ShowS) -> a -> ShowS
forall a b. (a -> b) -> a -> b
$ NDecimalDigits -> Double -> ShowS
forall a. RealFloat a => NDecimalDigits -> a -> ShowS
showsFloatToN' NDecimalDigits
nDecimalDigits