{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE ScopedTypeVariables  #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FunctionalDependencies #-}
{-|
    Module      :  Control.ERNet.Foundations.Channel
    Description :  an abstraction of channels within networks
    Copyright   :  (c) Michal Konecny
    License     :  BSD3

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

    Abstraction of data flow channels and its sockets with associated
    query-answer protocol for gradual data communication.
    
    To be imported qualified, usually with the prefix CH.
-}

module Control.ERNet.Foundations.Channel where


import qualified Control.ERNet.Foundations.Event.Logger as LG 

import Control.ERNet.Foundations.Protocol

{-|  
    A channel type, as it is presented to the processes, 
    consists of an input socket and an output socket types.
    
    Each socket type has a unique protocol associated with
    it.  Whenever the protocol can be determined at
    compile time, we use the sIn and sOut types, otherwise
    we use the sInAnyProt and sOutAnyProt types.
    Elements of sInAnyProt and sOutAnyProt can be dynamically
    cast to elements of sIn and sOut once the protocol
    can be deduced by the Haskell type checker. 
-}
class Channel sIn sOut sInAnyProt sOutAnyProt
    | sIn -> sOut sInAnyProt sOutAnyProt,
      sOut -> sIn sInAnyProt sOutAnyProt,
      sInAnyProt -> sOutAnyProt sIn sOut, 
      sOutAnyProt -> sInAnyProt sIn sOut 
    where
    castIn ::
        (QAProtocol q a) =>
        String {-^ place where function used; for error messages -} -> 
        sInAnyProt -> 
        sIn q a
    castOut ::
        (QAProtocol q a) =>
        String {-^ place where function used; for error messages -} -> 
        sOutAnyProt -> 
        sOut q a
    castInIO ::
        (QAProtocol q a) =>
        String {-^ place where function used; for error messages -} -> 
        sInAnyProt -> 
        IO (sIn q a)
    castOutIO ::
        (QAProtocol q a) =>
        String {-^ place where function used; for error messages -} -> 
        sOutAnyProt -> 
        IO (sOut q a)
    {-|
        Register a new query on the given socket.  
        Return the new query's id.
    
        This is a version using a statically typed protocol.
    -}
    makeQuery ::
        (QAProtocol q a, Show q, Show a) =>
        sOut q2 a2 {-^ initiator query socket -} ->
        QueryId {-^ the query to the initiator that this query reacts to -} ->
        sIn q a {-^ socket to send query to -} ->
        q {-^ the query data -} ->
        IO QueryId {-^ query ID to be able to match the answers with queries -}
    {-|
        Register a new query on the given socket.  
        Return the new query's id.
    
        This is a version using a dynamically typed protocol.
    -}
    makeQueryAnyProt ::
        String {-^ place where function used; for error messages -} -> 
        sOutAnyProt {-^ initiator query socket -} ->
        QueryId {-^ the query to the initiator that this query reacts to -} ->
        sInAnyProt {-^ socket to send query to -} ->
        QueryAnyProt {-^ the query data -} ->
        IO QueryId {-^ query ID to be able to match the answers with queries -}
    {-|
        Wait until the given socket has at least one new query.
        When there is at least one, return the earliest one and set its status to pending.
    
        This function uses a statically typed protocol.
    -}
    waitForQuery ::
        (QAProtocol q a, Show q, Show a) =>
        sOut q a {-^ output socket to wait on -} ->
        IO (QueryId, q)
    {-|
        Wait until one of the given sockets has at least one new query.
        When there is at least one, return the earliest one 
        and set its status to pending.
    
        This is function uses a dynamically typed protocol.
    -}
    waitForQueryMulti ::
        [sOutAnyProt] {-^ output sockets to wait on -} ->
        IO (Int, (QueryId, QueryAnyProt))
    {-|
        Send the provided answer to the given socket as an answer to
        the query with the given query ID.
    
        This is a version using a statically typed protocol.
    -}
    answerQuery ::
        (QAProtocol q a) =>
        Bool {-^ should the answer be cached? -} ->
        (sOut q a) -> 
        (QueryId, a) ->
        IO ()
    {-|
        Send the provided answer to the given socket as an answer to
        the query with the given query ID.
    
        This is a version using a dynamically typed protocol.
    -}
    answerQueryAnyProt ::
        String {-^ place where function used; for error messages -} -> 
        Bool {-^ should the answer be cached? -} ->
        sOutAnyProt -> 
        (QueryId, AnswerAnyProt) ->
        IO ()
    {-|
        Wait for an answer to a query with the given query ID.
    -}
    waitForAnswer ::
        (QAProtocol q a, Show q, Show a) => 
        sOut q2 a2 {-^ initiator query socket -} ->
        QueryId {-^ the query to the initiator that this query reacted to -} ->
        sIn q a -> 
        QueryId ->
        IO a
    {-|
        Wait for an answer to one of several queries with the given query IDs.
    -}
    waitForAnswerMulti ::
        sOutAnyProt {-^ initiator query socket -} ->
        QueryId {-^ the query to the initiator that all of these queries reacted to -} ->
        [(sInAnyProt, QueryId)] -> 
        IO (Int, AnswerAnyProt)
--    {-|
--        Work out the name of process on the other side of the channel
--        that this socket leads to.
--    -}
--    inGetProviderName ::
--        (QAProtocol q a) => 
--        sIn q a -> 
--        String 
    

class (Channel sIn sOut sInAnyProt sOutAnyProt, LG.Logger lg) => 
    ChannelForScheduler lg sIn sOut sInAnyProt sOutAnyProt
    | sIn -> lg
    where
    {-| create a new channel that is then given to processes -}
    new ::
        lg {-^ a logger to use by the new channel -} -> 
        String {-^ name of channel responder process -} -> 
        Int {-^ channel id -} ->
        ChannelType {-^ used to determine the embedded instance of QAProtocol -} -> 
        IO (sInAnyProt, sOutAnyProt) {-^ the channel's input and output sockets -}