Skip to content

Commit

Permalink
Representar los numeros internamente con ratio para tener precision a…
Browse files Browse the repository at this point in the history
…rbitraria
  • Loading branch information
JuanFdS committed Jan 21, 2023
1 parent 375b3e6 commit a35ad32
Show file tree
Hide file tree
Showing 5 changed files with 83 additions and 43 deletions.
1 change: 1 addition & 0 deletions package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -49,3 +49,4 @@ tests:
dependencies:
- pdeprelude
- hspec
- QuickCheck
5 changes: 3 additions & 2 deletions pdeprelude.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ cabal-version: 1.12
--
-- see: https://github.com/sol/hpack
--
-- hash: 59331dd2abcb3ca21452099e13964df448fcc0789d9aee6c6cfaecfc34c4127c
-- hash: 4ea43701a6a0ec35ac00d14921ffb0ef2a0ca17191b0a1741c3a5b0316d4290f

name: pdeprelude
version: 0.2.0.0
Expand Down Expand Up @@ -70,7 +70,8 @@ test-suite pdeprelude-test
DerivingVia
ghc-options: -threaded -rtsopts -with-rtsopts=-N
build-depends:
base >=4.7 && <5
QuickCheck
, base >=4.7 && <5
, hspec
, pdeprelude
default-language: Haskell2010
48 changes: 40 additions & 8 deletions src/Number.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,19 +5,26 @@ module Number (Number,
numberToFractional,
numberToIntegral,
integerToNumber,
numberToFloat) where
numberToFloat) where

import Prelude (($), (.), (<$>))
import qualified Prelude as P
import Data.Ratio (Ratio, Rational, (%), numerator, denominator)
import GHC.Real (Ratio(..))
import GHC.Num (divInteger)
import Numeric (showFFloat)
import GHC.Stack (HasCallStack)

newtype Number = Number { wrappedNum :: WrappedNum }
deriving (P.RealFrac, P.Num, P.Real, P.Fractional, P.Floating) via WrappedNum
deriving (P.RealFrac, P.Num, P.Real, P.Fractional
-- , P.Floating
) via WrappedNum

type WrappedNum = P.Double
type WrappedNum = Ratio P.Integer

-- Funciones para convertir entre Number y los Num del Prelude

numberToIntegral :: (P.Integral a) => Number -> a
numberToIntegral :: HasCallStack => (P.Integral a) => Number -> a
numberToIntegral number = case rounded number of
Integer integer -> P.fromInteger integer
Decimal _ -> P.error $ "Se esperaba un valor entero pero se pasó uno con decimales: " P.++ P.show number
Expand Down Expand Up @@ -60,28 +67,53 @@ fromInteger = P.fromInteger
fromRational :: P.Rational -> Number
fromRational = P.fromRational


-- Redondeos para evitar los errores que pueden surgir de trabajar con numeros de punto flotante

roundWrappedNum :: WrappedNum -> WrappedNum
roundWrappedNum = roundingTo digitsAfterComma
roundWrappedNum = P.id

digitsAfterComma :: P.Integer
digitsAfterComma = P.round $ wrappedNum 9.0

roundingTo :: P.Integer -> WrappedNum -> WrappedNum
roundingTo :: (P.RealFrac a, P.Integral b) => b -> a -> a
roundingTo n = (P./ exp) . P.fromIntegral . P.round . (P.* exp)
where exp = (numberToFractional 10) P.^ n
where exp = numberToFractional 10 P.^ n

instance P.Ord Number where
compare (Number a) (Number b) = P.compare (roundWrappedNum a) (roundWrappedNum b)

instance P.Eq Number where
Number a == Number b = roundWrappedNum a P.== roundWrappedNum b

-- >>> (wrappedNum $ P.negate 1.1)
-- (-11) % 10

-- >>> numerator $ (wrappedNum $ P.negate 1.1)
-- -11

-- >>> denominator $ (wrappedNum $ P.negate 1.1)
-- 10

-- >>> (P.negate 11) `P.mod` (10 :: P.Integer)
-- Couldn't match expected type ‘Integer’ with actual type ‘Number’
-- Couldn't match expected type ‘Number’ with actual type ‘Integer’

instance P.Show Number where
show number = case rounded number of
Integer integer -> P.show integer
Decimal decimal -> P.show decimal
Decimal decimal -> showRatioAsDecimal decimal

