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

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

Why is this not enough?

complxMeas ::
  ([a] -> Complex a) ->
  Measurement (Complex Double) ->
  Measurement (Complex Double)

And even this is not enough:

complxMeas ::
  (RealFloat a => [a] -> Complex a) ->
  Measurement (Complex Double) ->
  Measurement (Complex Double)

When and why should “forall” be added?

Because

complxMeas ::
  ([a] -> Complex a) ->
  Measurement (Complex Double) ->
  Measurement (Complex Double)

and

complxMeas ::
  (RealFloat a => [a] -> Complex a) ->
  Measurement (Complex Double) ->
  Measurement (Complex Double)

respectively mean

complxMeas ::
  forall a.
  ([a] -> Complex a) ->
  Measurement (Complex Double) ->
  Measurement (Complex Double)

and

complxMeas ::
  forall a.
  (RealFloat a => [a] -> Complex a) ->
  Measurement (Complex Double) ->
  Measurement (Complex Double)

because type variables that are not explicitly qualified are implicitly qualified over the whole expression. As for why it must be

complxMeas ::
  (forall a. RealFloat a => [a] -> Complex a) ->
  Measurement (Complex Double) ->
  Measurement (Complex Double)

and not

complxMeas ::
  forall a.
  (RealFloat a => [a] -> Complex a) ->
  Measurement (Complex Double) ->
  Measurement (Complex Double)

well, in the former the implementation of comlxMeas gets to choose a. In fact it chooses a to be Double in v = f [q, w] and Numeric.AD.Internal.Reverse.Reverse s Double in the calls that in the arguments to grad. In the latter the caller gets to choose a. That’s no good! The caller could choose a to be Double. You can’t use AD on a function of type ([Double] -> Complex Double). It needs to remain symbolic.

3 Likes

Perhaps you want the below? I don’t think I really follow what you’re doing closely enough to be able to give a “systematic” procedure, but perhaps we can start with this rule of thumb:

Anything argument to grad has to be “fully polymorphic” in the sense that its type has to be forall a. Num a => <args> -> a (where args is a type involving a, in practice often [a]). When you trace the provenance of that argument to grad back to a function argument you must annotate that function argument with a “fully polymorphic” type.

So in the code below, realF and imagF must be fully polymorphic, and their provenance is from the argument g, so we have give g a “fully polymorphic” type (forall a. Num a => [a] -> a).

[EDIT: Actually RealFloat => is more general than Num => but the latter works in this case. In other cases you might need RealFloat. The type system will tell you, if so.]

