Ambiguous MonadIO and Monad

Hi, I'm trying to understand how Network.OAuth.Consumer works, and run sample code found here with Twitter API. (the full code is attached at the bottom) http://hackage.haskell.org/packages/archive/hoauth/0.3.3/doc/html/Network-OA... When I load the test code with GHCi 7.0.2, it raises error: --- Error message begin TestOAuth.hs:21:103: Ambiguous type variable `m0' in the constraints: (MonadIO m0) arising from a use of `serviceRequest' at TestOAuth.hs:21:103-116 (Monad m0) arising from a use of `>>=' at TestOAuth.hs:21:99-101 Possible cause: the monomorphism restriction applied to the following: response :: m0 Response (bound at TestOAuth.hs:17:1) Probable fix: give these definition(s) an explicit type signature or use -XNoMonomorphismRestriction In the second argument of `(>>=)', namely `serviceRequest CurlClient' In the expression: signRq2 HMACSHA1 (Just $ Realm "realm") srvUrl >>= serviceRequest CurlClient In the second argument of `($)', namely `do { signRq2 PLAINTEXT Nothing reqUrl >>= oauthRequest CurlClient; cliAskAuthorization authUrl; signRq2 PLAINTEXT Nothing accUrl >>= oauthRequest CurlClient; signRq2 HMACSHA1 (Just $ Realm "realm") srvUrl >>= serviceRequest CurlClient }' --- Error message end I seem using NoMonomorphismRestriction is workaround, so I want to add a proper type signature, but I cannot figure out what it is. What confuses me is why GHC didn't just take MonadIO as MonadIO is a Monad according to the definition. http://hackage.haskell.org/packages/archive/transformers/0.2.2.0/doc/html/Co... I tried to add a type signature by replacing the second line from the bottom with this, in vain. ((signRq2 HMACSHA1 (Just $ Realm "realm") srvUrl) :: (MonadIO m) => OAuthMonadT m OAuthRequest) >>= serviceRequest CurlClient Can you help me find what's wrong with this? Thanks in advance, Ken --- Test code (TestOAuth.hs) import Control.Monad.IO.Class (MonadIO) import Data.Maybe (fromJust) import Network.OAuth.Consumer import Network.OAuth.Http.CurlHttpClient import Network.OAuth.Http.Request import Network.OAuth.Http.Response consumerKey = "MY CONSUMER KEY" consumerSec = "MY CONSUMER SEC" reqUrl = fromJust . parseURL $ "https://api.twitter.com/oauth/request_token" accUrl = fromJust . parseURL $ "https://api.twitter.com/oauth/access_token" srvUrl = fromJust . parseURL $ "http://service/path/to/resource/" authUrl = ("https://api.twitter.com/oauth/authorize?oauth_token="++) . findWithDefault ("oauth_token","ERROR") . oauthParams app = Application consumerKey consumerSec OOB response = runOAuthM (fromApplication app) $ do { signRq2 PLAINTEXT Nothing reqUrl >>= oauthRequest CurlClient ; cliAskAuthorization authUrl ; signRq2 PLAINTEXT Nothing accUrl >>= oauthRequest CurlClient ; signRq2 HMACSHA1 (Just $ Realm "realm") srvUrl >>= serviceRequest CurlClient }

On Wednesday 07 March 2012, 00:42:05, Ken KAWAMOTO wrote:
Hi,
I'm trying to understand how Network.OAuth.Consumer works, and run sample code found here with Twitter API. (the full code is attached at the bottom) http://hackage.haskell.org/packages/archive/hoauth/0.3.3/doc/html/Networ k-OAuth-Consumer.html
When I load the test code with GHCi 7.0.2, it raises error:
--- Error message begin TestOAuth.hs:21:103: Ambiguous type variable `m0' in the constraints: (MonadIO m0) arising from a use of `serviceRequest' at TestOAuth.hs:21:103-116 (Monad m0) arising from a use of `>>=' at TestOAuth.hs:21:99-101 Possible cause: the monomorphism restriction applied to the following: response :: m0 Response (bound at TestOAuth.hs:17:1) Probable fix: give these definition(s) an explicit type signature or use -XNoMonomorphismRestriction In the second argument of `(>>=)', namely
I seem using NoMonomorphismRestriction is workaround, so I want to add a proper type signature, but I cannot figure out what it is.
What confuses me is why GHC didn't just take MonadIO as MonadIO is a Monad according to the definition.
From the definition of response, the two constraints MonadIO m0 Monad m0 are inferred. Since response is bound by a simple pattern binding (no function arguments) and without a type signature, by the monomorphism restriction, it must get a monomorphic type, so the compiler tries to find a specific MonadIO (and Monad, but that would follow) to use. But there is no defaulting for those constraints (defaulting takes place for constraints where at least one of the involved classes is a numeric class [Num, Integral, Fractional, ...], and all involved classes are defined in the standard libraries), so that fails (no numeric class, and MonadIO is defined outside the standard libraries). To fix it, you just have to define response with a type signature, response :: MonadIO m => m Response You should give all your top-level definitions type signatures anyway. It's good for documentation, and it gives you much better error messages if you make a mistake.

Thanks Daniel.
Adding a type signature to response did resolve the issue.
The monomorphism restriction
(http://www.haskell.org/haskellwiki/Monomorphism_restriction)
is still a bit hard for me, but I'll definitely add type signatures to
all top-level defs to avoid this kind of issues.
-- Ken
On Wed, Mar 7, 2012 at 9:55 AM, Daniel Fischer
On Wednesday 07 March 2012, 00:42:05, Ken KAWAMOTO wrote:
Hi,
I'm trying to understand how Network.OAuth.Consumer works, and run sample code found here with Twitter API. (the full code is attached at the bottom) http://hackage.haskell.org/packages/archive/hoauth/0.3.3/doc/html/Networ k-OAuth-Consumer.html
When I load the test code with GHCi 7.0.2, it raises error:
--- Error message begin TestOAuth.hs:21:103: Ambiguous type variable `m0' in the constraints: (MonadIO m0) arising from a use of `serviceRequest' at TestOAuth.hs:21:103-116 (Monad m0) arising from a use of `>>=' at TestOAuth.hs:21:99-101 Possible cause: the monomorphism restriction applied to the following: response :: m0 Response (bound at TestOAuth.hs:17:1) Probable fix: give these definition(s) an explicit type signature or use -XNoMonomorphismRestriction In the second argument of `(>>=)', namely
I seem using NoMonomorphismRestriction is workaround, so I want to add a proper type signature, but I cannot figure out what it is.
What confuses me is why GHC didn't just take MonadIO as MonadIO is a Monad according to the definition.
From the definition of response, the two constraints
MonadIO m0 Monad m0
are inferred. Since response is bound by a simple pattern binding (no function arguments) and without a type signature, by the monomorphism restriction, it must get a monomorphic type, so the compiler tries to find a specific MonadIO (and Monad, but that would follow) to use. But there is no defaulting for those constraints (defaulting takes place for constraints where at least one of the involved classes is a numeric class [Num, Integral, Fractional, ...], and all involved classes are defined in the standard libraries), so that fails (no numeric class, and MonadIO is defined outside the standard libraries).
To fix it, you just have to define response with a type signature,
response :: MonadIO m => m Response
You should give all your top-level definitions type signatures anyway. It's good for documentation, and it gives you much better error messages if you make a mistake.
-- Ken KAWAMOTO kentaro.kawamoto@gmail.com
participants (2)
-
Daniel Fischer
-
Ken KAWAMOTO