-- SPDX-FileCopyrightText: 2021 Tocqueville Group -- -- SPDX-License-Identifier: LicenseRef-MIT-TQ {-# LANGUAGE RebindableSyntax #-} {-# LANGUAGE NoApplicativeDo #-} {-# OPTIONS_GHC -Wno-unused-do-bind #-} {-# OPTIONS_GHC -Wno-orphans #-} module Lorentz.CustomArith.Conversions ( -- * Rational to Fixed/NFixed convertFixedToRational , convertNFixedToRational , convertRationalToFixed , convertRationalToNFixed , unsafeConvertRationalToNFixed -- * NRational to Fixed/NFixed , convertFixedToNRational , unsafeConvertFixedToNRational , convertNFixedToNRational , convertNRationalToFixed , convertNRationalToNFixed ) where import Data.Fixed (HasResolution) import Prelude (Maybe) import Lorentz.CustomArith.FixedArith import Lorentz.CustomArith.RationalArith import Lorentz.Base import Lorentz.Coercions import Lorentz.Errors import Lorentz.Instr import Lorentz.Macro import Lorentz.Rebinded convertRationalToNRational :: Rational : s :-> Maybe (NRational) : s convertRationalToNRational = do dup; numerator ifGe0 (unsafeConvertRationalToNRational # some) (drop # none) unsafeConvertRationalToNRational :: Rational : s :-> NRational : s unsafeConvertRationalToNRational = deconstructRational # abs # constructRational convertNRationalToRational :: NRational : s :-> Rational : s convertNRationalToRational = deconstructRational # int # constructRational ---------------------------------------------------------------------------------------------------- -- Rationals ---------------------------------------------------------------------------------------------------- -- | Converts 'Rational' to 'Fixed' using value inside as numerator and base as denominator convertFixedToRational :: forall a s. HasResolution a => Fixed a : s :-> Rational : s convertFixedToRational = do coerceUnwrap push (resolution_ @a) swap constructRational -- | Converts 'Rational' to 'NFixed' using value inside as numerator and base as denominator convertNFixedToRational ::forall a s. HasResolution a => NFixed a : s :-> Rational : s convertNFixedToRational = do coerceUnwrap; int push (resolution_ @a) swap constructRational -- | Converts 'Fixed' to 'Rational' according to formulae: numerator * base / denominator -- Note: Since result's base is determined by user, it is recommended to use higher value in order to achieve -- better accuracy convertRationalToFixed :: forall a s. HasResolution a => Rational : s :-> Fixed a : s convertRationalToFixed = do deconstructRational push (resolution_ @a) mul ediv assertSome (Impossible @"Division by zero impossible") unpair add unsafeCoerceWrap unsafeConvertRationalToNFixed :: forall a s. HasResolution a => Rational : s :-> NFixed a : s unsafeConvertRationalToNFixed = convertRationalToFixed # unsafeCastFixedToNFixed convertRationalToNFixed :: forall a s. HasResolution a => Rational : s :-> Maybe (NFixed a) : s convertRationalToNFixed = convertRationalToFixed # castFixedToNFixed ---------------------------------------------------------------------------------------------------- -- NRationals ---------------------------------------------------------------------------------------------------- -- | Converts 'NRational' to 'Fixed'. convertNRationalToFixed :: forall a s. HasResolution a => NRational : s :-> Fixed a : s convertNRationalToFixed = convertNRationalToRational # convertRationalToFixed -- | Converts 'NRational' to 'NFixed'. convertNRationalToNFixed :: forall a s. HasResolution a => NRational : s :-> NFixed a : s convertNRationalToNFixed = do deconstructRational push (resolution_ @a) mul ediv assertSome (Impossible @"Division by zero impossible") unpair add unsafeCoerceWrap -- | Converts 'NFixed' to 'NRational'. convertNFixedToNRational :: forall a s. HasResolution a => NFixed a : s :-> NRational : s convertNFixedToNRational = do coerceUnwrap push (resolution_ @a) swap constructRational -- | Converts 'Fixed' to 'NRational' if it is greater than zero. If not, returns 'Data.Maybe.Nothing' convertFixedToNRational :: forall a s. HasResolution a => Fixed a : s :-> Maybe (NRational) : s convertFixedToNRational = convertFixedToRational # convertRationalToNRational -- | Converts 'Fixed' to 'NRational', using 'abs' on numerator. unsafeConvertFixedToNRational :: forall a s. HasResolution a => Fixed a : s :-> NRational : s unsafeConvertFixedToNRational = convertFixedToRational # unsafeConvertRationalToNRational