showRatioAsDecimal :: Rational -> P.String
showRatioAsDecimal numero@(numerator :% denominator) =
corregidorDeSigno P.++ P.show parteEntera P.++ P.dropWhile (P./= '.') (showFFloat P.Nothing parteDecimal "")
where parteEntera = numerator `P.quot` denominator :: P.Integer
zero = P.round 0
corregidorDeSigno = case parteEntera P.== zero P.&& numerator P.< zero of
P.True -> "-"
P.False -> ""
resto = numerator `P.rem` denominator
parteDecimal = P.fromInteger resto P./ P.fromInteger denominator

instance P.Enum Number where
toEnum integer = Number $ P.toEnum integer
Expand Down
36 changes: 18 additions & 18 deletions src/Redefinitions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -659,7 +659,7 @@ divMod unNumero otroNumero =
-- >>> pi
-- 3.141592654
pi :: Number
pi = P.pi
pi = P.undefined--P.pi

-- | Devuelve el valor de la función exponencial e^x, pasando como parámetro la __x__
--
Expand All @@ -673,7 +673,7 @@ pi = P.pi
-- >>> exp 5
-- 148.413159103
exp :: Number -> Number
exp = P.exp
exp = P.undefined--P.exp

-- | Devuelve el logaritmo en base 10 de un número.
--
Expand All @@ -682,14 +682,14 @@ exp = P.exp
-- >>> log 149
-- 5.003946306
log :: Number -> Number
log = P.log
log = P.undefined--P.log

-- | Devuelve la raíz cuadrada de un número.
--
-- >>> sqrt 9
-- 3
sqrt :: Number -> Number
sqrt = P.sqrt
sqrt = P.undefined--P.sqrt

-- | Dados dos números, devuelve el primero elevado a la potencia del segundo.
--
Expand All @@ -703,7 +703,7 @@ sqrt = P.sqrt
-- >>> (**) 2 4
-- 16
(**) :: Number -> Number -> Number
(**) = (P.**)
(**) = P.undefined--(P.**)

-- | Dados dos números (__x__ e __y__), devuelve el logaritmo en base __x__ del número __y__.
--
Expand All @@ -715,7 +715,7 @@ sqrt = P.sqrt
-- >>> logBase 10 100
-- 2
logBase :: Number -> Number -> Number
logBase = P.logBase
logBase = P.undefined--P.logBase

-- | Devuelve el seno de un número.
--
Expand All @@ -727,7 +727,7 @@ logBase = P.logBase
-- >>> sin (pi / 2)
-- 1
sin :: Number -> Number
sin = P.sin
sin = P.undefined--P.sin

-- | Devuelve el coseno de un número.
--
Expand All @@ -739,7 +739,7 @@ sin = P.sin
-- >>> cos (pi / 2)
-- 0
cos :: Number -> Number
cos = P.cos
cos = P.undefined--P.cos

-- | Devuelve la tangente de un número.
--
Expand All @@ -751,7 +751,7 @@ cos = P.cos
-- >>> tan (pi / 2)
-- 16331239353195370
tan :: Number -> Number
tan = P.tan
tan = P.undefined--P.tan

-- | Devuelve el arcoseno de un número.
--
Expand All @@ -760,7 +760,7 @@ tan = P.tan
-- >>> asin 1
-- 1.570796327
asin :: Number -> Number
asin = P.asin
asin = P.undefined--P.asin

-- | Devuelve el arcocoseno de un número.
--
Expand All @@ -769,7 +769,7 @@ asin = P.asin
-- >>> acos 0
-- 1.570796327
acos :: Number -> Number
acos = P.acos
acos = P.undefined--P.acos

-- | Devuelve el arcotangente de un número.
--
Expand All @@ -778,7 +778,7 @@ acos = P.acos
-- >>> atan 1
-- 0.785398163
atan :: Number -> Number
atan = P.atan
atan = P.undefined--P.atan

-- | Devuelve el seno hiperbólico de un número.
--
Expand All @@ -787,7 +787,7 @@ atan = P.atan
-- >>> sinh 1
-- 1.175201194
sinh :: Number -> Number
sinh = P.sinh
sinh = P.undefined--P.sinh

-- | Devuelve el coseno hiperbólico de un número.
--
Expand All @@ -796,7 +796,7 @@ sinh = P.sinh
-- >>> cosh 0
-- 1
cosh :: Number -> Number
cosh = P.cosh
cosh = P.undefined--P.cosh

