-----------------------------------------------------------------------------
-- |
-- Module      :  Network.XMPP.IQ
-- Copyright   :  (c) pierre, 2007
-- License     :  BSD-style (see the file libraries/base/LICENSE)
-- 
-- Maintainer  :  k.pierre.k@gmail.com
-- Stability   :  experimental
-- Portability :  portable
--
-- XMPP IQ utilites
--
-----------------------------------------------------------------------------

module Network.XMPP.IQ
  ( iqSend
  , iqReplyTo
  ) where 

import Network.XMPP.Types
import Network.XMPP.Stanza
import Network.XMPP.Utils
import Network.XMPP.Concurrent
    
import Text.XML.HaXml
import Text.XML.HaXml.Posn    

-- | Send IQ of specified type with supplied data
iqSend :: String -- ^ ID to use
       -> IQType -- ^ IQ type
       -> [CFilter Posn] -- ^ request contents 
       -> XmppStateT ()
iqSend id t d = do
  outStanza $ IQ Nothing Nothing id t (map toContent d)               

-- Extract IQ reply that matches the supplied predicate from the event stream and send it (transformed)        
iqReplyTo :: (Stanza -> Bool) -- ^ Predicate used to match required IQ reply
          -> (Stanza -> [CFilter Posn]) -- ^ transformer function
          -> XmppThreadT ()
iqReplyTo p t = do
  s <- waitFor (\x -> p x && isIQ x)
  writeChanS (transform t s)
    where
      transform t s@(IQ from' to' id' type' body') =
          IQ to' from' id' Result (map toContent $ t s)