[Haskell-cafe] Re: Foralls in records

apfelmus at quantentunnel.de apfelmus at quantentunnel.de
Wed Mar 14 04:10:49 EDT 2007


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



More information about the Haskell-Cafe mailing list