{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE PatternSignatures #-}
{-# LANGUAGE ScopedTypeVariables  #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-|
    Module      :  Control.ERNet.Foundations.Process
    Description :  processes and channels within networks
    Copyright   :  (c) Michal Konecny
    License     :  BSD3

    Maintainer  :  mik@konecny.aow.cz
    Stability   :  experimental
    Portability :  portable

    Kahn process networks with channels 
    adapted for arbitrary precision real higher-order data communication.
    Executed using a number of parallel threads.  
    Each process started in a dedicated thread 
    and each process typically starts further internal threads.
    Each channel is a transactional variable (TVar) 
    known to both end processes and allows them to communicate
    according to its instance of the 'QAProtocol' class.
-}
module Control.ERNet.Foundations.Process
(
    ERProcess(..),
    ERProcessName,
    ERProcessDeploy,
    ERProcessExpandCallback,
    subnetProcess
)
where

import Control.ERNet.Foundations.Protocol

import Control.Concurrent as Concurrent
import Control.Concurrent.STM as STM
import Data.Number.ER.MiscSTM

import qualified Data.Map as Map
import Data.Maybe
import Data.Typeable

{-|
    All data that define a process, including its behaviour.
    Each executing process is instantiated from one of these descriptions.
-}
data ERProcess sInAnyProt sOutAnyProt
    = ERProcess 
        {
            erprocName :: ERProcessName, -- ^ undeployed process name
            {-| 
                On deployment, a process either expands itself using
                the provided callback function and does not use the
                sockets at all
                
                OR it uses the sockets and never calls the expansion
                callback.
             -}
            erprocDeploy :: ERProcessDeploy sInAnyProt sOutAnyProt,
            erprocInputTypes :: [ChannelType],
            erprocOutputTypes :: [ChannelType]
        }

type ERProcessName = String

type ERProcessDeploy sInAnyProt sOutAnyProt =
    ERProcessName {--^ deployed process instance name -} -> 
    [sInAnyProt] {--^ input sockets -} ->
    [sOutAnyProt] {--^ output sockets -} ->
    (ERProcessExpandCallback sInAnyProt sOutAnyProt) 
        {--^ scheduler callback for expanding this process -} ->
    IO ()

type ERProcessExpandCallback sInAnyProt sOutAnyProt =
    String {--^ place where callback used; for error messages -} -> 
    [(ChannelType, Int)] {--^ input socket channel types and numbers -} ->
    [(ChannelType, Int)] {--^ output socket channel types and numbers -} ->
    [(ERProcess sInAnyProt sOutAnyProt, ([Int], [Int]))]
        {--^ internal processes and their in/out channel numbers -} ->
    IO ()

subnetProcess ::
    ERProcessName ->
    [(ChannelType, Int)] {-^ input socket channel types and numbers -} ->
    [(ChannelType, Int)] {-^ output socket channel types and numbers -} ->
    [(ERProcess sInAnyProt sOutAnyProt, ([Int], [Int]))]
        {-^ internal processes and their in/out channel numbers -} ->
    ERProcess sInAnyProt sOutAnyProt
subnetProcess defName inSockets outSockets subProcesses =
    ERProcess defName deploy inSocketTypes outSocketTypes
    where
    deploy deployName _ _ expandCallback =
        expandCallback deployName inSockets outSockets subProcesses
    outSocketTypes = map fst outSockets 
    inSocketTypes = map fst inSockets