[Haskell-cafe] Automatic differentiation (AD) with respect to list of matrices in Haskell

Miguel A. Santos miguel.a.santos.l at gmail.com
Tue May 10 20:01:22 UTC 2016


Sorry, while that all did work before, it looks like I screwed up again.
Tried playing around varying things trying to understand your fix better,
but I seem not to be able to figured out how to fix it now. This type
issues feel bizarre!

The code below doesn't compile. The error is now on a line that before gave
absolutely no problem before, name the evaluation of sc1 xin mbW1. The
error is now, basically, "expected [Scalar a] ; Actual [Double a]" and
explicitly stating types doesn't help either. That is, explicitly declaring
sc1 type as "sc1 :: (Floating a, Mode a) => [Scalar a] -> Matrix a -> a"
still gives that error.

Yet, there is no problem in calculating its gradient, namely "grad (sc1
xin) mbW1" works ok !?

I'm at lost here. What's wrong/missing now?  Evaluation of sc0 or sc2 on
the input list xin works, but no for sc1!?

Somehow, from the detailed error message (see below) it looks like ghc
can't really figure out the type of 'a' in '[Scalar a]'. Some lack of
injectivity issues or so? And I can only imaging that the type Double it
sees may be induced by the use of the exponential implicit in the
definition of `phi'` which is used in that of sc1, but I have no clue how
to tweak `phi'`.

As I said before, I still don't grasp Haskell's type system. Usually it
seems easier to not give explicitly a type and let ghc guess it.
Unfortunately this doesn't work in the present case. I apologize in advance
if I happen to be missing something elementary. I just don't see it.

Regards,
MA

PD:
Without the offending line evaluating sc1, the output of the program is
(again the 1,2,3 is my arbitrary input to the program):

--------
mbW1:M [[1,0,0],[-1,5,1],[1,2,-3]]
mbW2:M [[0,0,0],[1,3,-1],[-2,4,6]]
---
sc0:
---
sc0 xin mbW1
1
2
3
9.0
grad (sc0 [3,5,7]) mbW1
M [[3,5,7],[3,5,7],[3,5,7]]
---
sc1:
---
grad (sc1 xin) mbW1
M
[[1.0,2.0,3.0],[6.1441368513331755e-6,1.2288273702666351e-5,1.8432410553999525e-5],[1.7662706213291118e-2,3.5325412426582235e-2,5.298811863987335e-2]]
grad (sc1 [3,5,7]) mbW1
M
[[3.0,5.0,7.0],[7.630996942126885e-13,1.2718328236878141e-12,1.7805659531629398e-12],[1.0057130122694228e-3,1.6761883537823711e-3,2.3466636952953197e-3]]
---
sc2:
---
sc2 xin [mbW1,mbW2]
1.8733609463863194
---
sc3:
---
grad (sc3 xin) [mbW1,mbW2]
MatrixList [M
[[-0.1752205960584877,-0.3504411921169754,-0.525661788175463],[2.7052661672554392e-6,5.4105323345108785e-6,8.115798501766318e-6],[9.919472739879849e-3,1.9838945479759697e-2,2.9758418219639544e-2]],M
[[1.0,0.9999938558253978,1.798620996209156e-2],[1.79718498433056e-2,1.7971739421122238e-2,3.232454646888768e-4],[9.659622295089665e-2,9.659562944683693e-2,1.7373999475398345e-3]]]
--------

and the code producing that output is:

