@@ -75,7 +75,7 @@ import GHC.Real (Ratio(..), (%))
75
75
import GHC.TypeLits
76
76
import Text.Read
77
77
import qualified Text.Read.Lex as L
78
- import System.Random (Random (.. ), RandomGen ( .. ) )
78
+ import System.Random (Random (.. ))
79
79
import Control.Concurrent.MVar
80
80
import Control.Exception
81
81
import System.IO.Unsafe (unsafePerformIO )
@@ -128,7 +128,7 @@ atPrecision :: CReal n -> Int -> Integer
128
128
(CR mvc f) `atPrecision` (! p) = unsafePerformIO $ modifyMVar mvc $ \ vc -> do
129
129
vc' <- evaluate vc
130
130
case vc' of
131
- Current j v | j >= p -> do
131
+ Current j v | j >= p ->
132
132
pure (vc', v /^ (j - p))
133
133
_ -> do
134
134
v <- evaluate $ f p
@@ -268,8 +268,8 @@ instance Floating (CReal n) where
268
268
-- 0.75 <= x <= 2
269
269
| l == 0 -> logBounded x
270
270
-- x >= 2
271
- | l > 0 -> let a = x `shiftR` l
272
- in logBounded a + fromIntegral l *. ln2
271
+ | otherwise -> let a = x `shiftR` l
272
+ in logBounded a + fromIntegral l *. ln2
273
273
274
274
sqrt x = crMemoize (\ p -> let n = atPrecision x (2 * p)
275
275
in isqrt n)
@@ -297,7 +297,7 @@ instance Floating (CReal n) where
297
297
298
298
tan x = sin x .* recip (cos x)
299
299
300
- asin x = ( atan (x .*. recipBounded (1 + sqrt (1 - squareBounded x) ))) `shiftL` 1
300
+ asin x = atan (x .*. recipBounded (1 + sqrt (1 - squareBounded x))) `shiftL` 1
301
301
302
302
acos x = piBy2 - asin x
303
303
@@ -355,9 +355,7 @@ instance KnownNat n => RealFrac (CReal n) where
355
355
v = x `atPrecision` p
356
356
r = v .&. (bit p - 1 )
357
357
n = unsafeShiftR (v - r) p
358
- in case r /= 0 of
359
- True -> fromInteger $ n + 1
360
- _ -> fromInteger n
358
+ in if r /= 0 then fromInteger $ n + 1 else fromInteger n
361
359
362
360
floor x = let p = crealPrecision x
363
361
v = x `atPrecision` p
@@ -411,7 +409,7 @@ instance KnownNat n => Eq (CReal n) where
411
409
x == y = let p = crealPrecision x + 2
412
410
in (atPrecision x p - atPrecision y p) /^ 2 == 0
413
411
414
- -- | Like equality values of type @CReal p@ are compared at precision @p@.
412
+ -- | Like equality, values of type @CReal p@ are compared at precision @p@.
415
413
instance KnownNat n => Ord (CReal n ) where
416
414
compare (CR mvx _) (CR mvy _) | mvx == mvy = EQ
417
415
compare x y = let p = crealPrecision x + 2
@@ -442,7 +440,7 @@ instance KnownNat n => Random (CReal n) where
442
440
--
443
441
444
442
piBy4 :: CReal n
445
- piBy4 = ( atanBounded (recipBounded 5 ) `shiftL` 2 ) - atanBounded (recipBounded 239 ) -- Machin Formula
443
+ piBy4 = atanBounded (recipBounded 5 ) `shiftL` 2 - atanBounded (recipBounded 239 ) -- Machin Formula
446
444
447
445
piBy2 :: CReal n
448
446
piBy2 = piBy4 `shiftL` 1
@@ -609,7 +607,7 @@ shiftR :: CReal n -> Int -> CReal n
609
607
shiftR x n = crMemoize (\ p -> let p' = p - n
610
608
in if p' >= 0
611
609
then atPrecision x p'
612
- else atPrecision x 0 /^ ( negate p') )
610
+ else atPrecision x 0 /^ negate p')
613
611
614
612
-- | @x \`shiftL\` n@ is equal to @x@ multiplied by 2^@n@
615
613
--
@@ -645,8 +643,7 @@ rationalToDecimal places (n :% d) = p ++ is ++ if places > 0 then "." ++ fs else
645
643
_ -> " "
646
644
ds = show (roundD (abs n * 10 ^ places) d)
647
645
l = length ds
648
- (is, fs) = if | l <= places -> (" 0" , replicate (places - l) ' 0' ++ ds)
649
- | otherwise -> splitAt (l - places) ds
646
+ (is, fs) = if l <= places then (" 0" , replicate (places - l) ' 0' ++ ds) else splitAt (l - places) ds
650
647
651
648
652
649
--
@@ -713,7 +710,7 @@ isqrt :: Integer -> Integer
713
710
isqrt x | x < 0 = error " Sqrt applied to negative Integer"
714
711
| x == 0 = 0
715
712
| otherwise = until satisfied improve initialGuess
716
- where improve r = unsafeShiftR (r + ( x `div` r) ) 1
713
+ where improve r = unsafeShiftR (r + x `div` r) 1
717
714
satisfied r = let r2 = r * r in r2 <= x && r2 + unsafeShiftL r 1 >= x
718
715
initialGuess = bit (unsafeShiftR (log2 x) 1 )
719
716
@@ -727,7 +724,7 @@ findFirstMonotonic :: (Int -> Bool) -> Int
727
724
findFirstMonotonic p = findBounds 0 1
728
725
where findBounds ! l ! u = if p u then binarySearch l u
729
726
else findBounds u (u * 2 )
730
- binarySearch ! l ! u = let ! m = l + (( u - l) `div` 2 )
727
+ binarySearch ! l ! u = let ! m = l + (u - l) `div` 2
731
728
in if | l+ 1 == u -> l
732
729
| p m -> binarySearch l m
733
730
| otherwise -> binarySearch m u
@@ -743,7 +740,11 @@ findFirstMonotonic p = findBounds 0 1
743
740
-- [1,-2,3,-4,5]
744
741
{-# INLINABLE alternateSign #-}
745
742
alternateSign :: Num a => [a ] -> [a ]
746
- alternateSign = \ ls -> foldr (\ a r b -> if b then (negate a): r False else a: r True ) (const [] ) ls False
743
+ alternateSign ls = foldr
744
+ (\ a r b -> if b then negate a : r False else a : r True )
745
+ (const [] )
746
+ ls
747
+ False
747
748
748
749
-- | @powerSeries q f x `atPrecision` p@ will evaluate the power series with
749
750
-- coefficients @q@ up to the coefficient at index @f p@ at value @x@
0 commit comments