-- |
-- Module     : Simulation.Aivika.GPSS.Block.Priority
-- 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 PRIORITY.
--
module Simulation.Aivika.GPSS.Block.Priority
       (priorityBlock) where

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

-- | This is the GPSS construct
--
-- @PRIORITY A@
priorityBlock :: Int
                 -- ^ the priority
                 -> Block (Transact a) (Transact a)
priorityBlock :: Int -> Block (Transact a) (Transact a)
priorityBlock Int
priority =
  Block :: forall a b. (a -> Process b) -> Block a b
Block { blockProcess :: Transact a -> Process (Transact a)
blockProcess = \Transact a
a -> Transact a -> Process (Transact a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Transact a -> Int -> Transact a
forall a. Transact a -> Int -> Transact a
assignTransactPriority Transact a
a Int
priority) }