dbanas
dbanas

Reputation: 1898

Is there a standard Haskell function with type: (Floating a, RealFrac b) => a -> b?

I need to call floor() on a value, which is only constrained to be of class Floating, but floor() requires RealFrac.

How can I do this?

I'm perfectly willing to call abs() before calling floor(), but this alone seems insufficient to solve my constraint conflict. And coerce complains that the two representations cannot be assumed equivalent, which isn't surprising.

It seems what I need is a function with type signature:

(Floating a, RealFrac b) => a -> b

And it seems (to me) perfectly legitimate to give some augmented version of abs() this signature. Alas, a Hoogle search on the above type signature left me empty handed.

Any thoughts?

Thanks.
:)

Upvotes: 5

Views: 235

Answers (2)

rampion
rampion

Reputation: 89093

Can you afford an Ord constraint?

module FBound (ffloor, fceil) where
import Data.List (foldl')

-- |
-- >>> ffloor . fromInteger <$> [-10..10]
-- [-10,-9,-8,-7,-6,-5,-4,-3,-2,-1,0,1,2,3,4,5,6,7,8,9,10]
-- >>> ffloor . (+0.001) . fromInteger <$> [-10..10]
-- [-10,-9,-8,-7,-6,-5,-4,-3,-2,-1,0,1,2,3,4,5,6,7,8,9,10]
-- >>> ffloor . (+0.999) . fromInteger <$> [-10..10]
-- [-10,-9,-8,-7,-6,-5,-4,-3,-2,-1,0,1,2,3,4,5,6,7,8,9,10]
ffloor :: (Ord a, Floating a, Integral b) => a -> b
ffloor a | a >= 0     = ffloor' a
         | otherwise  = negate $ fceil' (-a)

-- |
-- >>> fceil. fromInteger <$> [-10..10]
-- [-10,-9,-8,-7,-6,-5,-4,-3,-2,-1,0,1,2,3,4,5,6,7,8,9,10]
-- >>> fceil . (-0.001) . fromInteger <$> [-10..10]
-- [-10,-9,-8,-7,-6,-5,-4,-3,-2,-1,0,1,2,3,4,5,6,7,8,9,10]
-- >>> fceil . (-0.999) . fromInteger <$> [-10..10]
-- [-10,-9,-8,-7,-6,-5,-4,-3,-2,-1,0,1,2,3,4,5,6,7,8,9,10]
fceil :: (Ord a, Floating a, Integral b) => a -> b
fceil a | a >= 0     = fceil' a
        | otherwise  = negate $ ffloor' (-a)

-- given a >= 0, ffloor' a <= a < ffloor' a + 1
ffloor' :: (Ord a, Floating a, Integral b) => a -> b
ffloor' = foldl' roundDown 0 . reverse . takeWhile (>=1) . iterate (/2)

-- given a >= 0, fceil' a - 1 < a <= fceil' a
fceil' :: (Ord a, Floating a, Integral b) => a -> b
fceil' a = ffloor' (a/2) `roundUp` a

-- given 2*i <= a < 2*i + 2, roundDown i a <= a < roundDown i a + 1
roundDown :: (Ord a, Num a, Integral b) => b -> a -> b
roundDown i a | a < fromIntegral (2*i + 1) = 2*i
              | otherwise                  = 2*i + 1

-- given 2*i <= a < 2*i + 2, roundUp i a - 1 < a <= roundUp i a
roundUp :: (Ord a, Num a, Integral b) => b -> a -> b
roundUp i a | a == fromIntegral (2*i)     = 2*i
            | a <= fromIntegral (2*i + 1) = 2*i + 1
            | otherwise                   = 2*i + 2

Upvotes: 0

melpomene
melpomene

Reputation: 85837

Consider the following instance of Floating:

import Control.Applicative

instance (Num a) => Num (e -> a) where
    (+) = liftA2 (+)
    (*) = liftA2 (*)
    (-) = liftA2 (-)
    abs = fmap abs
    signum = fmap signum
    negate = fmap negate
    fromInteger = pure . fromInteger

instance (Fractional a) => Fractional (e -> a) where
    fromRational = pure . fromRational
    recip = fmap recip
    (/) = liftA2 (/)

instance (Floating a) => Floating (e -> a) where
    pi = pure pi
    exp = fmap exp
    log = fmap log
    sin = fmap sin
    cos = fmap cos
    asin = fmap asin
    acos = fmap acos
    atan = fmap atan
    sinh = fmap sinh
    cosh = fmap cosh
    asinh = fmap asinh
    acosh = fmap acosh
    atanh = fmap atanh

Demo:

main :: IO ()
main = do
    print (sqrt sqrt 81)
    let f = sin^2 + cos^2
    print (f 42)

(This outputs 3.0000000000000004 and 1.0.)

This makes functions an instance of Floating, but the code generalizes to all types that are Monads or Applicatives.

Your hypothetical function would need to have the type

(Floating a, RealFrac b) => (e -> a) -> b

in this instance. We could set a and b to Double:

(e -> Double) -> Double

How do you implement that operation?

Remember that I said this generalizes to all Applicatives? We can replace e -> by IO in the above instances. Then the type you end up with gets even worse:

IO Double -> Double

The problem is that Floating can be anything that supports e.g. exp or sin operations (which could be purely symbolic operations e.g. on a syntax tree) while RealFrac must be a number (or something convertible to a number).

Upvotes: 6

Related Questions