module Control.ERNet.Foundations.Protocol
(
module Control.ERNet.Foundations.Protocol
)
where
import Data.Number.ER.BasicTypes
import Data.Number.ER.ShowHTML
import qualified Text.Html as H
import Data.Typeable
type QueryId = Int
class (Ord q, H.HTML q, H.HTML a, Show q, Show a, Typeable q, Typeable a) =>
QAProtocol q a
| a -> q, q -> a
where
qaMatch :: q -> a -> Maybe String
qaaSetMinGran :: Granularity -> a -> a
qaaSetMinGran _ a = a
qaMatchDefaultMessage q a =
"answer " ++ show a ++ " does not match query " ++ show q
data ChannelType =
forall q a. (QAProtocol q a, Eq q, Show q, Eq a, Show a) =>
ChannelType q a
instance (Eq ChannelType) where
(ChannelType q1 a1) == (ChannelType q2 a2) =
case cast (q1,a1) of
Nothing -> False
Just (q1c, a1c) ->
q1c == q2 && a1c == a2
instance (Show ChannelType) where
show (ChannelType q a) =
"ChT(q=" ++ show q ++ ",a=" ++ show a ++ ")"
data QueryAnyProt =
forall q a. (QAProtocol q a, Show q, Show a) =>
QueryAnyProt q
instance (Show QueryAnyProt)
where
show (QueryAnyProt qry) = show qry
instance H.HTML QueryAnyProt
where
toHtml (QueryAnyProt qry) = H.toHtml qry
data AnswerAnyProt =
forall q a. (QAProtocol q a, Show q, Show a) =>
AnswerAnyProt a
instance (Show AnswerAnyProt)
where
show (AnswerAnyProt ans) = show ans
instance H.HTML AnswerAnyProt
where
toHtml (AnswerAnyProt ans) = H.toHtml ans
instance (QAProtocol QAUnitQ QAUnitA)
where
qaMatch _ _ = Nothing
data QAUnitQ
= QAUnitQ
deriving (Eq, Ord, Show, Typeable)
data QAUnitA
= QAUnitA
deriving (Eq, Ord, Show, Typeable)
instance H.HTML QAUnitQ where
toHtml = toHtmlDefault
instance H.HTML QAUnitA where
toHtml = toHtmlDefault
chTUnit = ChannelType QAUnitQ QAUnitA
instance (QAProtocol QABoolQ Bool)
where
qaMatch _ _ = Nothing
data QABoolQ
= QABoolQ
deriving (Eq, Ord, Show, Typeable)
instance H.HTML Bool where
toHtml = toHtmlDefault
instance H.HTML QABoolQ where
toHtml = toHtmlDefault
chTBool = ChannelType QABoolQ True
instance (QAProtocol QANatQ QANatA)
where
qaMatch _ _ = Nothing
data QANatQ
= QANatQ
deriving (Eq, Ord, Show, Typeable)
data QANatA
= QANatA Integer
deriving (Eq, Ord, Show, Typeable)
instance H.HTML QANatQ where
toHtml = toHtmlDefault
instance H.HTML QANatA where
toHtml = toHtmlDefault
chTNat = ChannelType QANatQ (QANatA 0)