-- | Devuelve la tangente hiperbólica de un número.
--
Expand All @@ -805,28 +805,28 @@ cosh = P.cosh
-- >>> tanh 0
-- 0
tanh :: Number -> Number
tanh = P.tanh
tanh = P.undefined--P.tanh

-- | Devuelve el arcoseno hiperbólico de un número.
--
-- >>> asinh 1
-- 0.881373587
asinh :: Number -> Number
asinh = P.asinh
asinh = P.undefined--P.asinh

-- | Devuelve el arcocoseno hiperbólico de un número.
--
-- >>> acosh 1
-- 0
acosh :: Number -> Number
acosh = P.acosh
acosh = P.undefined--P.acosh

-- | Devuelve el arcotangente hiperbólica de un número.
--
-- >>> atanh 0
-- 0
atanh :: Number -> Number
atanh = P.atanh
atanh = P.undefined--P.atanh

-- | La aplicación de funciones
--
Expand Down
36 changes: 21 additions & 15 deletions test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,9 @@ module Main where
import PdePreludat
import Test.Hspec
import Control.Exception (evaluate)
import qualified Prelude
import qualified Prelude as P
import Test.Hspec.QuickCheck
import Test.QuickCheck

main :: IO ()
main = hspec $ do
Expand All @@ -21,23 +23,27 @@ main = hspec $ do
show 1 `shouldBe` "1"
it "mostrar un numero decimal incluye la parte decimal" $ do
show 1.5 `shouldBe` "1.5"
describe "redondea a 9 decimales para compensar errores de punto flotante" $ do
it "los numeros con muchos decimales se muestran redondeados" $ do
show 0.9999999999 `shouldBe` "1"
it "los decimales literales se redondean" $ do
0.9999999999 `shouldBeTheSameNumberAs` 1
it "los resultados de sumas se redondean" $ do
describe "no hay errores de punto flotante al usar numeros decimales" $ do
it "números enteros más allá de la precisión de Double se muestran correctamente" $ do
show 12345678901234567890 `shouldBe` "12345678901234567890"
it "números decimales más allá de la precisión de Double se muestran correctamente" $ do
show 12345678901234567890.7 `shouldBe` "12345678901234567890.7"
it "numeros decimales negativos se muestran correctamente" $ do
show (-0.5) `shouldBe` "-0.5"
it "numeros decimales muy grandes se muestran correctamente" $ do
show (-12345678901234567890.3) `shouldBe` "-12345678901234567890.3"
it "los numeros decimales positivos NO se muestran en notacion cientifica" $ do
show 0.000001 `shouldBe` "0.000001"
it "los numeros decimales negativos NO se muestran en notacion cientifica" $ do
show (-0.000001) `shouldBe` "-0.000001"
it "los resultados de sumas dan el resultado esperado" $ do
(0.1 + 0.7) `shouldBeTheSameNumberAs` 0.8
it "los resultados de restas se redondean" $ do
it "los resultados de restas dan el resultado esperado" $ do
(0.8 - 0.1) `shouldBeTheSameNumberAs` 0.7
it "los resultados de multiplicaciones se redondean" $ do
it "los resultados de multiplicaciones dan el resultado esperado" $ do
(0.1 * 3) `shouldBeTheSameNumberAs` 0.3
it "los resultados de divisiones se redondean" $ do
(1 / 3) `shouldBeTheSameNumberAs` 0.333333333
it "no se pierde informacion al redondear en sucesivas operaciones" $ do
it "no se pierde informacion al hacer sucesivas operaciones con decimales" $ do
(1 / 3 * 3) `shouldBeTheSameNumberAs` 1
it "se redondea al usarse como parámetro de funciones que necesitan enteros" $ do
take 0.9999999999 [1,2,3,4] `shouldBe` [1]

describe "enumFromThenTo" $ do
describe "cuando todos los numeros son enteros" $ do
Expand Down Expand Up @@ -75,7 +81,7 @@ main = hspec $ do
it "aplica la función para una lista con elementos" $ do
sumOf length ["abracadabra", "pata", "de", "cabra"] `shouldBe` 22

shouldBeTheSameNumberAs :: Number -> Number -> Expectation
shouldBeTheSameNumberAs :: HasCallStack => Number -> Number -> Expectation
shouldBeTheSameNumberAs aNumber anotherNumber =
(aNumber `shouldBe` anotherNumber) <>
(aNumber < anotherNumber `shouldBe` False) <>
Expand Down

0 comments on commit a35ad32

Please sign in to comment.