Defining the behaviour of a Num instance with other Num types and with itself

Is there a reason you made a second post? :thinking:

1 Like

It was not giving me the expected results, in fact I had mistaken the fromInteger function. I also thought I had to overload the operators for all Num types, so I made a second post. You are right, I should have continued there, I apologize.

1 Like

I have more questions related to this example:
– Why does Floating require the definition of pi? Why should pi be special and not 0 or 1?

– I tried to define Measurement as a Floating instance like this

import Numeric.AD
----

instance Floating a => Floating (Measurement a) where
    pi = Measurement pi 0 
    exp   (Measurement a b) = Measurement (exp a)   (sqrt ((b**2) * diff exp a ** 2))
    log   (Measurement a b) = Measurement (log a)   (sqrt ((b**2) * diff log a ** 2))
    sqrt  (Measurement a b) = Measurement (sqrt a)  (sqrt ((b**2) * diff sqrt a **2))
    sin   (Measurement a b) = Measurement (sin a)   (sqrt ((b**2) * diff sin a ** 2))
    cos   (Measurement a b) = Measurement (cos a)   (sqrt ((b**2) * diff cos a ** 2))
    asin  (Measurement a b) = Measurement (asin a)  (sqrt ((b**2) * diff asin a ** 2))
    acos  (Measurement a b) = Measurement (acos a)  (sqrt ((b**2) * diff acos a ** 2))
    atan  (Measurement a b) = Measurement (atan a)  (sqrt ((b**2) * diff atan a ** 2))
    sinh  (Measurement a b) = Measurement (sinh a)  (sqrt ((b**2) * diff sinh a ** 2))
    cosh  (Measurement a b) = Measurement (cosh a)  (sqrt ((b**2) * diff cosh a ** 2))
    asinh (Measurement a b) = Measurement (asinh a) (sqrt ((b**2) * diff asinh a ** 2))
    acosh (Measurement a b) = Measurement (acosh a) (sqrt ((b**2) * diff acosh a ** 2))
    atanh (Measurement a b) = Measurement (atanh a) (sqrt ((b**2) * diff atanh a ** 2))

There is a pattern, which could be rewritten in one of two ways:

sqrtDiff f a b = sqrt ((b**2) * diff f a ** 2)
newMeasurement f (Measurement c d) = Measurement (f c) (sqrtDiff f c d)

or

instance Functor Measurement where
    fmap f (Measurement a b) = Measurement (f a) (sqrt ((b**2) * diff f a ** 2))

But both do not work, why?

The first works if you provide an explicit type signature for f

{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}

import Numeric.AD

data Measurement a = Measurement !a !a

sqrtDiff (f :: forall a. Num a => a -> a) a b =
    sqrt ((b**2) * diff f a ** 2)
newMeasurement (f :: forall a. Num a => a -> a) (Measurement c d) =
    Measurement (f c) (sqrtDiff f c d)

The second doesn’t work because the fmap f of a Functor instance needs to work for f of an unrestricted type a -> b. In newMeasurement you are restricting f to forall a. Num a => a -> a.

1 Like

Were there not talks (at some point in history) about some extensions allowing restricted functors and co ?

There’s this talk:

But nothing has come from that yet. Or actually there is also a more recent talk:

But I still don’t think there have been concrete steps to actually get this into GHC.

2 Likes

Are there ways to replace every function that has Measurement as its argument with newMeasurement?
example:

w x = sin x  * 5 + x ^ 2 + tan x + 12 --myfunction
a = Measurement 10 0.1
-- if I want (w a) I need to call newMeasurement
correctResult = newMeasurement w a -- (109.92825527301224 ± 1.7225014117201172)
wrongResult = w a -- (109.92825527301224 ± 1.4791137150045124)

What do you mean “replace”?

I would like to call (w a) and get the correct result

Hmm, not really. newMeasurement w is the correct way of calling it.

1 Like

This:

(<|) :: (forall a1. Floating a1 => a1 -> a1) -> Measurement Double -> Measurement Double
(<|) = newMeasurement

allows me to do this and get the correct result:

w <| a -- (109.92825527301224 ± 1.7225014117201172)

but it is ugly

Many sins against compositionality were committed in trying to avoid ugliness.

1 Like

How about:

w = newMeasurement (\x -> sin x  * 5 + x ^ 2 + tan x + 12)
1 Like

But I don’t want to have to redefine all the functions I need by hand.
And the problem with newMeasurement is that if I should forget it once I would silently get wrong results

