
Hi all, I've been trying to create working example with "ig" https://hackage.haskell.org/package/ig-0.2.2 - library over instagram API and I am facing little monad problem. Can someone advise me please how to make this small piece of code work? {-# LANGUAGE OverloadedStrings #-} import Network.HTTP.Client import Instagram code = "xxx_some_code" redirectUrl = "http://localhost:9988/instagram/oauth2/callback" credentials = Credentials "xxx_some_api_id" "xxx_some_api_secret" main :: IO () main = do manager <- newManager defaultManagerSettings token <- runInstagramT credentials manager $ getUserAccessTokenURL2 redirectUrl code print token I am getting following error: src/Main.hs:14:9: No instance for (Control.Monad.Trans.Resource.Internal.MonadResource IO) arising from a use of ‘getUserAccessTokenURL2’ In the second argument of ‘($)’, namely ‘getUserAccessTokenURL2 redirectUrl code’ In a stmt of a 'do' block: token <- runInstagramT credentials manager $ getUserAccessTokenURL2 redirectUrl code In the expression: do { manager <- newManager defaultManagerSettings; token <- runInstagramT credentials manager $ getUserAccessTokenURL2 redirectUrl code; print token } Thanks Rene

Great question! Many libraries use a monad transformer stack on top of IO
rather than a direct IO interface. This can be convenient if you are also
using such a stack, but it certainly complicates things a bit if you're
just in IO directly.
If you follow the error messages it says that it's expecting your Monad to
have an instance of MonadResource. IO does not (or else it would've just
worked). This means that you'll need to find a monad transformer that
provides MonadResource. By looking at the name "
Control.Monad.Trans.Resource.Internal.MonadResource" I know that I should
probably start looking for something called "Control.Monad.Trans.Resource".
After a bit of searching on Hackage I found
http://hackage.haskell.org/package/resourcet
The relevant function is `runResourceT` (most monad transformers are going
to have a similarly named run function to "unwrap" a transformer):
http://hackage.haskell.org/package/resourcet-1.1.5/docs/Control-Monad-Trans-...
Something like this should compile:
{-# LANGUAGE OverloadedStrings #-}
import Network.HTTP.Client
import Instagram
import Control.Monad.Trans.Resource
code = "xxx_some_code"
redirectUrl = "http://localhost:9988/instagram/oauth2/callback"
credentials = Credentials "xxx_some_api_id" "xxx_some_api_secret"
main :: IO ()
main = do
manager <- newManager defaultManagerSettings
token <- runResourceT . runInstagramT credentials manager $
getUserAccessTokenURL2 redirectUrl code
print token
On Sat, Jul 11, 2015 at 5:16 AM, René Klačan
Hi all,
I've been trying to create working example with "ig" https://hackage.haskell.org/package/ig-0.2.2 - library over instagram API and I am facing little monad problem.
Can someone advise me please how to make this small piece of code work?
{-# LANGUAGE OverloadedStrings #-}
import Network.HTTP.Client import Instagram
code = "xxx_some_code" redirectUrl = "http://localhost:9988/instagram/oauth2/callback" credentials = Credentials "xxx_some_api_id" "xxx_some_api_secret"
main :: IO () main = do manager <- newManager defaultManagerSettings token <- runInstagramT credentials manager $ getUserAccessTokenURL2 redirectUrl code print token
I am getting following error:
src/Main.hs:14:9: No instance for (Control.Monad.Trans.Resource.Internal.MonadResource IO) arising from a use of ‘getUserAccessTokenURL2’ In the second argument of ‘($)’, namely ‘getUserAccessTokenURL2 redirectUrl code’ In a stmt of a 'do' block: token <- runInstagramT credentials manager $ getUserAccessTokenURL2 redirectUrl code In the expression: do { manager <- newManager defaultManagerSettings; token <- runInstagramT credentials manager $ getUserAccessTokenURL2 redirectUrl code; print token }
Thanks
Rene
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Many libraries use a monad transformer stack on top of IO rather than a direct IO interface.
Does this mean that they do not perform IO, or do IO but "break out of" / hide their IO using unsafe or something? if we tried to call runInstagramT from a regular (non-IO) "do", would it have worked without runResourceT?

Hello,
Does this mean that they do not perform IO, or do IO but "break out of" / hide their IO using unsafe or something?
No, monad transformers sort of compose "backwards", that is, if you have something like FooT (BarT (IO a)) then after running everything, you'll get something in the lines of IO (Bar (Foo a)). That's why IO, if it is there at all, must be at the bottom of the stack. Now, I don't know the library you're using, from the docs it would appear that you indeed can runInstagramT without any IO in there, but some of the actions defined force this or that constraint, and in particular this "getUserAccessTokenURL2" forces (MonadControlBase IO m), which is more or less a fancy way of saying that there must be IO at the bottom. Best regards, Marcin Mrotek

Bob Ippolito, thank you for great explanation! Your suggestion is working.
Marcin Mrotek, thank you for additional info.
On Sat, Jul 11, 2015 at 9:09 PM, Marcin Mrotek
Hello,
Does this mean that they do not perform IO, or do IO but "break out of" / hide their IO using unsafe or something?
No, monad transformers sort of compose "backwards", that is, if you have something like FooT (BarT (IO a)) then after running everything, you'll get something in the lines of IO (Bar (Foo a)). That's why IO, if it is there at all, must be at the bottom of the stack.
Now, I don't know the library you're using, from the docs it would appear that you indeed can runInstagramT without any IO in there, but some of the actions defined force this or that constraint, and in particular this "getUserAccessTokenURL2" forces (MonadControlBase IO m), which is more or less a fancy way of saying that there must be IO at the bottom.
Best regards, Marcin Mrotek _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Imants Cekusins, Well using monad transformers like that is a fairly common design pattern in Haskell, so I think you should get used to it ;) But you don't really need to understand monad transformers in depth just to use the ig library, it appears that all actions defined there have a type like :: (MonadBaseControl IO m, MonadResource m) => _ some arguments _ -> InstagramT m _result_ The smallest monad that satisfies both (MonadBaseControl IO m) and (MonadResource m) is just (ResourceT IO), so the code suggested by Bob Ippolito token <- runResourceT . runInstagramT credentials manager $ getUserAccessTokenURL2 redirectUrl code works, because "getUserAccessTokenURL2 redirectUrl code" has type "InstagramT (ResourceT IO) OAuthToken". It is one of Haskell's features that the actual concrete type of an expression is inferred according to the context in which it appears, and thus may vary. * The whole thing starts with the type "MonadBaseControl IO m, MonadResource m => InstagramT m OAuthToken" * runInstagramT strips the InstagramT layer, leaving "MonadBaseControl IO m, MonadResource m =>m OAuthToken" * runResourceT has type "MonadBaseControl IO m => ResourceT m a -> m a", so Haskell infers that the "m OAuthToken" above is actually "MonadBaseControl IO m => ResourceT m OAuthToken". The satisfaction of the MonadResource constraint is provided by the ResouceT layer itself, which is stripped by runResourceT then. * at the end, Haskell is left with "MonadBaseControl IO m => m OAuthToken", which it tries to unify with "IO something", because you're using it in the do block of main, that must have the type IO () in the end. As "IO OAuthToken" does satisfy this constraint, everything is fine. The library uses type classes instead of this concrete type, because some users might want to supply a more complicated monad transformer stack than that, but of course you don't actually have to do this. Best regards, Marcin Mrotek

Cheers Marcin, One more question: MonadBaseControl IO m, MonadResource m => getUserAccessTokenURL2 however Monad m => getUserAccessTokenURL1 if we used getUserAccessTokenURL1, would we be able to access result "a" (Text in this case) with: token <- runInstagramT ... ?

Yes, apparently the getUserAccessTokenURL1 action doesn't do any IO or use the ResourceT transformer, so you can bind it directly to IO actions. Actually, since it works with literally any monad, you could instantiate it Identity and run it as a pure computation: let token = runIdentity . runInstagram ... Best regards, Marcin Mrotek

You're welcome :) Though I made a mistake in my previous post, if the getUserWhatever function did IO, i.e. had a type like (MonadBaseControl IO m => m a), then of course you could also use it in IO directly, but of course running it with runIdentity would no longer work. Btw. for the record, instead of something like "MonadBaseControl IO m" you may see "MonadBase IO m" or just "MonadIO m" (of which MonadBase is a generalization, to allow other base monads than just IO). All three type classes have instances for IO, so it doesn't matter at all if you use it like above (though MonadBaseControl and MonadBase require MultiParamTypeclasses and FunctionalDependencies extensions, so they might not work in compilers other than GHC) it only matters when implementing instances for other monads, as MonadBaseControl requires one to implement a little more complicated methods. Best regards, Marcin Mrotek
participants (4)
-
Bob Ippolito
-
Imants Cekusins
-
Marcin Mrotek
-
René Klačan