3
{-# LANGUAGE DeriveDataTypeable, OverloadedStrings, ScopedTypeVariables #-}
module Db (
    couchTest
) where

import Control.Monad.IO.Class (liftIO)
import Data.ByteString (ByteString)
import Data.Generics (Data, Typeable)
import Database.CouchDB.Conduit
import Database.CouchDB.Conduit.Generic

conn :: CouchConnection
conn = def {couchLogin = "admin", couchPass = "admin"}

data D = D { f1 :: Int, f2 :: String } deriving (Show, Data, Typeable)

couchTest = runCouch conn $ do
    rev1 <- couchPut "mydb" "my-doc1" "" [] $ D 123 "str"
    rev2 <- couchPut "mydb" "my-doc1" rev1 [] $ D 1234 "another"
    (rev3, d1 :: D) <- couchGet "mydb" "my-doc1" []
    liftIO $ print d1
    couchPut' "mydb" "my-doc1" [] $ D 12345 "third"    -- notice - no rev
    rev3 <- couchRev "mydb" "my-doc1"
    couchDelete "mydb" "my-doc1" rev3

error

No instance for (monad-control-0.3.1.3:Control.Monad.Trans.Control.MonadBaseControl
                   IO m0)
  arising from a use of `couchPut'
Possible fix:
  add an instance declaration for
  (monad-control-0.3.1.3:Control.Monad.Trans.Control.MonadBaseControl
     IO m0)
In the expression: couchPut "mydb" "my-doc1" "" []
In a stmt of a 'do' block:
  rev1 <- couchPut "mydb" "my-doc1" "" [] $ D 123 "str"
In the second argument of `($)', namely
  `do { rev1 <- couchPut "mydb" "my-doc1" "" [] $ D 123 "str";
        rev2 <- couchPut "mydb" "my-doc1" rev1 [] $ D 1234 "another";
        (rev3, d1 :: D) <- couchGet "mydb" "my-doc1" [];
        liftIO $ print d1;
        .... }'

1) How do you add an instance declaration for monad-control-0.3.1.3:Control.Monad.Trans.Control.MonadBaseControl IO m0?

2) Is it possible to create attachments with couchdb-conduit?

3) Is there a example of using couchdb directly with http package, basically to see how much code it takes?

Gert Cuykens
  • 6,845
  • 13
  • 50
  • 84
  • 1) out of pure luck i found out adding `couchTest:: IO ()` as type signature works? Which is really confusing especially with `liftIO $ print d1` – Gert Cuykens Aug 03 '12 at 17:00
  • `liftIO` if you're already in the `IO` monad is well supported, it just doesn't do anything: http://hackage.haskell.org/packages/archive/transformers/0.3.0.0/doc/html/src/Control-Monad-IO-Class.html#liftIO – Nathan Howell Aug 03 '12 at 17:03
  • 1
    However the `liftIO` in your example code is required because `runCouch` runs an action (effectively) in `ResourceT IO`, not `IO`. – Nathan Howell Aug 03 '12 at 17:06

1 Answers1

3

Might be better to split your question up since you're asking three different things. As far as #1 goes, no new instance is required for MonadBaseControl. Add type signatures to remove the ambiguity and it compiles straight away:

{-# LANGUAGE DeriveDataTypeable, FlexibleContexts,
             OverloadedStrings, ScopedTypeVariables #-}
module Db (
    couchTest
) where

import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Monad.Trans.Resource (MonadThrow, MonadUnsafeIO)
import Control.Monad.Trans.Control (MonadBaseControl)
import Data.ByteString (ByteString)
import Data.Generics (Data, Typeable)
import Database.CouchDB.Conduit
import Database.CouchDB.Conduit.Generic

conn :: CouchConnection
conn = def {couchLogin = "admin", couchPass = "admin"}

data D = D { f1 :: Int, f2 :: String } deriving (Show, Data, Typeable)

couchTest
  :: (MonadIO m, MonadUnsafeIO m, MonadThrow m, MonadBaseControl IO m)
  => m ()
-- couchTest :: IO () -- restricting it to IO is also an option
couchTest = runCouch conn $ do
    rev1 <- couchPut "mydb" "my-doc1" "" [] $ D 123 "str"
    rev2 <- couchPut "mydb" "my-doc1" rev1 [] $ D 1234 "another"
    (rev3, d1 :: D) <- couchGet "mydb" "my-doc1" []
    liftIO $ print d1
    couchPut' "mydb" "my-doc1" [] $ D 12345 "third"    -- notice - no rev
    rev3 <- couchRev "mydb" "my-doc1"
    couchDelete "mydb" "my-doc1" rev3

I had GHC come up with the constraint list for me by enabling the NoMonomorphismRestriction language pragma and running the following in GHCi. You can also leave the NMR flag set in many cases instead of adding explicit signatures, but I prefer explicit signatures.

*Db> :info couchTest 
couchTest ::
  (MonadIO m, Control.Monad.Trans.Resource.MonadUnsafeIO m,
   Control.Monad.Trans.Resource.MonadThrow m,
   MonadBaseControl IO m) =>
  m ()
    -- Defined at /tmp/cdb.hs:21:5
Nathan Howell
  • 4,627
  • 1
  • 22
  • 30
  • can I bother you with a simmalar type question pleas http://stackoverflow.com/questions/11731941/haskell-facebook-exceptions – Gert Cuykens Aug 03 '12 at 18:15