No instance for (Fractional Int) arising from a use of `area' - haskell

I'm new to Haskell and I'm writing a program that calculates the limit of a function. So given two lists a and b, a delta dx = 0.001, and the limits of integration l and r, I want to recursively compute the area under the curve with equation:
a1(x)^b1 + a2(x)^b2 + ... + an(x)bn where x is all the values between l an r with an increment of dx between each value. The technical part isn't that important I guess but it helps to read the code:
import Text.Printf (printf)
-- This function should return a list [area].
solve :: Int -> Int -> [Int] -> [Int] -> [Double]
solve l r x y = [area l r x y]
area l r a b = if (l < r)
then (calc l a b) * 0.001 + (area (l + 1) r a b)
else (calc r a b) * 0.001
calc n (a:arest) (b:brest) = (fromIntegral(n) ^^ b) * fromIntegral(a) + (calc n arest brest)
calc n [] [] = 0
--Input/Output.
main :: IO ()
main = getContents >>= mapM_ (printf "%.1f\n"). (\[a, b, [l, r]] -> solve l r a b). map (map read. words). lines
I get no error with the above code but as soon as I change area (l + 1) r a b to area (l + 0.001) r a b I get the following error message:
No instance for (Fractional Int) arising from a use of `area'
I tried making a new class and having a be an abstract type but that didn't work, any other ideas?

