[NumericPrelude] NP bug reports
Henning Thielemann
lemming at henning-thielemann.de
Sat Aug 27 06:30:37 BST 2016
On Thu, 25 Aug 2016, Eric Crockett wrote:
> Is there a github (or similar) repo for this library where I can file bug reports and feature requests?
E-mail to me is ok, you may also mail to
numeric-prelude at projects.haskell.org. However, the mailing list had
problems. I could move to darcs-hub. It includes a bug tracker, but
requires conversion to darcs-2 format. So I did not perform the move so
far because of low volume of issues.
> With the NP equivalent:
>
> {-# LANGUAGE NoImplicitPrelude, RebindableSyntax #-}
Btw. you may omit NoImplicitPrelude. It is implied by RebindableSyntax.
> module Main where
>
> import NumericPrelude
>
> main :: IO ()
> main = do
> let x = sqrt $ -1.0 :: Double
> print x -- NaN
> let y = round x :: Int
> print y -- crashes
>
> When compiled with -O0, I get NaN and 0, respectively (same as Prelude). When compiled with -O1, I get NaN and
> "Prelude.Enum.pred{Int}: tried to take `pred' of minBound".
I think the behavior is better than that of Prelude, yet, the error
message is confusing. I think it is caused by Algebra.RealRing.roundInt. I
wrote 'pred n' instead of 'n-1'. In general I did such things in order to
avoid working with number literals because they are not available in all
numeric-prelude modules. However, in this case 'n-1' should also work.
More information about the Numeric-Prelude
mailing list