
Hi haskellers, I am trying to understand why I get the following error in learning applicative style. Prelude> let estimates = [5,5,8,8,2,1,5,2] Prelude> (/) <$> Just $ foldl (+) 0 estimates <*> Just . fromIntegral $ length estimates <interactive>:54:1: Non type-variable argument in the constraint: Fractional (Maybe r) (Use FlexibleContexts to permit this) When checking that 'it' has the inferred type it :: forall a r. (Fractional (Maybe r), Num a, Num (Int -> Maybe a -> r)) => Maybe r -> Maybe r All the parts work individually. If use let and assign the parts to x and y it also works. E.g. This works let x = Just $ foldl (+) estimates Let y = Just . fromIntegral $ length estimates (/) <$> x <*> y I clearly do not understand exactly how these work. :-) Thanks for any help, -wes

On Fri, Aug 28, 2015 at 1:12 PM, Williams, Wes(AWF)
Num (Int -> Maybe a -> r))
That looks highly suspect. If it infers a function Num instance, you probably got your parentheses wrong. Or your $-s... ...in fact, that is the problem. That final $ does not do what you think; it produces (foldl (+) 0 estimates <*> Just . fromIntegral) (length estimates) when you presumably intended foldl (+) 0 estimates <+> (Just . fromIntegral) (length estimates) -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

This mail got stuck in my spam filter because of auth reason.
Bumping in case someone else who missed it wants to answer.
2015-08-28 19:12 GMT+02:00 Williams, Wes(AWF)
Hi haskellers,
I am trying to understand why I get the following error in learning applicative style.
Prelude> let estimates = [5,5,8,8,2,1,5,2]
Prelude> (/) <$> Just $ foldl (+) 0 estimates <*> Just . fromIntegral $ length estimates
<interactive>:54:1:
Non type-variable argument in the constraint: Fractional (Maybe r)
(Use FlexibleContexts to permit this)
When checking that ‘it’ has the inferred type
it :: forall a r.
(Fractional (Maybe r), Num a, Num (Int -> Maybe a -> r)) =>
Maybe r -> Maybe r
All the parts work individually. If use let and assign the parts to x and y it also works.
E.g. This works let x = Just $ foldl (+) estimates Let y = Just . fromIntegral $ length estimates (/) <$> x <*> y
I clearly do not understand exactly how these work. :-)
Thanks for any help, -wes
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

David Moberg
This mail got stuck in my spam filter because of auth reason. Bumping in case someone else who missed it wants to answer.
2015-08-28 19:12 GMT+02:00 Williams, Wes(AWF)
: Hi haskellers,
I am trying to understand why I get the following error in learning applicative style.
Prelude> let estimates = [5,5,8,8,2,1,5,2]
Prelude> (/) <$> Just $ foldl (+) 0 estimates <*> Just . fromIntegral $ length estimates
I think $ is the culprit. You can not combine $ and <*> and get what you expect, because $ works on *the whole* expression: Prelude> (/) <$> Just (foldl (+) 0 estimates) <*> Just (fromIntegral (length estimates)) Just 4.5 Another problem was (.), you actually don't need any function composition here. -- CYa, ⡍⠁⠗⠊⠕
participants (4)
-
Brandon Allbery
-
David Moberg
-
Mario Lang
-
Williams, Wes(AWF)