So the problem is that Int is not a Fractional type. In other words, it does not have a value called 0.001 [note 1], but you have requested Haskell to give you such a value in your code.
You are making this request because 0.001 is fed to the (+) function with another argument (in this case l) which is of type Int. This is a problem because the function has type (+) :: (Num a) => a -> a -> a: in other words, there are a lot of different functions (+) all having the type a -> a -> a; one of these functions exists for every type a in the Num type class.
Since we know that one argument to the function is an Int, it follows that we're using the specific function (+) :: Int -> Int -> Int. That is why l + 0.001 gets weird.
As for solving the problem: You probably wanted l and r to be of type Double (they're left and right bounds on where a number can be?) but if you're sure that they must be Ints then you probably meant to write fromIntegral l + 0.001.
Side note on style: parentheses in Haskell are always just grouping/precedence, functions are higher precedence than operators which are higher precedence than special forms (let, case, if, do), and function application is always left-associative or "greedy nom": a function eats whatever is immediately in front of it. What you have written:
(fromIntegral(n) ^^ b) * fromIntegral(a) + (calc n arest brest)
is probably better written as:
fromIntegral a * fromIntegral n ^^ b + calc n arest brest
The parentheses around calc are not necessary (because operators like + have lower precedence than function applications), nor are the parentheses around n and a (because those sub-expressions are indivisible chunks; fromIntegral(n) is identical to fromIntegral (n) is identical to fromIntegral n).
As #dfeuer mentions below: secretly, when you write 0.001 it does not have a definite type; rather it is translated to fromRational 0.001 internally, where the latter 0.001 is a definite value of the definite type Rational, just as when you write 4 it is translated to fromInteger 4 where the latter 4 is a definite value of the definite type Integer. The problem is really that there is no fromRational function for Int, because Int is not part of the Fractional typeclass which defines fromRational. And it's not part of that typeclass because the language designers preferred an error to a silent rounding/dropping of a fraction.

Related

Perplexing behaviour when approximating the derivative in haskell

I have defined a typeclass Differentiable to be implemented by any type which can operate on infinitesimals.
Here is an example:
class Fractional a => Differentiable a where
dif :: (a -> a) -> (a -> a)
difs :: (a -> a) -> [a -> a]
difs = iterate dif
instance Differentiable Double where
dif f x = (f (x + dx) - f(x)) / dx
where dx = 0.000001
func :: Double -> Double
func = exp
I have also defined a simple Double -> Double function to differentiate.
But when I test this in the ghc this happens:
... $ ghci
GHCi, version 8.8.4: https://www.haskell.org/ghc/ :? for help
Prelude> :l testing
[1 of 1] Compiling Main ( testing.hs, interpreted )
Ok, one module loaded.
*Main> :t func
func :: Double -> Double
*Main> derivatives = difs func
*Main> :t derivatives
derivatives :: [Double -> Double]
*Main> terms = map (\f -> f 0) derivatives
*Main> :t terms
terms :: [Double]
*Main> take 5 terms
[1.0,1.0000004999621837,1.000088900582341,-222.0446049250313,4.440892098500626e8]
*Main>
The approximations to the nth derivative of e^x|x=0 are:
[1.0,1.0000004999621837,1.000088900582341,-222.0446049250313,4.440892098500626e8]
The first and 2nd derivatives are perfectly reasonable approximations given the setup, but suddenly, the third derivative of func at 0 is... -222.0446049250313! HOW!!?
The method you're using here is a finite difference method of 1st-order accuracy.
Layman's translation: it works, but is pretty rubbish numerically speaking. Specifically, because it's only 1st-order accurate, you need those really small steps to get good accuracy even with exact-real-arithmetic. You did choose a small step size so that's fine, but small step size brings in another problem: rounding errors. You need to take the difference f (x+δx) - f x with small δx, meaning the difference is small whereas the individual values may be large. That always brings up the floating-point inaccuracy – consider for example
Prelude> (1 + pi*1e-13) - 1
3.141931159689193e-13
That might not actually hurt that much, but since you then need to divide by δx you boost up the error.
This issue just gets worse/compounded as you go to the higher derivatives, because now each of the f' x and f' (x+δx) has already an (non-identical!) boosted error on it, so taking the difference and boosting again is a clear recipe for disaster.
The simplest way to remediate the problem is to switch to a 2nd-order accurate method, the obvious being central difference. Then you can make the step a lot bigger, and thus largely avoid rounding issues:
Prelude> let dif f x = (f (x + δx) - f(x - δx)) / (2*δx) where δx = 1e-3
Prelude> take 8 $ ($0) <$> iterate dif exp
[1.0,1.0000001666666813,1.0000003333454632,1.0000004990740052,0.9999917560676863,0.9957312752106873,8.673617379884035,7806.255641895632]
You see the first couple of derivatives are good now, but then eventually it also becomes unstable – and this will happen with any FD method as you iterate it. But that's anyway not really a good approach: note that every evaluation of the n-th derivative requires 2 evaluations of the n−1-th. So, the complexity is exponential in the derivative degree.
A better approach to approximate the n-th derivative of an opaque function is to fit an n-th order polynomial to it and differentiate this symbolically/automatically. Or, if the function is not opaque, differentiate itself symbolically/automatically.
tl;dr: the dx denominator gets small exponentially quickly, which means that even small errors in the numerator get blown out of proportion.
Let's do some equational reasoning on the first "bad" approximation, the third derivative.
dif (dif (dif exp))
= { definition of dif }
dif (dif (\x -> (exp (x+dx) - exp x)/dx))
= { definition of dif }
dif (\y -> ((\x -> (exp (x+dx) - exp x)/dx) (y+dx)
- (\x -> (exp (x+dx) - exp x)/dx) y
)/dx)
= { questionable algebra }
dif (\y -> (exp (y + 2*dx) - 2*exp (y + dx) + exp y)/dx^2)
= { alpha }
dif (\x -> (exp (x + 2*dx) - 2*exp (x + dx) + exp x)/dx^2)
= { definition of dif and questionable algebra }
\x -> (exp (x + 3*dx) - 3*exp (x + 2*dx) + 3*exp (x + dx) - exp x)/dx^3
Hopefully by now you can see the pattern we're getting into: as we take more and more derivatives, the error in the numerator gets worse (because we are computing exp farther and farther away from the original point, x + 3*dx is three times as far away e.g.) while the sensitivity to error in the denominator gets higher (because we are computing dx^n for the nth derivative). By the third derivative, these two factors become untenable:
> exp (3*dx) - 3*exp (2*dx) + 3*exp (dx) - exp 0
-4.440892098500626e-16
> dx^3
9.999999999999999e-19
So you can see that, although the error in the numerator is only about 5e-16, the sensitivity to error in the denominator is so high that you start to see nonsensical answers.

Unresolved top level overloading

Task is to find all two-valued numbers representable as the sum of the sqrt's of two natural numbers.
I try this:
func = [sqrt (x) + sqrt (y) | x <- [10..99], y <- [10..99], sqrt (x) `mod` 1 == 0, sqrt (y) `mod` 1 == 0]
Result:
Unresolved top-level overloading Binding : func
Outstanding context : (Integral b, Floating b)
How can I fix this?
This happens because of a conflict between these two types:
sqrt :: Floating a => a -> a
mod :: Integral a => a -> a -> a
Because you write mod (sqrt x) 1, and sqrt is constrained to return the same type as it takes, the compiler is left trying to find a type for x that simultaneously satisfies the Floating constraint of sqrt and the Integral constraint of mod. There are no types in the base library that satisfy both constraints.
A quick fix is to use mod' :: Real a => a -> a -> a:
import Data.Fixed
func = [sqrt (x) + sqrt (y) | x <- [10..99], y <- [10..99], sqrt (x) `mod'` 1 == 0, sqrt (y) `mod'` 1 == 0]
However, from the error you posted, it looks like you may not be using GHC, and mod' is probably a GHC-ism. In that case you could copy the definition (and the definition of the helper function div') from here.
But I recommend a more involved fix. The key observation is that if x = sqrt y, then x*x = y, so we can avoid calling sqrt at all. Instead of iterating over numbers and checking if they have a clean sqrt, we can iterate over square roots; their squares will definitely have clean square roots. A straightforward application of this refactoring might look like this:
sqrts = takeWhile (\n -> n*n <= 99)
. dropWhile (\n -> n*n < 10)
$ [0..]
func = [x + y | x <- sqrts, y <- sqrts]
Of course, func is a terrible name (it's not even a function!), and sqrts is a constant we could compute ourselves, and is so short we should probably just inline it. So we might then simplify to:
numberSums = [x + y | x <- [4..9], y <- [4..9]]
At this point, I would be wondering whether I really wanted to write this at all, preferring just
numberSums = [8..18]
which, unlike the previous iteration, doesn't have any duplicates. It has lost all of the explanatory power of why this is an interesting constant, though, so you would definitely want a comment.
-- sums of pairs of numbers, each of whose squares lies in the range [10..99]
numberSums = [8..18]
This would be my final version.
Also, although the above definitions were not parameterized by the range to search for perfect squares in, all the proposed refactorings can be applied when that is a parameter; I leave this as a good exercise for the reader to check that they have understood each change.

Why doesn't this Haskell code compile? [duplicate]

I'm just learning haskell (on my own, for fun) and I've come up against a wall.
My Question:
How can I define a function
flrt = (floor . sqrt)
When I try it in a file and compile, GCHi complains with the following:
AKS.hs:11:9:
No instance for (RealFrac Integer)
arising from a use of `floor'
Possible fix: add an instance declaration for (RealFrac Integer)
In the first argument of `(.)', namely `floor'
In the expression: (floor . sqrt)
In an equation for `flrt': flrt = (floor . sqrt)
AKS.hs:11:17:
No instance for (Floating Integer)
arising from a use of `sqrt'
Possible fix: add an instance declaration for (Floating Integer)
In the second argument of `(.)', namely `sqrt'
In the expression: (floor . sqrt)
In an equation for `flrt': flrt = (floor . sqrt)
I don't understand why the resulting function isn't just Int -> Int.
I've just finished my second year of CS and done a basic PL course. I've heard of, but don't quite get types yet. I tried reading through a few haskell tutorials but it's all going above my head.
P.S. - I also don't understand what a monad is. (a lot of the other questions that my search turned up talked about these)
P.P.S. - My full source
bar = \a b -> if (2^a) > b
then (a-1)
else bar (a+1) b
foo = bar 1
flrt :: Integer -> Integer
flrt = (floor . sqrt)
aks target = if (target < 2)
then putStr "Not a Prime.\n\n"
else if elem (mod target 10) [0,2,4,5,6,8]
then putStr "Composite\n\n"
else if (elem target) [a^b | a <- [3,5..(flrt target)], b <- [1.. (foo target)]]
then putStr "Composite\n\n"--}
else
putStr "filler"
The problem is that you're trying to use Integer as the input. Haskell is strongly typed, which means there are no implicit coercions or conversions of any kind. Look at signatures of functions you're trying to compose:
sqrt :: Floating a => a -> a
floor :: (RealFrac a, Integral b) => a -> b
And at the signature of your function inferred by GHC:
> :t floor . sqrt
floor . sqrt :: (RealFrac b, Integral c, Floating b) => b -> c
So, to have a function that goes from Integer (which doesn't have a Floating instance) to Integer, you have to first convert your argument to Floating, which can be done by using fromIntegral:
> :t floor . sqrt . fromIntegral
floor . sqrt . fromIntegral :: (Integral a, Integral c) => a -> c
As copumpkin remarked, it might actually be a bad idea to convert to floating point here, because this comes with loss of precision and therefore might, even with rounding, yield incorrect results for sufficiently large integer inputs.
I assume all numbers you're dealing with will at least be small enough that there is some floating-point representation for them, e.g. all are < 10300. But, for instance
Prelude> round(sqrt.fromInteger$10^60 :: Double) ^ 2
1000000000000000039769249677312000395398304974095154031886336
Prelude> {- and not -} 10^60 {- == (10^30)^2 == (sqrt$10^60) ^ 2 -}
1000000000000000000000000000000000000000000000000000000000000
Which is way off, in terms of absolute difference. Still it's certainly a rather good approximation relative to the numbers themselves, so you can use it as a quickly determined starting point for an algorithm to find the exact result. You can implement Newton/Raphson (in this case AKA Heron) with Integers:
flrt :: Integer -> Integer -- flrt x ≈ √x, with flrt x^2 ≤ x < flrt(x+1)^2
flrt x = approx (round . (sqrt::Double->Double) . fromInteger $ x)
where approx r
| ctrl <= x, (r+1)^2 > x = r
| otherwise = approx $ r - diff
where ctrl = r^2
diff = (ctrl - x) // (2*r) -- ∂/∂x x² = 2x
a//b = a`div`b + if (a>0)==(b>0) then 1 else 0 -- always away from 0
This now works as desired:
*IntegerSqrt> (flrt $ 10^60) ^ 2
1000000000000000000000000000000000000000000000000000000000000
The division always away from 0 in the Newton-Raphson correction is here necessary to prevent getting stuck in an infinite recursion.

How to optimize a sum over list comprehension

I have to make a large computation (for statistics), but the following function is making haskell say nothing if n is close to 100, but I have to make n = 500. When I remove one of the factors (for example (p**fromIntegral l)) things get better. Any idea how to make the sum more efficient? Also, the 'choose' function is from a library that is optimized (hackage said). Thanks a lot
probaMetodo :: Integral b => b -> b -> Double -> b -> Double
probaMetodo i j p n = sum [(p ** fromIntegral l) * (fromIntegral(n `choose` l)) * ((1-p) ** fromIntegral (n-l)) | l <- [i,i+1..j]]

Haskell: How To Fix Error With "add An Instance Declaration For (Unbox A)" When Using Unboxed Vectors?

I have written some code in which a small part of the code takes a large one dimensional Unboxed.Vector and returns them as a Vector (Vector a).
A part of the code is giving an error. Here is a sample piece of code that is similar to the actual code and gives the same error.
import Data.Vector.Unboxed as D
xs = [0,1,2,3,4,5,6,7,8,9,10,11]
rows = 3
cols = 4
sb = D.fromList xs
takeRows::Int -> Int -> Vector Int -> Vector (Vector Int)
takeRows rows cols x0 = D.map (\x -> D.slice x (fromIntegral cols) x0) starts
where
starts = D.enumFromStepN 0 cols rows
-- takeRowsList::Int -> Int -> Vector Int -> [Vector Int]
-- takeRowsList rows cols x0 = Prelude.map (\x -> D.slice x (fromIntegral cols) x0) starts
-- where
-- starts = D.toList . D.enumFromStepN 0 cols $ rows
the error is
No instance for (Unbox (Vector Int))
arising from a use of `D.map'
Possible fix: add an instance declaration for (Unbox (Vector Int))
In the expression:
D.map (\ x -> slice x (fromIntegral cols) x0) starts
In an equation for `takeRows':
takeRows rows cols x0
= D.map (\ x -> slice x (fromIntegral cols) x0) starts
where
starts = enumFromStepN 0 cols rows
I have written a similar function takeRowsList, which makes the outer Vector as a List and this doesn't suffer from the same problem. I've also included it above but commented it out, to demonstrate my problem.
I understand that some functions need type definitions, when, I use them with Unboxed Vectors. But in this case I am stumped as to where to put a type definition. I've tried pretty much type defining everything and I keep getting the above error.
Thanks in advance for your help.
Unboxed vectors need to know the size of their elements, and that size must be constant. Vectors can have different sizes, so they can't be elements of unboxed vectors. They could be elements of boxed vectors, though, so if lists aren't good for what you do, you can make it a boxed vector (import qualified Data.Vector as B and qualify the relevant functions with B instead of D).
You cannot have an unboxed vector contain another vector. Only certain primitive datatypes can be unboxed, namely the ones for which Unbox instances are defined. Vectors are not primitive datatypes.
What you can do is have your function return a normal (boxed) vector of unboxed vectors.

Resources