azure-servicebus-0.1.0.1: Windows Azure ServiceBus API

StabilityExperimental
Maintainersaihemanth@gmail.com
Safe HaskellNone

Web.WindowsAzure.ServiceBus.Queue

Contents

Description

Provides API to pull from and push to ServiceBus queue Please refer to Service Bus Rest API for Service bus API

Following piece of code illustrates the use of API

 module Main where

import Web.WindowsAzure.ServiceBus.SBTypes
 import Web.WindowsAzure.ServiceBus.Queue
 import qualified Data.ByteString.Char8 as C

main = do
   sbContext <- sbContext (simpleSBInfo sb-namespace insert-your-issuer-key)
   enQueueBS sbContext queue-name (C.pack hello Haskell world)
   res <- deQueue sbContext kqueue 30
   print res

Synopsis

Pushing data to Queue

enQueueBS :: String -> ByteString -> SBContext -> IO ()Source

publish a message containing ByteString to queue.

The following publishes a strict bytestring bs to queue q

 enQueueBS q bs ctx

enQueueLBS :: String -> ByteString -> SBContext -> IO ()Source

publish a message containing ByteString to queue

The following publishes a lazy bytestring ,lbs, to queue q,

  
 enQueueLBS q lbs  ctx

Reading data from Queue

deQueue :: String -> Int -> SBContext -> IO ByteStringSource

Reads and deletes the message from a queue.

In order to destructively read the latest message from the queue (with a time out of n seconds),

deQueue queueName n context Note that the timeout can be at the most 55 seconds. This silently ignores the timeouts greater than 55