[Haskell-cafe] IO in HApps handler ?

Marc Weber marco-oweber at gmx.de
Sun Aug 19 20:10:54 EDT 2007


Hi TAESCH,

THat's what haskell is good for.
It prevents you from doing unsafe things by accident.
You must get the source and have a look at the definition of the Ev
type: (module HAppS.MACID.Types where:)
(Not sure wether this code is most recent or not (Version: 0.8.8))

=============  =======================================================
[...]
  data Env st ev = Env { 
                      -- | Read only event.
                      evEvent                  :: TxContext ev,
                      -- | State, can be used with get and put.
                      evState                  :: MutVar st,
                      -- | Internal. List of side effects.
                      evSideEffects            :: MutVar [(Seconds, IO ())],
                      -- | Internal. Used to signal completion of background IO.
                      evBackgroundIOCompletion :: IO (),
                      -- | Internal. Random numbers that should be used.
                      evRandoms                :: MutVar StdGen
  --                    -- | Internal. New event generation.
  --                    evCreateEvent            :: ev -> IO ()
                    }

  type TxId      = Int64
  type EpochTime = Int64
  type Seconds   = Int

  instance Typeable StdGen where typeOf _ = undefined -- !! for default serial

  data TxContext evt = TxContext
      { txId     :: TxId,
        txTime   :: EpochTime,
        txStdGen :: StdGen,
        txEvent  :: evt
      }  deriving (Read,Show,Typeable)

  -- | ACID computations that work with any state and event types.
  type AnyEv a = forall state event. Ev state event a

  -- | Monad for ACID event handlers.
  newtype Ev state event t = Ev { unEv :: Env state event -> STM t }

  -- unsafe lifting

  unsafeIOToEv :: IO a -> AnyEv a
  unsafeIOToEv c = Ev $ \_ -> unsafeIOToSTM c
  unsafeSTMToEv :: STM a -> AnyEv a
  unsafeSTMToEv c = Ev $ \_ -> c
  unsafeIOToSTM :: IO a -> STM a
  unsafeIOToSTM = GHC.Conc.unsafeIOToSTM

[...]
=============  =======================================================

Now have a look at the line
  newtype Ev state event t = Ev { unEv :: Env state event -> STM t }

which shows that you have some kind of state passed (Env state event)
which results in STM t )
The next thing is having a look at either Env or STM.. 
  data Env st ev = Env { 
  [...]
  evBackgroundIOCompletion :: IO (),
shows that an IO may be passed, which must be transformed into STM
somehow: Yeah. STM permits this
  newtype STM a = STM (IORef (IO ()) -> IO a)

this ( lifting an IO action into a different monad) is called lift(IO)
most of the time.. and as you can see theere are some transformers
defined:
  unsafeIOToEv :: IO a -> AnyEv a
  unsafeIOToEv c = Ev $ \_ -> unsafeIOToSTM c
  unsafeSTMToEv :: STM a -> AnyEv a
  unsafeSTMToEv c = Ev $ \_ -> c
  unsafeIOToSTM :: IO a -> STM a
  unsafeIOToSTM = GHC.Conc.unsafeIOToSTM
But why they are called unsafe etc you should ask people familiar with
HaPPS and its design.. But at least you can now use grep or google to
see wether you can find some more info on those unsafe functions

HTH
Marc


More information about the Haskell-Cafe mailing list