File: AMI.hs

package info (click to toggle)
haskell-ami 0.1-3
  • links: PTS, VCS
  • area: main
  • in suites: jessie, jessie-kfreebsd
  • size: 92 kB
  • sloc: haskell: 260; makefile: 2
file content (334 lines) | stat: -rw-r--r-- 10,134 bytes parent folder | download
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
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
{-# LANGUAGE OverloadedStrings, BangPatterns #-}
module Network.AMI
  (-- * Usage
   -- $usage

   -- * Types
   Parameters,
   ActionType, EventType,
   ActionID, ResponseType,
   EventHandler,
   AMI,
   Action (..),
   Response (..),
   Event (..),
   ConnectInfo (..),
   -- * Functions
   withAMI, withAMI_MD5,
   query,
   handleEvent
  ) where

import Control.Monad
import Control.Monad.Trans
import Control.Monad.Instances
import Control.Monad.Reader
import Control.Concurrent
import Control.Concurrent.STM
import qualified Control.Exception as E
import qualified Data.Map as M
import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Lazy as L
import Data.Digest.Pure.MD5
import System.IO.Unsafe (unsafePerformIO)
import Network
import Network.Socket hiding (close)
import System.IO

{- $usage
 
> import Network.AMI
> 
> info :: ConnectInfo
> info = ConnectInfo {
>          ciHost = "localhost"
>        , ciPort = 5038
>        , ciUsername = "admin"
>        , ciSecret = "PASSWORD" }
> 
> main :: IO ()
> main = withAMI_MD5 info $ do
>   handleEvent "FullyBooted" onBooted
>   mail <- query "MailboxCount" [("Mailbox","900")]
>   liftIO $ print mail
>   jabber <- query "JabberSend" [("Jabber", "asterisk"),
>                          ("JID", "someone@example.com"),
>                          ("ScreenName", "asterisk"),
>                          ("Message", "Jabber via AMI")]
>   liftIO $ print jabber
> 
> onBooted :: EventHandler
> onBooted ps = liftIO $ do
>   putStrLn "Asterisk is fully booted."
>   print ps
 
 -}

-- | Action or response or event parameters
type Parameters = [(B.ByteString, B.ByteString)]

type ActionType = B.ByteString

type EventType = B.ByteString

type ActionID = Integer

type ResponseType = B.ByteString

type EventHandler = Parameters -> IO ()

-- | Action packet (sent to Asterisk)
data Action = Action ActionID ActionType Parameters
  deriving (Eq, Show)

-- | Response packet (received from Asterisk)
data Response = Response ActionID ResponseType Parameters [B.ByteString]
  deriving (Eq, Show)

-- | Event packet (received from Asterisk)
data Event = Event EventType Parameters
  deriving (Eq, Show)

-- | AMI monad internal state
data AMIState = AMIState {
    amiHandle :: Maybe Handle                        -- ^ Handle for socket of Asterisk connection
  , amiActionID :: ActionID                          -- ^ ActionID of last action
  , amiResponses :: M.Map ActionID (Maybe Response)  -- ^ Responses for sent actions
  , amiEventHandlers :: M.Map EventType EventHandler -- ^ Event handlers
  }

-- | Info needed to connect and authenticate in Asterisk
data ConnectInfo = ConnectInfo {
    ciHost :: String           -- ^ Host with Asterisk server (e.g. `localhost')
  , ciPort :: Int              -- ^ Port of Asterisk server (usually 5038)
  , ciUsername :: B.ByteString -- ^ Username
  , ciSecret :: B.ByteString   -- ^ Secret
  } deriving (Eq, Show)

-- | The AMI monad
type AMI a = ReaderT (TVar AMIState) IO a

packID :: ActionID -> B.ByteString
packID i = B.pack (show i)

-- | Sort-of Control.Monad.State.gets
getAMI :: (AMIState -> a) -> AMI a
getAMI fn = do
  var <- ask
  st <- liftIO $ atomically $ readTVar var
  return (fn st)

-- | Sort-of Control.Monad.State.put
putAMI :: AMIState -> AMI ()
putAMI st = do
  var <- ask
  liftIO $ atomically $ writeTVar var st

-- | Sort-of Control.Monad.State.modify
modifyAMI :: (AMIState -> AMIState) -> AMI ()
modifyAMI fn = do
  st <- getAMI id
  putAMI (fn st)

-- | Return next ActionID
inc :: AMI ActionID
inc = do
  st <- getAMI id
  let n = 1 + amiActionID st
  putAMI $ st {amiActionID = n}
  return n

-- | Get connection handle
getHandle :: AMI Handle
getHandle = do
  mbh <- getAMI amiHandle
  case mbh of
    Nothing -> fail "Connection is not opened"
    Just h -> return h

-- | Add an event handler
handleEvent :: EventType -> EventHandler -> AMI ()
handleEvent t handler = modifyAMI add
  where
    add st = st {amiEventHandlers = M.insert t handler (amiEventHandlers st)}

-- | Send an Action packet and return the response.
--
-- CAUTION: the response value should be evaluated in order
-- to be removed from internal responses queue. Leaving
-- response value un-evaluated (e.g. unused) will cause
-- memory leak.
--
query :: ActionType -> Parameters -> AMI Response
query t ps = do
  i <- inc
  var <- ask
  liftIO $ atomically $ do
      st <- readTVar var
      let resps = M.insert i Nothing (amiResponses st)
      writeTVar var $ st {amiResponses = resps}

  h <- getHandle
  liftIO $ sendPacket h (Action i t ps)
  return $ unsafePerformIO $ do
    st <- atomically $ readTVar var
    atomically $ do 
      st <- readTVar var
      let resps = amiResponses st
      case M.lookup i resps of
        Just (Just a) -> do
           writeTVar var $ st {amiResponses = M.delete i resps}
           return a
        Just (Nothing) -> retry
        Nothing -> fail $ "There was no response for Action " ++ show i

-- | Open a connection to Asterisk and authenticate
open :: ConnectInfo -> AMI ThreadId
open info = do
    h <- liftIO $ connectTo (ciHost info) (PortNumber $ fromIntegral $ ciPort info)
    t <- forkAnswersReader h
    modifyAMI $ \st -> st {amiHandle = Just h}
    s <- liftIO $ B.hGetLine h
    auth <- query "Login" [("Username", ciUsername info), ("Secret", ciSecret info)]
    case auth of
      Response _ "Success" _ _ -> return t
      _ -> fail "Authentication failed"

-- | Open a connection to Asterisk and authenticate using MD5 challenge
openMD5 :: ConnectInfo -> AMI ThreadId
openMD5 info = do
    h <- liftIO $ connectTo (ciHost info) (PortNumber $ fromIntegral $ ciPort info)
    s <- liftIO $ B.hGetLine h
    t <- forkAnswersReader h
    modifyAMI $ \st -> st {amiHandle = Just h}
    chp <- query "Challenge" [("AuthType", "md5")]
    case chp of
      Response _ "Success" [("Challenge", ch)] _ -> do
        let key = B.pack $ show $ md5 $ L.fromChunks [ch `B.append` ciSecret info]
        auth <- query "Login" [("AuthType", "md5"),
                            ("Username", ciUsername info),
                            ("Key", key)]
        case auth of
          Response _ "Success" _ _ -> return t
          x -> fail $ "MD5 authentication failed: " ++ show x
      _ -> fail "Cannot get challenge for MD5 authentication"

-- | Close Asterisk connection
close :: ThreadId -> AMI ()
close t = do
  !x <- query "Logoff" [] 
  h <- getHandle
  modifyAMI $ \st -> st {amiHandle = Nothing}
  rs <- getAMI amiResponses
  liftIO $ killThread t
  liftIO $ hClose h

-- | Connect, execute acions, disconnect
withAMI :: ConnectInfo -> AMI a -> IO a
withAMI info ami = runAMI $ do
    t <- open info
    r <- ami
    close t
    return r

-- | Connect (using MD5 challenge), execute acions, disconnect
withAMI_MD5 :: ConnectInfo -> AMI a -> IO a
withAMI_MD5 info ami = runAMI $ do
    t <- openMD5 info
    r <- ami
    close t
    return r

-- | Send one AMI packet
sendPacket :: Handle -> Action -> IO ()
sendPacket h p = do
  let s = format p `B.append` "\r\n"
  B.hPutStr h s
  B.hPutStr h "\r\n"
  hFlush h

-- | Run AMI actions
runAMI :: AMI a -> IO a
runAMI ami = do
  var <- atomically $ newTVar (AMIState Nothing 0 M.empty M.empty)
  runReaderT ami var

readUntilEmptyLine :: Handle -> IO B.ByteString
readUntilEmptyLine h = do
  str <- B.hGetLine h `E.catch` \(E.SomeException _) -> return "\n"
  if (str == "\n") || (str == "\r") || (str == "\r\n")
    then return str
    else do
         next <- readUntilEmptyLine h
         return $ str `B.append` next

forkAnswersReader :: Handle -> AMI ThreadId
forkAnswersReader h = do
    var <- ask
    liftIO $ forkIO (forever $ reader h var)
  where
    reader :: Handle -> TVar AMIState -> IO ()
    reader h var = do
      str <- readUntilEmptyLine h
      case parse str of
        Left err -> do
                    putStrLn $ "Error parsing answer: " ++ err
                    return ()
        Right (Right p@(Response i _ _ _)) -> do
          atomically $ do
            st <- readTVar var
            let resps = M.insert i (Just p) (amiResponses st)
            writeTVar var $ st {amiResponses = resps}
        Right (Left p@(Event t ps)) -> do
            st <- atomically $ readTVar var
            case M.lookup t (amiEventHandlers st) of
              Nothing -> return ()
              Just handler -> handler ps

linesB y = h : if B.null t then [] else linesB (B.drop 2 t)
   where (h,t) = B.breakSubstring "\r\n" y

parse :: B.ByteString -> Either String (Either Event Response)
parse str = uncurry toPacket =<< (toPairs [] $ B.split '\r' str)
  where
    toPairs :: Parameters -> [B.ByteString] -> Either String (Parameters, [B.ByteString])
    toPairs [] [] = Left "Empty packet"
    toPairs acc [] = Right (acc, [])
    toPairs acc (s:ss) =
      case B.split ':' s of
        []     -> return (acc, [])
        [n,v]  -> let new = (n, B.dropWhile (== ' ') v)
                  in  toPairs (acc ++ [new]) ss
        x      -> Right (acc, (s:ss))

    toPacket :: Parameters -> [B.ByteString] -> Either String (Either Event Response)
    toPacket [] text = Right $ Right $ Response 0 "text" [] text
    toPacket ((k,v):pairs) text =
      case k of
        "Response" -> toResponse v pairs text
        "Event"    -> toEvent    v pairs
        _          -> Left  $ "Invalid first parameter: " ++ show v

    getField :: B.ByteString -> Parameters -> Either String (B.ByteString, Parameters)
    getField x ps = go x [] ps

    go x acc [] = Left "No field in packet"
    go x acc ((k,v):rest)
      | x == k    = Right (v, acc ++ rest)
      | otherwise = go x ((k,v):acc) rest

    toResponse name pairs text = do
      (i, ps) <- getField "ActionID" pairs
      return $ Right $ Response (read $ B.unpack i) name ps text

    toEvent name pairs = Right $ Left $ Event name pairs

format :: Action -> B.ByteString
format (Action i name ps) =
    formatParams $ [("Action", name), ("ActionID", packID i)] ++ ps

formatParams :: Parameters -> B.ByteString
formatParams pairs = B.intercalate "\r\n" $ map one pairs
  where
    one (k,v) = k `B.append` ": " `B.append` v