
Hi. I'm experimenting with implementing database transactions as monads but I'm getting stuck on how to store a generic connection (only constrained by a typeclass) inside the transaction. The reason I'm doing it this way is that the connection could be a different kind of structure depending on what database the transaction is using. The goal is to enable all functions using the monad to extract the connection using getConnection. I realise I could probably get it running by adding a type parameter for the connection type to TransactionT and Transaction but I feel I shouldn't have to. All the compiler needs to know is that the contained value conforms to the interface of Connection. <code> data TransactionT = forall c. (Connection c) => TransactionT c data Transaction a = Transaction (TransactionT -> (a, TransactionT)) instance Monad Transaction where ... getConnection :: Transaction c getConnection = Transaction (\t@(TransactionT c) -> (c, t)) class Connection c where connectionExecute :: c -> String -> Transaction () execute :: String -> Transaction () execute s = connectionExecute getConnection s </code> I'm getting the following error: Couldn't match expected type `c' (a rigid variable) against inferred type `c1' (a rigid variable) `c' is bound by the type signature for `getConnection' at Database.hs:19:29 `c1' is bound by the pattern for `TransactionT' at Database.hs:20:33-46 In the expression: c In the expression: (c, t) In a lambda abstraction: \ (t@(TransactionT c)) -> (c, t)

Adde:
data TransactionT = forall c. (Connection c) => TransactionT c
data Transaction a = Transaction (TransactionT -> (a, TransactionT))
getConnection :: Transaction c getConnection = Transaction (\t@(TransactionT c) -> (c, t))
class Connection c where connectionExecute :: c -> String -> Transaction ()
execute :: String -> Transaction () execute s = connectionExecute getConnection s
I'm assuming you've read the GHC user's guide on existentially quantified data constructors: http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html... When you wrap a value in an existentially quantified data constructor, the concrete type of the value is erased. Although the wrapped value does have a concrete type, "the compiler" has forgotten it. This is what the "existential" part means: you know the type exists, but that's about all you know. In this case, you've used a context to restrict the existential quantification, so at least you know the type conforms to the Connection class. Since the concrete type has been forgotten, there's no way to get it back. You can't write a function that exposes the forgotten type, so getConnection is basically a lost cause. When you write "getConnection :: Transaction c", you are saying that the function is fully polymorphic in c. In other words, you are allowing the caller of getConnection to specify the type of connection. But you can't do that, because you already gave the connection a concrete type when you constructed the TransactionT. You might think you could get away with "getConnection :: Connection c => Transaction c", but this is still too polymorphic. So what can you do? You can pattern-match on a TransactionT, provided you don't allow the existentially-quantified type to escape the scope of the pattern-match. In this case, all you know is that the type conforms to the Connection class, so you must use methods from the Connection class within that scope to consume the quantified type. Now, I'm a little confused by the circular dependency between TransactionT, Transaction and the Connection class, so I'll use a slightly different example:
class Connection c where connectionExecute :: c -> String -> IO ()
Now, you can write a corresponding function for a TransactionT (not tested):
transactionExecute :: TransactionT -> String -> IO () transactionExecute (TransactionT c) s = connectionExecute c s
Note that the existentially-quantified type variable is not exposed in the signature of transactionExecute, because it has been consumed by connectionExecute within the scope of the TransactionT pattern-match. Hope that helps.

Matthew Brecknell
Since the concrete type has been forgotten, there's no way to get it back. You can't write a function that exposes the forgotten type, so getConnection is basically a lost cause. When you write "getConnection :: Transaction c", you are saying that the function is fully polymorphic in c. In other words, you are allowing the caller of getConnection to specify the type of connection. But you can't do that, because you already gave the connection a concrete type when you constructed the TransactionT. You might think you could get away with "getConnection :: Connection c => Transaction c", but this is still too polymorphic.
So what can you do? You can pattern-match on a TransactionT, provided you don't allow the existentially-quantified type to escape the scope of the pattern-match. In this case, all you know is that the type conforms to the Connection class, so you must use methods from the Connection class within that scope to consume the quantified type.
Thanks, using pattern matching to avoid mentioning the type didn't even cross my mind. You are correct in assuming that I thought I could get away with "getConnection :: Connection c => Transaction c". To be honest, I still don't understand why it's too polymorphic. To me it says that it'll return a Transaction parameterised by a type confirming to the Connection interface, even though the concrete type is long lost.