I would just drop the Num instance for Measurement. It doesn’t look like you actually need it any more! ad seems to take care of whatever you wanted to do with it.

If I remove Num I can no longer handle a+a, a-a, etc.
Now my code is:

data Measurement a = Measurement !a !a

instance Show a => Show (Measurement a) where
    show (Measurement v e) = "(" ++ show v ++ " ± " ++ show e ++ ")" 

instance Floating a => Num (Measurement a) where
    fromInteger n = Measurement (fromInteger n) 0
    Measurement a b + Measurement c d = Measurement (a + c) (sqrt (b**2 + d**2))
    Measurement a b - Measurement c d = Measurement (a - c) (sqrt (b**2 + d**2))
    Measurement a b * Measurement c d = Measurement z (z * sqrt ((b/a)**2+(d/c)**2)) where z = a * c
    abs (Measurement a b) = Measurement (abs a) b
    signum (Measurement a b) = Measurement (signum a) (signum b) 

instance Floating a => Fractional (Measurement a) where
    Measurement a b / Measurement c d = Measurement z (z * sqrt ((b/a)**2+(d/c)**2)) where z = a / c
    fromRational k = Measurement (fromRational k) 0

instance Floating a => Floating (Measurement a) where
    pi = Measurement pi 0 
    exp   = newMeasurement exp  
    log   = newMeasurement log  
    sqrt  = newMeasurement sqrt 
    sin   = newMeasurement sin  
    cos   = newMeasurement cos  
    asin  = newMeasurement asin 
    acos  = newMeasurement acos 
    atan  = newMeasurement atan 
    sinh  = newMeasurement sinh 
    cosh  = newMeasurement cosh 
    asinh = newMeasurement asinh
    acosh = newMeasurement acosh
    atanh = newMeasurement atanh

sqrtDiff :: Floating a => (forall a1. Floating a1 => a1 -> a1) -> a -> a -> a
sqrtDiff f a b = sqrt ((b**2) * diff f a ** 2)
newMeasurement :: Floating a => (forall a1. Floating a1 => a1 -> a1) -> Measurement a -> Measurement a
newMeasurement f (Measurement c d) = Measurement (f c) (sqrtDiff f c d)

Sure, but you won’t do those any more. You’ll write a polymorphic function of type forall a. Num a => a -> a (in which you can use +, - etc.) and then just run newMeasurement at the top level.

1 Like

you are right! thank you

1 Like

How did you find the correct type signature?
I am trying to do the same function with complex numbers, but I cannot find the correct type.

complxMeas f (Measurement (q :+ w) (r :+ t)) =
  Measurement v (sqrt (sum $ zipWith (*) gR errSq) :+ sqrt (sum $ zipWith (*) gIm errSq))
    where
      v = f [q, w] -- value of the function
      gR  = map (**2) (grad (realPart . f) [q, w]) -- sqr of the gradient of the real part
      gIm = map (**2) (grad (imagPart . f) [q, w]) -- sqr of the gradient of the imag Part
      errSq = map (**2) [r, t] -- sqr of the uncertainties

this is an example of f:

myComplexExponential :: RealFloat a => [a] -> Complex a
myComplexExponential [x, y] = exp (x:+y)

Are you looking for this? By the way, I suggest (a, a) -> Complex a rather than [a] -> Complex a.

{-# LANGUAGE RankNTypes #-}

import Numeric.AD
import Data.Complex

data Measurement a = Measurement !a !a
  deriving Show

complxMeas ::
  (forall a. RealFloat a => [a] -> Complex a) ->
  Measurement (Complex Double) ->
  Measurement (Complex Double)
complxMeas f (Measurement (q :+ w) (r :+ t)) =
  Measurement v (sqrt (sum $ zipWith (*) gR errSq) :+ sqrt (sum $ zipWith (*) gIm errSq))
    where
      v = f [q, w] -- value of the function
      gR  = map (**2) (grad (realPart . f) [q, w]) -- sqr of the gradient of the real part
      gIm = map (**2) (grad (imagPart . f) [q, w]) -- sqr of the gradient of the imag Part
      errSq = map (**2) [r, t] -- sqr of the uncertainties

myComplexExponential :: RealFloat a => [a] -> Complex a
myComplexExponential [x, y] = exp (x:+y)

example :: Measurement (Complex Double)
example = complxMeas myComplexExponential (Measurement (1 :+ 2) (3 :+ 4))

-- ghci> example
-- Measurement ((-1.1312043837568135) :+ 2.4717266720048188) (10.453111215235202 :+ 8.68670641815356)
1 Like