<div dir="ltr"><div class="gmail_extra">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!<br><br>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. <br><br></div><div class="gmail_extra">Yet, there is no problem in calculating its gradient, namely "grad (sc1 xin) mbW1" works ok !?<br><br></div><div class="gmail_extra">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!? <br><br>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'`. <br><br></div><div class="gmail_extra">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.<br><br></div><div class="gmail_extra">Regards,<br></div><div class="gmail_extra">MA<br><br></div><div class="gmail_extra">PD:<br></div><div class="gmail_extra">Without the offending line evaluating sc1, the output of the program is (again the 1,2,3 is my arbitrary input to the program):<br><br>--------<br><div style="margin-left:40px"><span style="font-family:monospace,monospace">mbW1:M [[1,0,0],[-1,5,1],[1,2,-3]]<br>mbW2:M [[0,0,0],[1,3,-1],[-2,4,6]]<br>---<br>sc0:<br>---<br>sc0 xin mbW1<br>1<br>2<br>3<br>9.0<br>grad (sc0 [3,5,7]) mbW1<br>M [[3,5,7],[3,5,7],[3,5,7]]<br>---<br>sc1:<br>---<br>grad (sc1 xin) mbW1<br>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]]<br>grad (sc1 [3,5,7]) mbW1<br>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]]<br>---<br>sc2:<br>---<br>sc2 xin [mbW1,mbW2]<br>1.8733609463863194<br>---<br>sc3:<br>---<br>grad (sc3 xin) [mbW1,mbW2]<br>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]]]</span><span style="font-family:monospace,monospace"></span><br></div>--------<br><br></div><div class="gmail_extra">and the code producing that output is:<br><br>--------<br><span style="font-family:monospace,monospace">        {-# LANGUAGE DeriveTraversable, DeriveFunctor, DeriveFoldable #-}<br>    import Numeric.AD<br>    import Numeric.AD.Mode.Reverse as R<br>    import Data.Traversable as T<br>    import Data.Foldable as F<br><br>    --- Non-linear function on "vectors"<br>    logistic x = 1.0 / (1.0 + exp(-x) )<br>    phi v = map logistic v<br>    phi' (x:xs) = x : (phi xs)<br><br>    --- dot product<br>    dot u v = foldr (+) 0 $ zipWith (*) u v<br><br>    --- simple matrix type<br>    data Matrix a = M [[a]] deriving (Eq,Show,Functor,F.Foldable,T.Traversable)<br><br>    --- action of a matrix on a vector<br>    mv _ [] = []<br>    mv (M []) _ = []<br>    mv ( M m ) v = ( dot (head m)  v ) :  (mv (M (tail m)) v )<br><br>    --- two matrices<br>    mbW1,mbW2 :: Num a => Matrix a<br>    mbW1 = M $ [[1,0,0],[-1,5,1],[1,2,-3]]<br>    mbW2 = M $ [[0,0,0],[1,3,-1],[-2,4,6]]<br><br>    --- different scoring functions<br>    sc0 v m = foldr (+) 0 $ mv m v<br><br>    --sc1 :: (Floating a, Mode a) => [Scalar a] -> Matrix a -> a<br>    sc1 v m = foldr (+) 0 $ (phi' . (mv m) )  (map auto v)<br><br>    --sc2 :: Floating a => [a] -> [Matrix a] -> a<br>    sc2 v [m1, m2] = foldr (+) 0 $ (phi' . (mv m2) . phi' . (mv m1) ) v<br><br>    -- Provide a type signature, use auto and use the newtype<br>    newtype MatrixList a = MatrixList [Matrix a] deriving (Show, Functor,Foldable,Traversable)<br><br>    sc3 :: (Floating a, Mode a) => [Scalar a] -> MatrixList a -> a<br>    sc3 v (MatrixList [m1, m2]) = foldr (+) 0 $ (phi' . (mv m2) . phi' . (mv m1) ) (map auto v)<br><br><br>    strToInt = read :: String -> Double<br>    strLToIntL = map strToInt<br>    --- testing<br>    main = do<br>            putStrLn $ "mbW1:" ++ (show mbW1)<br>            putStrLn $ "mbW2:" ++ (show mbW2)<br>            rawInput <-  readFile "/dev/stdin"<br>            let xin= strLToIntL $ lines rawInput<br>            ---<br>            putStrLn "---\nsc0:\n---"<br>            ---<br>            --putStrLn "sc0 [3,5,7] mbW1"<br>            --print $ sc0 [3,5,7] mbW1<br>            putStrLn "sc0 xin mbW1"<br>            print $ sc0 xin mbW1<br>            putStrLn "grad (sc0 [3,5,7]) mbW1"<br>            print $ grad ( sc0 [3,5,7]) mbW1<br>            --print $ grad ( sc0 xin) mbW1<br>            ---<br>            putStrLn "---\nsc1:\n---"<br>            ---<br>            --putStrLn "sc1 xin mbW1"<br>            --print $ sc1 xin mbW1  --- ok. =     NOT OK anymore using map auto!? : Expected [Scalar a0] ; Actual [Double]<br>            putStrLn "grad (sc1 xin) mbW1"<br>            print $ grad ( sc1 xin) mbW1   -- ok now just with auto !? Was: yields an error: expects xin [Reverse s Double] instead of [Double]<br>            putStrLn "grad (sc1 [3,5,7]) mbW1"<br>            print $ grad ( sc1 [3,5,7]) mbW1   --- ok. =<br>            ---<br>            putStrLn "---\nsc2:\n---"<br>            ---<br>            putStrLn "sc2 xin [mbW1,mbW2]"<br>            print $ sc2 xin [mbW1, mbW2]<br>            ---<br>            putStrLn "---\nsc3:\n---"<br>            ---<br>            putStrLn "grad (sc3 xin) [mbW1,mbW2]"<br>            print $ grad ( sc3 xin) (MatrixList [mbW1, mbW2])<br></span>--------<br><br></div><div class="gmail_extra">When trying to evaluate 'sc1 xin mbW1', the he precise error message is:<br><br>--------<br><span style="font-family:monospace,monospace">    Couldn't match type ‘Scalar r0’ with ‘Double’<br>    The type variable ‘r0’ is ambiguous<br>    Expected type: [Scalar r0]<br>      Actual type: [Double]<br>    In the first argument of ‘sc1’, namely ‘xin’<br>    In the second argument of ‘($)’, namely ‘sc1 xin mbW1’<br></span><br><br></div><div class="gmail_extra"> <br></div><div class="gmail_extra"><br></div><div class="gmail_extra"><br> <br></div><div class="gmail_extra"><br clear="all"><div><div class="gmail_signature"><div dir="ltr"><div><div dir="ltr">--<br>Public key ID: E8FE60D7 <br>Public key server: see, e.g., hkp://<a href="http://keys.gnupg.net" target="_blank">keys.gnupg.net</a> <br></div></div></div></div></div>
</div></div>