{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE NoMonomorphismRestriction #-}

import Data.Complex
import Numeric.AD

complexMeasurementError ::
  (forall a. [a] -> a) ->
  ComplexMeasurement [Complex Double] ->
  ComplexMeasurement (Complex Double)
complexMeasurementError g xs =
    ComplexMeasurement res (computeError convertedEInput rGrad :+ computeError convertedEInput iGrad)
        where
            f = convertFunction1 g
            realF :: forall a. Num a => [a] -> a
            imagF :: forall a. Num a => [a] -> a
            (realF, imagF) = (realPart . f, imagPart . f)
            (vInput, eInput) = (complexValuePart xs, complexErrorPart xs)
            (convertedVInput, convertedEInput) = (convertInput vInput, convertInput eInput)
            res = f convertedVInput
            (rGrad, iGrad) = (grad realF convertedVInput, grad imagF convertedVInput)

data ComplexMeasurement a = ComplexMeasurement !a !a deriving Show

complexValuePart :: ComplexMeasurement a -> a
complexValuePart (ComplexMeasurement v _) = v
complexErrorPart :: ComplexMeasurement a -> a
complexErrorPart (ComplexMeasurement _ e) = e

-- example: (f [3:+2, 4:+1]) ----> (f [3, 2, 4, 1]) with the same result
convertFunction1 :: ([Complex a] -> b) -> ([a] -> b)
convertFunction1 f x = f [x!!i :+ x!!(i+1) | i <- [0, 2..length x - 1]]

realAndImag :: Complex a -> [a]
realAndImag (x :+ y) = [x, y]
-- convert the input for the convertedfunction
convertInput :: [Complex a] -> [a]
convertInput = concatMap realAndImag

computeError :: Floating a => [a] -> [a] -> a
computeError es gs = sqrt $ sum $ map (**2) $ zipWith (*) gs es

-- the algorithm inside the function
a = ComplexMeasurement (2:+3.2) (0.1:+0.27)
1 Like

I removed the previous comment because it contained an example that was too specific.
Here is a simpler example:

-- I have a function f that compute a complex function 
-- of a list of complex args
f :: RealFloat a => [Complex a] -> Complex a
f [q, w] = exp q + sin w
f _ = error "error"
-- f [3:+1, 1:+2] -- 14.018040427414126 :+ 18.8609975765717
---------------------------------------------------------------
--I don't want to work with complex functions so I convert it
-- to a function that takes a list of reals
---------------------------------------------------------------
-- change f to a function that takes a list of reals
-- instead of a list of complex 
convertFunction1 :: ([Complex a] -> b) -> ([a] -> b)
convertFunction1 f x = f [x!!i :+ x!!(i+1) | i <- [0, 2..length x - 1]]
g = convertFunction1 f
-- g [3, 1, 1, 2] == f [3:+1, 1:+2]
-- now g is a function that takes reals and spits out a Complex
----------------------------------------------------------------
-- I must also change the input of f to an input of converted function
realAndImag :: Complex a -> [a]
realAndImag (x :+ y) = [x, y]
convertInput :: [Complex a] -> [a]
convertInput = concatMap realAndImag
-- convertInput [3:+1, 1:+2] -> [3, 1, 1, 2]
-- now g $ convertInput [3:+1, 1:+2] gives the same result of f [3:+1, 1:+2]

xs = convertInput [3.0:+1.0, 1.0:+2.0]
---------------------------------------------------------------
-- finally myFunc is a function that return the sum of the gradients 
-- of the imagPart and realPart of g
myFunc g xs =
    sum (grad imagG xs) + sum (grad realG xs)
    where 
        imagG = imagPart . g
        realG = realPart . g
result = myFunc g xs

I don’t understand how to write the type signature for myFunc.

As I said above, everything that’s going to be the argument to grad has to be kept fully polymorphic, by annotating it with an explicit type signature, like this

{-# LANGUAGE RankNTypes #-}

module Test where

import Data.Complex
import Numeric.AD

-- I have a function f that compute a complex function
-- of a list of complex args
f :: RealFloat a => [Complex a] -> Complex a
f [q, w] = exp q + sin w
f _ = error "error"
-- f [3:+1, 1:+2] -- 14.018040427414126 :+ 18.8609975765717
---------------------------------------------------------------
--I don't want to work with complex functions so I convert it
-- to a function that takes a list of reals
---------------------------------------------------------------
-- change f to a function that takes a list of reals
-- instead of a list of complex
convertFunction1 :: ([Complex a] -> b) -> ([a] -> b)
convertFunction1 f x = f [x!!i :+ x!!(i+1) | i <- [0, 2..length x - 1]]

g :: forall a. RealFloat a => [a] -> Complex a
g = convertFunction1 f
-- g [3, 1, 1, 2] == f [3:+1, 1:+2]
-- now g is a function that takes reals and spits out a Complex
----------------------------------------------------------------
-- I must also change the input of f to an input of converted function
realAndImag :: Complex a -> [a]
realAndImag (x :+ y) = [x, y]
convertInput :: [Complex a] -> [a]
convertInput = concatMap realAndImag
-- convertInput [3:+1, 1:+2] -> [3, 1, 1, 2]
-- now g $ convertInput [3:+1, 1:+2] gives the same result of f [3:+1, 1:+2]

xs = convertInput [3.0:+1.0, 1.0:+2.0]
---------------------------------------------------------------
-- finally myFunc is a function that return the sum of the gradients
-- of the imagPart and realPart of g

myFunc :: (forall a. RealFloat a => [a] -> Complex a) -> [Double] -> Double
myFunc g xs =
    sum (grad imagG xs) + sum (grad realG xs)
    where
        imagG :: forall a. RealFloat a => [a] -> a
        imagG = imagPart . g
        realG :: forall a. RealFloat a => [a] -> a
        realG = realPart . g

result = myFunc g xs
1 Like