Add Applicative instance for STM

Bas van Dijk v.dijk.bas at gmail.com
Mon May 24 19:20:55 EDT 2010


Hello,

This is just a reminder and summary of my proposal to add Applicative
and Alternative instances for STM. We're in the second and last week
of this proposal.

Ticket: http://hackage.haskell.org/trac/ghc/ticket/4076

Here's a description of the proposed patches:

* stm_applicative-instance-sequential-stm.dpatch:
This patch adds an Applicative instance for Control.Sequential.STM.
Note that it doesn't add an Alternative instance because sequential
STM does not support retrying transactions.

Now for the regular STM there are actually two modules where we can
define the Applicative and Alternative instances: GHC.Conc (which
defines the type) and Control.Applicative (which defines the classes).

The former has the advantage that the Functor, Applicative and Monad
instances are grouped together. The disadvantage is that it requires
to import Control.Applicative via {-# SOURCE #-} because we get an
import cycle otherwise and so also requires the
Control/Applicative.hs-boot file. The following patch makes this
change:
* base_applicative-instance-stm.dpatch

More people like to add the instances to Control.Applicative however.
The following patch makes that change:
* base_add_applicative_and_alternative_instances_for_STM_to_Control.Applicative.dpatch

Note there's a related proposal with patches for moving the MonadPlus
instance for STM from Control.Monad.STM to GHC.Conc to avoid an
orphaned instance. See:
http://hackage.haskell.org/trac/ghc/ticket/4077

One last thing, I actually used to different Applicative instances for STM:

The one in Control.Applicative:
instance Applicative STM where
    pure = return
    (<*>) = ap

Or the one in GHC.Conc:
instance Applicative STM where
    {-# INLINE pure  #-}
    {-# INLINE (<*>) #-}
    pure  = returnSTM
    (<*>) = appSTM

returnSTM :: a -> STM a
returnSTM x = STM (\s -> (# s, x #))

appSTM :: STM (a -> b) -> STM a -> STM b
appSTM (STM mf) (STM mx) = STM ( \s ->
  case mf s of
    (# s', f #) -> case mx s' of
                     (# s'', x #) -> (# s'', f x #)
  )

Currently I don't have time to investigate if one is more efficient
than the other. Does anybody have a hunch?

Regards,

Bas


More information about the Libraries mailing list