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)