--------
        {-# LANGUAGE DeriveTraversable, DeriveFunctor, DeriveFoldable #-}
    import Numeric.AD
    import Numeric.AD.Mode.Reverse as R
    import Data.Traversable as T
    import Data.Foldable as F

    --- Non-linear function on "vectors"
    logistic x = 1.0 / (1.0 + exp(-x) )
    phi v = map logistic v
    phi' (x:xs) = x : (phi xs)

    --- dot product
    dot u v = foldr (+) 0 $ zipWith (*) u v

    --- simple matrix type
    data Matrix a = M [[a]] deriving
(Eq,Show,Functor,F.Foldable,T.Traversable)

    --- action of a matrix on a vector
    mv _ [] = []
    mv (M []) _ = []
    mv ( M m ) v = ( dot (head m)  v ) :  (mv (M (tail m)) v )

    --- two matrices
    mbW1,mbW2 :: Num a => Matrix a
    mbW1 = M $ [[1,0,0],[-1,5,1],[1,2,-3]]
    mbW2 = M $ [[0,0,0],[1,3,-1],[-2,4,6]]

    --- different scoring functions
    sc0 v m = foldr (+) 0 $ mv m v

    --sc1 :: (Floating a, Mode a) => [Scalar a] -> Matrix a -> a
    sc1 v m = foldr (+) 0 $ (phi' . (mv m) )  (map auto v)

    --sc2 :: Floating a => [a] -> [Matrix a] -> a
    sc2 v [m1, m2] = foldr (+) 0 $ (phi' . (mv m2) . phi' . (mv m1) ) v

    -- Provide a type signature, use auto and use the newtype
    newtype MatrixList a = MatrixList [Matrix a] deriving (Show,
Functor,Foldable,Traversable)

    sc3 :: (Floating a, Mode a) => [Scalar a] -> MatrixList a -> a
    sc3 v (MatrixList [m1, m2]) = foldr (+) 0 $ (phi' . (mv m2) . phi' .
(mv m1) ) (map auto v)


    strToInt = read :: String -> Double
    strLToIntL = map strToInt
    --- testing
    main = do
            putStrLn $ "mbW1:" ++ (show mbW1)
            putStrLn $ "mbW2:" ++ (show mbW2)
            rawInput <-  readFile "/dev/stdin"
            let xin= strLToIntL $ lines rawInput
            ---
            putStrLn "---\nsc0:\n---"
            ---
            --putStrLn "sc0 [3,5,7] mbW1"
            --print $ sc0 [3,5,7] mbW1
            putStrLn "sc0 xin mbW1"
            print $ sc0 xin mbW1
            putStrLn "grad (sc0 [3,5,7]) mbW1"
            print $ grad ( sc0 [3,5,7]) mbW1
            --print $ grad ( sc0 xin) mbW1
            ---
            putStrLn "---\nsc1:\n---"
            ---
            --putStrLn "sc1 xin mbW1"
            --print $ sc1 xin mbW1  --- ok. =     NOT OK anymore using map
auto!? : Expected [Scalar a0] ; Actual [Double]
            putStrLn "grad (sc1 xin) mbW1"
            print $ grad ( sc1 xin) mbW1   -- ok now just with auto !? Was:
yields an error: expects xin [Reverse s Double] instead of [Double]
            putStrLn "grad (sc1 [3,5,7]) mbW1"
            print $ grad ( sc1 [3,5,7]) mbW1   --- ok. =
            ---
            putStrLn "---\nsc2:\n---"
            ---
            putStrLn "sc2 xin [mbW1,mbW2]"
            print $ sc2 xin [mbW1, mbW2]
            ---
            putStrLn "---\nsc3:\n---"
            ---
            putStrLn "grad (sc3 xin) [mbW1,mbW2]"
            print $ grad ( sc3 xin) (MatrixList [mbW1, mbW2])
--------

When trying to evaluate 'sc1 xin mbW1', the he precise error message is:

--------
    Couldn't match type ‘Scalar r0’ with ‘Double’
    The type variable ‘r0’ is ambiguous
    Expected type: [Scalar r0]
      Actual type: [Double]
    In the first argument of ‘sc1’, namely ‘xin’
    In the second argument of ‘($)’, namely ‘sc1 xin mbW1’







--
Public key ID: E8FE60D7
Public key server: see, e.g., hkp://keys.gnupg.net
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160510/5b96dbcf/attachment.html>


More information about the Haskell-Cafe mailing list