summaryrefslogtreecommitdiff
path: root/src/Remote/KRPC/Method.hs
blob: 3c757d07ed33def966f25c3ab030847f43311892 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
{-# LANGUAGE OverloadedStrings #-}
module Remote.KRPC.Method
       ( Method(methodName, methodParams, methodVals)

         -- * Construction
       , method

         -- * Predefined methods
       , idM, composeM
       ) where

import Prelude hiding ((.), id)
import Control.Category
import Control.Monad

import Remote.KRPC.Protocol



-- | The
--
--   * argument: type of method parameter
--
--   * remote: A monad used by server-side.
--
--   * result: type of return value of the method.
--
data Method param result = Method {
    -- | Name used in query and
    methodName   :: [MethodName]

    -- | Description of each parameter in /right to left/ order.
  , methodParams :: [ParamName]

    -- | Description of each return value in /right to left/ order.
  , methodVals   :: [ValName]
  }

instance Category Method where
  {-# SPECIALIZE instance Category Method #-}
  id  = idM
  {-# INLINE id #-}

  (.) = composeM
  {-# INLINE (.) #-}


-- TODO ppMethod

-- | Remote identity function. Could be used for echo servers for example.
--
--   idM = method "id" ["x"] ["y"] return
--
idM :: Method a a
idM = method "id" ["x"] ["y"]
{-# INLINE idM #-}

-- | Pipelining of two or more methods.
--
--   NOTE: composed methods will work only with this implementation of
--   KRPC, so both server and client should use this implementation,
--   otherwise you more likely get the 'ProtocolError'.
--
composeM :: Method b c -> Method a b -> Method a c
composeM g h = Method (methodName g ++ methodName h)
                      (methodParams h)
                      (methodVals g)
{-# INLINE composeM #-}


method :: MethodName -> [ParamName] -> [ValName] -> Method param result
method name = Method [name]
{-# INLINE method #-}