5

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.
:)

Daniel Wagner
  • 145,880
  • 9
  • 220
  • 380
dbanas
  • 1,707
  • 14
  • 24
  • 4
    It *definitely* isn't sensible to ask for a value with the type you propose. Can you add `RealFrac` to your constraints? If not, what type do you want to use this with? Perhaps we can help you do something sensible with that type -- but definitely not with *every* possible pairing of `Floating` and `RealFrac` instances. – Daniel Wagner Jun 14 '19 at 14:16
  • 1
    I _agree_ with your request. IMO, the `Num` class should have and associated synonym `type Abs a :: *` and then `abs :: a -> Abs a` and `fromAbs :: Abs a -> a`. Then your constraint could be changed to `(Floating a, RealFrac (Abs a))`, and it would work. – leftaroundabout Jun 14 '19 at 14:28
  • @leftaroundabout, aside from `abs` and `signum`, `Num` is just ring operations. What do each of those add to a ring, mathematically? – dfeuer Jun 14 '19 at 20:31

2 Answers2

6

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).

melpomene
  • 84,125
  • 8
  • 85
  • 148
  • I'm not sure I like this example. Many `Num` instances, although you _can_ define them, don't really make sense mathematically – specifically, the `Num` instances for vector types like those from `hmatrix` and `linear` caused me all sorts of headache through weird bugs that _could_ have been caught by the type checker, if not for the `Num` instance that allowed innocuous number-literals to get inferred and unwanted vector type. The correct instance is usually `VectorSpace` and subclasses of that. For functions, I'm torn – this instance _makes_ sense, but there might still be better classes. – leftaroundabout Jun 14 '19 at 14:33
  • 4
    The `instance Num a => Num (IO a)` instance you propose is not lawful; there is a law saying `abs x * signum x = x`, and this is not validated for `x = putStrLn "hi!" >> return 42`. (But the rest of the argument is sound. Just a minor quibble.) – Daniel Wagner Jun 14 '19 at 15:17
  • 2
    There's [**`Data.Complex.Complex`**](http://hackage.haskell.org/package/base-4.12.0.0/docs/Data-Complex.html#t:Complex) as another example of a type that implements `Floating` but not `RealFrac` (and there really isn't a good instance of `RealFrac` for it). – Mor A. Jun 14 '19 at 22:19
  • @M.Aroosi Yeah, but you could sensibly apply `abs` to a complex number to get a real result, as suggested by OP. – melpomene Jun 14 '19 at 22:34
  • 2
    You don't even need to go all the way to `IO` to for your "generalization" to become unlawful. Consider `Maybe`. You don't satisfy `x + negate x = fromInteger 0` when `x` is `Nothing`. – Joseph Sible-Reinstate Monica Jun 15 '19 at 05:05
  • I think `e -> a` is an excellent example already. Since we don't know what `e` is, and since it could even be something like `Void`, there's absolutely no way to use the argument function! So a function with the requested polymorphic type must be constant and therefore not a ring homomorphism. – dfeuer Jun 15 '19 at 18:57
0

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
duplode
  • 33,731
  • 7
  • 79
  • 150
rampion
  • 87,131
  • 49
  • 199
  • 315