module TypedSockets(TPort,tPort,tSocketServerF,TServerAddress,tServerAddress,tTransceiverF,ClientMsg(..),SocketMsg(..)) where
import Fudgets
import SocketServer
import Debug.Trace
newtype TPort a b = TPort Port
tPort :: (Show a, Read a,Show b,Read b) => Port -> TPort a b
tPort :: forall a b. (Show a, Read a, Show b, Read b) => Port -> TPort a b
tPort Port
p = forall a b. Port -> TPort a b
TPort Port
p
newtype TSocket t r = TSocket Socket
newtype TLSocket t r = TLSocket LSocket
data TServerAddress c s = TServerAddress Host (TPort c s)
tServerAddress :: Host -> TPort c s -> TServerAddress c s
tServerAddress Host
host TPort c s
port = forall c s. Host -> TPort c s -> TServerAddress c s
TServerAddress Host
host TPort c s
port
tSocketServerF ::
(Read c, Show s) =>
TPort c s -> (Peer -> F s (SocketMsg c) -> F a (SocketMsg b)) ->
F (Int, a) (Int, ClientMsg b)
tSocketServerF :: forall c s a b.
(Read c, Show s) =>
TPort c s
-> (Host -> F s (SocketMsg c) -> F a (SocketMsg b))
-> F (Port, a) (Port, ClientMsg b)
tSocketServerF (TPort Port
p) Host -> F s (SocketMsg c) -> F a (SocketMsg b)
f = forall {a1} {a2}.
Port
-> (Socket -> Host -> F a1 (SocketMsg a2))
-> F (Port, a1) (Port, ClientMsg a2)
socketServerF Port
p (\ Socket
s Host
p -> Host -> F s (SocketMsg c) -> F a (SocketMsg b)
f Host
p (forall {e} {a}. (Show e, Read a) => Socket -> F e (SocketMsg a)
textTransceiver Socket
s))
textTransceiver :: Socket -> F e (SocketMsg a)
textTransceiver Socket
s = SP Host (SocketMsg a)
postSP forall a b e. SP a b -> F e a -> F e b
>^^=< Socket -> F Host Host
transceiverF Socket
s forall c d e. F c d -> (e -> c) -> F e d
>=^< forall {a}. Show a => a -> Host
pre
where
pre :: a -> Host
pre a
s = forall a. Show a => a -> ShowS
shows a
s Host
"\n"
postSP :: SP Host (SocketMsg a)
postSP = forall {t1} {a} {t2} {b}.
(t1 -> a) -> (t2 -> b) -> SP a t2 -> SP t1 b
prepostMapSP forall {a}. Host -> Either (SocketMsg a) Host
eos forall {a}. Either a a -> a
stripEither forall a b. (a -> b) -> a -> b
$
forall {a1} {b} {a2}. SP a1 b -> SP (Either a2 a1) (Either a2 b)
idLeftSP (forall {t} {b}. (t -> Maybe b) -> SP t b
mapFilterSP forall {a}. Read a => Host -> Maybe (SocketMsg a)
reader forall {a1} {b} {a2}. SP a1 b -> SP a2 a1 -> SP a2 b
-==- SP Host Host
inputLinesSP)
eos :: Host -> Either (SocketMsg a) Host
eos Host
"" = forall a b. a -> Either a b
Left forall a. SocketMsg a
SocketEOS
eos Host
s = forall a b. b -> Either a b
Right Host
s
reader :: Host -> Maybe (SocketMsg a)
reader Host
s = case forall a. Read a => ReadS a
reads Host
s of
[(a
a,Host
"")] -> forall a. a -> Maybe a
Just (forall a. a -> SocketMsg a
SocketMsg a
a)
[(a, Host)]
_ -> forall a. Host -> a -> a
trace (Host
"No parse from socket: "forall a. [a] -> [a] -> [a]
++Host
s) forall a. Maybe a
Nothing
tTransceiverF :: (Show c, Read s) => TServerAddress c s -> F c (SocketMsg s)
tTransceiverF :: forall c s.
(Show c, Read s) =>
TServerAddress c s -> F c (SocketMsg s)
tTransceiverF (TServerAddress Host
host (TPort Port
port)) =
forall {f :: * -> * -> *} {hi} {ho}.
FudgetIO f =>
Host -> Port -> (Socket -> f hi ho) -> f hi ho
openSocketF Host
host Port
port forall {e} {a}. (Show e, Read a) => Socket -> F e (SocketMsg a)
textTransceiver