<div dir="ltr">Awesome! Lots of new info! And more importantly, I got it to work.<br><div class="gmail_extra"><div class="gmail_quote"><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div dir="ltr"><div><br></div><div><div><div>I still need to work on it a bit more, but things seems to be getting clearer.<br></div><div><br><div class="gmail_extra"><div class="gmail_quote"><span class="">On Sun, May 8, 2016 at 2:25 PM, Moritz Kiefer <span dir="ltr"><<a href="mailto:moritz.kiefer@purelyfunctional.org" target="_blank">moritz.kiefer@purelyfunctional.org</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex"><span><br>
Miguel A. Santos <<a href="mailto:miguel.a.santos.l@gmail.com" target="_blank">miguel.a.santos.l@gmail.com</a>> writes:<br>
<br>
</span><span>> Thanks a lot for your quick answer.<br>
><br>
> First, I can't get your modifications through: What are Scalar & Mode? ghc<br>
> says type/class not in scope.<br>
<br>
</span>Oh sorry you need to import Numeric.AD for that. Mode is a typeclass<br>
with an associated type called Scalar. You can just think of it as some<br>
magic that allows you to use constants in your function.<br>
<span><br></span></blockquote><div><br></div></span><div>Yes. I figured out as well. I was only importing its Mode.Reverse as R.<br></div><span class=""><div><br> </div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex"><span>
> Some more questions to help me understand your suggestions below.<br>
><br>
><br>
> On Sun, May 8, 2016 at 1:14 PM, Moritz Kiefer <<br>
> <a href="mailto:moritz.kiefer@purelyfunctional.org" target="_blank">moritz.kiefer@purelyfunctional.org</a>> wrote:<br>
><br>
>><br>
>> There are two orthogonal errors going on here:<br>
>><br>
>> 1. You need to use auto to embed constants. See the comments at the code<br>
>> below on how to use it.<br>
>><br>
>> Ah, that solves indeed the first problem. Thanks!<br>
><br>
><br>
>> 2. You need to wrap [Matrix a] in a newtype. grad requires you to<br>
>> provide a function f a -> a, however sc2 _ has the type [Matrix a] -> a<br>
>> so if you replace [] by f you end up with f (Matrix a) -> a which<br>
>> results in the error you’re seeing.<br>
>><br>
><br>
> I've problems following you here. For example this is legit and works<br>
> grad (\[x,y] -> x^2y^3) [5,7]<br>
><br>
> That is, grad here is taking a function f [a,a] -> a. That seems to work as<br>
> well with sc1 in my example: I do get the rigth gradient.<br>
<br>
</span>That function has type [a] -> a which can be rewritten as [] a -> a and if you unify [] and f you have f a<br>
-> a which is exactly what you need.<br>
<br>
However in sc2 you have a function of type [Matrix a] -> a which can be<br>
rewritten as [] (Matrix a) -> a and if you unify f and [] you end up<br>
with f (Matrix a) -> a. However Matrix a and a are not the same type so<br>
you get an error.<br>
<span><br></span></blockquote><div><br></div></span><div>I got confused by the expression "[the] function f a -> a": I though the word 'function' was referring to the symbol 'f'.<br></div><div><br>Yet, I still can't follow things completely...uhm, issuing :type grad in ghci I get <br>grad<br>  :: (Num a, Traversable f) =><br>     (forall s.<br>      Data.Reflection.Reifies s Numeric.AD.Internal.Reverse.Tape =><br>      f (Numeric.AD.Internal.Reverse.Reverse s a)<br>      -> Numeric.AD.Internal.Reverse.Reverse s a)<br>     -> f a -> f a<br><br>which I'd say could be simplified to <br></div><div>grad :: Num a => ( f Reverse s a -> Reverse s a) -> f a -> f a<br><br></div><div>Now, It's not only that I don't see your "grad expects a 'f a -> a' ", but I don't even see how something like grad (\[x,y]-> x*y) [2,3] fits...or do I? The notation 'f' seems was misleading me. I'd say what's important is its type, name Traversable f. [] seems to fit there, isn't? So the first argument of grad more or less would be what you were referring to ( f a -> a) , the second it the point to calculate the gradient at (of course a [a], or, [] a, hence, f a) and it does yield a "vector" (on paper). Interestingly, its implementation means that grad's output is the same type the input of the function we want to take its gradient of.<br><br></div><div>I think it starts making sense to me now. <br></div><span class=""><div> <br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex"><span>
<br>
>> Miguel A. Santos <<a href="mailto:miguel.a.santos.l@gmail.com" target="_blank">miguel.a.santos.l@gmail.com</a>> writes:<br>
>><br>
>> > mv _ [] = []<br>
>> > mv (M []) _ = []<br>
>> > mv ( M m ) v = ( dot (head m)  v ) :  (mv (M (tail m)) v )<br>
>> > --- two matrices<br>
>><br>
>> You need explicit type annotations to make this polymorphic here because<br>
>> of the monomorphism<br>
>> restriction.<br>
>><br>
>><br>
> Just for the sake of learning how to use that jargon in this context:<br>
> which/what is that monomorphism restriction are you referring to? Also,<br>
> when you say my mbW1 is polymorphic, do you mean, given my definition of<br>
> it, ghc cannot adscribe it one _unique_ type signature, but that will vary<br>
> depending on the context?<br>
<br>
</span>I’m going to refer you to the haskell report [1] for information on the<br>
monomorphism restriction. By polymorphic I’m referring to the choice of<br>
a which is now left open.<br>
<div><div><br></div></div></blockquote></span><div>Thanks!!<br></div><div><div class="h5"><div> </div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex"><div><div>
>> mbW1 :: 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>
>> > --- two different scoring functions<br>
>><br>
>> -- Provide a type signature and map auto over the constants<br>
>> sc1 :: (Floating b, Mode b) => [Scalar b] -> Matrix b -> b<br>
>> sc1 v m = foldr (+) 0 $ (phi' . (mv m) ) (map auto v)<br>
>><br>
><br>
>> -- Provide a type signature, use auto and use the newtype<br>
>> newtype MatrixList a = MatrixList [Matrix a] deriving<br>
>> (Functor,Foldable,Traversable)<br>
>><br>
>> sc2 :: (Floating a,Mode a) => [Scalar a] -> MatrixList a -> a<br>
>> sc2 v [m1, m2] = foldr (+) 0 $ (phi' . (mv m2) . phi' . (mv m1) ) (map<br>
>> auto v)<br>
>><br>
>> > strToInt = read :: String -> Double<br>
>> > strLToIntL = map strToInt--- 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>
>> >         putStrLn "sc xin mbW1"<br>
>><br>
>> -- That needs an explicit type annotation because mbW1 is polymorphic<br>
>>          print $ sc1 xin (mbW1 :: Matrix Double) --- ok. =<br>
>><br>
>> uhm...but it doesn't seem to give any problem, especially not after using<br>
> auto...I've still problems getting an intuition on when ghc does need "my<br>
> help" and when it can walk on it own.<br>
<br>
</div></div>Hm maybe you don’t need it after all. I thought I got an error<br>
locally. Sorry I don’t have any good tip on how to get an<br>
intuition. I add them when I’m unsure about the type of something myself<br>
to help me to figure it out and when I get an error.<br>
<span><br>
>> >         putStrLn "grad (sc1 xin) mbW1"<br>
>> >         print $ grad ( sc1 xin) mbW1   -- yields an error: expects xin<br>
>> > [Reverse s Double] instead of [Double]<br>
>> >         putStrLn "grad (sc1 [3,5,7]) mbW1"<br>
>> >         print $ grad ( sc1 [3,5,7]) mbW1   --- ok. =<br>
>> >         putStrLn "sc2 xin [mbW1,mbW2]"<br>
>> >         print $ sc2 xin [mbW1, mbW2]<br>
>> >         putStrLn "grad (sc2 [3,5,7) [mbW1,mbW2]"<br>
>><br>
>> -- Use the newtype defined above<br>
>>          print $ grad ( sc2 [3,5,7]) (MatrixList [mbW1, mbW2])  --- Error:<br>
>> see text<br>
>><br>
>> Also as a general recommendation, write your type signatures explicitely<br>
>> at least for top level definitions.<br>
>><br>
><br>
> What do you mean by "top level" definitions? --again, just a side comment<br>
> to fine-tune my jargon registers.<br>
<br>
</span>Top level definitions are the definitions in your module that are not in<br>
a let or where. So basically everything that’s accessible from other<br>
definitions outside of the current one.<br>
<br></blockquote><div><br></div></div></div><div>I still have to learn my way through all types. Sometimes this rule makes my life a bit too hard, specially<br></div><div>when I just want to quickly test some ideas, like here: logistic expects a Floating a but if I don't  make things<br></div><div>explicit, ghc was finding its way around my use of Num a and this Floating requirement of the exp function.<br><br></div><div>I'll keep this rule in mind.<br></div><div> <br></div><div>Thanks a lot!!<br><br></div><div>Regards,<br></div><div>MA<br></div></div></div></div></div></div></div></blockquote><div><br></div><div>PD: Forgot to reply to the list before... <br></div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div dir="ltr"><div><div><div><div class="gmail_extra"><div class="gmail_quote"><div><br></div><span class=""><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex">
Cheers Moritz<br>
<br>
[1] <a href="https://www.haskell.org/onlinereport/decls.html#sect4.5.5" rel="noreferrer" target="_blank">https://www.haskell.org/onlinereport/decls.html#sect4.5.5</a><br>
</blockquote></span></div><br></div></div></div></div></div>
</blockquote></div><br></div></div>