Adde:
Thanks, using pattern matching to avoid mentioning the type didn't even cross my mind. You are correct in assuming that I thought I could get away with "getConnection :: Connection c => Transaction c". To be honest, I still don't understand why it's too polymorphic. To me it says that it'll return a Transaction parameterised by a type confirming to the Connection interface, even though the concrete type is long lost.
That's not quite right. Replace "a type" with "any type" in that statement, and you'll be closer to the truth. There is an implicit "forall" (which can also be read as "for any") in front of any type with a free type variable, so you actually have: getConnection :: forall c. Connection c => Transaction c Universally ("forall")-quantified type variables are resolved through unification with the context (in this case, by the caller of getConnection). If we had an "exists" quantifier, then you might be able to read an existentially-quantified type variable as a placeholder for some type that you know exists, but where you don't know the concrete type. This seems to be the way you are reading the type you want to give to getConnection. If you still don't see the difference between universal and existstential quantification, try substituting "any type the caller wants" in place of "a type" in your statement about the type. Of course, we can't give the caller any type it wants, even if the caller is limited to types conforming to the Connection class. We would only be able to give it the concrete type that was originally wrapped in the TransactionT, except for the fact we've forgotten what that type is. Since we don't have an "exists" quantifier, there is a common transformation used to convert to "forall" quantification. Martin demonstrated the transformation with his "withConnection". What Martin didn't mention is that "withConnection" is rank-2 polymorphic, and that can be a whole world of fun of its own. :-)

Thanks! Serious food for thought. Ten years of object oriented brainwashing to undo :)

Adde wrote:
I'm experimenting with implementing database transactions as monads but I'm getting stuck on how to store a generic connection (only constrained by a typeclass) inside the transaction. The reason I'm doing it this way is that the connection could be a different kind of structure depending on what database the transaction is using.
data TransactionT = forall c. (Connection c) => TransactionT c
data Transaction a = Transaction (TransactionT -> (a, TransactionT))
instance Monad Transaction where ....
getConnection :: Transaction c getConnection = Transaction (\t@(TransactionT c) -> (c, t))
class Connection c where connectionExecute :: c -> String -> Transaction ()
execute :: String -> Transaction () execute s = connectionExecute getConnection s
Do you want to mix differently typed Connections inside a single transaction? It looks like you don't, so you may well leave out existential types altogether and simply parametrize the Transaction monad on the type of the connection it uses. data Connection c => TransactionState c = TS c data Transaction c a = Transaction (TransactionState c -> (a, TransactionState c) instance Monad (Transaction c) where ... getConnection :: Transaction c c ... Note that Control.Monad.State does the same. Regards, apfelmus

