-- |
-- Module     : Simulation.Aivika.GPSS.Block.Enter
-- Copyright  : Copyright (c) 2017, David Sorokin <david.sorokin@gmail.com>
-- License    : BSD3
-- Maintainer : David Sorokin <david.sorokin@gmail.com>
-- Stability  : experimental
-- Tested with: GHC 8.0.2
--
-- This module defines the GPSS block ENTER.
--
module Simulation.Aivika.GPSS.Block.Enter
       (enterBlock) where

import Simulation.Aivika
import Simulation.Aivika.GPSS.Transact
import Simulation.Aivika.GPSS.Block
import Simulation.Aivika.GPSS.Storage

-- | This is the GPSS construct
--
-- @ENTER A,B@
enterBlock :: Storage
              -- ^ the storage
              -> Int
              -- ^ the content decrement
              -> Block (Transact a) (Transact a)
enterBlock :: forall a. Storage -> Int -> Block (Transact a) (Transact a)
enterBlock Storage
r Int
decrement =
  Block { blockProcess :: Transact a -> Process (Transact a)
blockProcess = \Transact a
a -> forall a. Storage -> Transact a -> Int -> Process ()
enterStorage Storage
r Transact a
a Int
decrement forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return Transact a
a }