Do you want to mix differently typed Connections inside a single transaction? It looks like you don't, so you may well leave out existential types altogether and simply parametrize the Transaction monad on the type of the connection it uses.
data Connection c => TransactionState c = TS c data Transaction c a = Transaction (TransactionState c -> (a, TransactionState c)
instance Monad (Transaction c) where ...
getConnection :: Transaction c c ...
Note that Control.Monad.State does the same.
Regards, apfelmus
You are correct in that I don't want to mix different kind of connections inside a single transaction. I just didn't want to have to parameterize every single function using the monad. doSomething :: Transaction FirebirdConnection () doSomethingElse :: Transaction FirebirdConnection () Maybe I'm misunderstanding something but as I see it that would kind of stop me from running doSomething and doSomethingElse using different kinds of databases.

Adde wrote:
Do you want to mix differently typed Connections inside a single transaction? It looks like you don't, so you may well leave out existential types altogether and simply parametrize the Transaction monad on the type of the connection it uses.
data Connection c => TransactionState c = TS c data Transaction c a = Transaction (TransactionState c -> (a, TransactionState c)
instance Monad (Transaction c) where ...
getConnection :: Transaction c c ...
Note that Control.Monad.State does the same.
You are correct in that I don't want to mix different kind of connections inside a single transaction. I just didn't want to have to parameterize every single function using the monad.
doSomething :: Transaction FirebirdConnection ()
doSomethingElse :: Transaction FirebirdConnection ()
Maybe I'm misunderstanding something but as I see it that would kind of stop me from running doSomething and doSomethingElse using different kinds of databases.
Your monadic action may well be polymorphic in the state type: doSomething :: Connection c => Transaction c () doSomethingElse :: Connection c => Transaction c () thus working for all databases. In case your function really depends on a particular database vendor, you have the possibility to annotate this in the connection type: doSomethingThatOnlyWorksForFirebird :: Transaction Firebird () The additional 'Connection c' constraint in the first examples may be a bit unwieldy. But I guess that you can drop when redesigning your monad. After all, I'm unsure what you intend 'Transaction' to do. Wouldn't runTransaction :: Transaction c a -> IO a be a function you need? Shouldn't things of the Transaction monad be completely back end independent so that you can drop the parameter c altogether? Why do you intend 'Transaction' to be a state monad, I mean why is the only thing you can do with the state something of type (c -> String -> IO ())? Btw, this has been (c -> String -> Transaction ()) in your original post. Regards, apfelmus

Hi, instead of writing a function getTransaction that retrieves the connection you could write a function withConnection that doesn't return the connection itself but performs an operation on the connection: withConnection :: (forall c. Connection c => c -> Transaction a) -> Transaction a withConnection f = Transaction (\t@(TransactionT c) -> let Transaction tf = f c in tf t) Then execute becomes: execute :: String -> Transaction () execute s = withConnection (\c -> connectionExecute c s) Regards, Martin.
getConnection :: Transaction c getConnection = Transaction (\t@(TransactionT c) -> (c, t))
class Connection c where connectionExecute :: c -> String -> Transaction ()
execute :: String -> Transaction () execute s = connectionExecute getConnection s

Martin Huschenbett
Hi,
instead of writing a function getTransaction that retrieves the connection you could write a function withConnection that doesn't return the connection itself but performs an operation on the connection:
withConnection :: (forall c. Connection c => c -> Transaction a) -> Transaction a withConnection f = Transaction (\t <at> (TransactionT c) -> let Transaction tf = f c in tf t)
Then execute becomes:
execute :: String -> Transaction () execute s = withConnection (\c -> connectionExecute c s)
Regards, Martin.
getConnection :: Transaction c getConnection = Transaction (\t <at> (TransactionT c) -> (c, t))
class Connection c where connectionExecute :: c -> String -> Transaction ()
execute :: String -> Transaction () execute s = connectionExecute getConnection s
Thanks, I would never have thought of that myself. I replaced TransactionT with a typeclass called TransactionType to allow for different transaction structures for different databases. The only thing i can't seem to figure out is how to bridge between the IO-monad and my own Transaction monad. class TransactionType t where transactionExecute :: t -> String -> IO () execute :: String -> Transaction () execute s = withTransaction (\t -> transactionExecute t s) withTransaction :: (forall t. (TransactionType t) => t -> Transaction a) -> Transaction a withTransaction f = Transaction (\t -> let Transaction tf = f t in tf t) This is what I'm getting back: Couldn't match expected type `Transaction ()' against inferred type `IO ()' If i try to use liftIO i get this instead: No instance for (MonadIO Transaction) arising from use of `liftIO' I can't seem to find any examples of how to actually implement liftIO for a monad. Any ideas/pointers?

I can't seem to find any examples of how to actually implement liftIO for a monad. Any ideas/pointers?
Searching the haskell wiki for MonadIO gives several examples. http://haskell.org/haskellwiki/New_monads/MonadExit
instance MonadIO m => MonadIO (ExitT e m) where liftIO = lift . liftIO
Where you can see you are just delegating the work of the transformer to the underlying monad. Eventually it hits the bottom of the stack and sees:
instance MonadIO IO where liftIO = id

Chris Kuklewicz
Searching the haskell wiki for MonadIO gives several examples.
http://haskell.org/haskellwiki/New_monads/MonadExit
instance MonadIO m => MonadIO (ExitT e m) where liftIO = lift . liftIO
Where you can see you are just delegating the work of the transformer to the underlying monad. Eventually it hits the bottom of the stack and sees:
instance MonadIO IO where liftIO = id
Ah, so to combine my monad with IO i need to write a monad Transformer (TransactionT), then I can make it an instance of MonadIO? I found examples like the ones you gave but the whole transformer-part got me a bit confused. Sorry, should have spent some more time reading before asking.
participants (5)
-
Adde
-
apfelmus@quantentunnel.de
-
Chris Kuklewicz
-
Martin Huschenbett
-
Matthew Brecknell