{-# OPTIONS_HADDOCK hide #-}
module Network.Xmpp.IM.Roster.Types where

import qualified Data.Map as Map
import           Data.Text (Text)
import           Network.Xmpp.Types

-- Note that `Remove' is not exported from IM.hs, as it will never be visible to
-- the user anyway.
data Subscription = None -- ^ the user does not have a subscription to the
                         -- contact's presence information, and the contact does
                         -- not have a subscription to the user's presence
                         -- information
                  | To  -- ^ the user has a subscription to the contact's
                        -- presence information, but the contact does not have a
                        -- subscription to the user's presence information
                  | From -- ^ the contact has a subscription to the user's
                         -- presence information, but the user does not have a
                         -- subscription to the contact's presence information
                  | Both -- ^ both the user and the contact have subscriptions
                         -- to each other's presence information
                  | Remove
                  deriving (Subscription -> Subscription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Subscription -> Subscription -> Bool
$c/= :: Subscription -> Subscription -> Bool
== :: Subscription -> Subscription -> Bool
$c== :: Subscription -> Subscription -> Bool
Eq, ReadPrec [Subscription]
ReadPrec Subscription
Int -> ReadS Subscription
ReadS [Subscription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Subscription]
$creadListPrec :: ReadPrec [Subscription]
readPrec :: ReadPrec Subscription
$creadPrec :: ReadPrec Subscription
readList :: ReadS [Subscription]
$creadList :: ReadS [Subscription]
readsPrec :: Int -> ReadS Subscription
$creadsPrec :: Int -> ReadS Subscription
Read, Int -> Subscription -> ShowS
[Subscription] -> ShowS
Subscription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Subscription] -> ShowS
$cshowList :: [Subscription] -> ShowS
show :: Subscription -> String
$cshow :: Subscription -> String
showsPrec :: Int -> Subscription -> ShowS
$cshowsPrec :: Int -> Subscription -> ShowS
Show)

data Roster = Roster { Roster -> Maybe Text
ver :: Maybe Text
                     , Roster -> Map Jid Item
items :: Map.Map Jid Item
                     } deriving Int -> Roster -> ShowS
[Roster] -> ShowS
Roster -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Roster] -> ShowS
$cshowList :: [Roster] -> ShowS
show :: Roster -> String
$cshow :: Roster -> String
showsPrec :: Int -> Roster -> ShowS
$cshowsPrec :: Int -> Roster -> ShowS
Show

-- | Roster Items
data Item = Item { Item -> Bool
riApproved :: Bool
                 , Item -> Bool
riAsk :: Bool
                 , Item -> Jid
riJid :: Jid
                 , Item -> Maybe Text
riName :: Maybe Text
                 , Item -> Subscription
riSubscription :: Subscription
                 , Item -> [Text]
riGroups :: [Text]
                 } deriving Int -> Item -> ShowS
[Item] -> ShowS
Item -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Item] -> ShowS
$cshowList :: [Item] -> ShowS
show :: Item -> String
$cshow :: Item -> String
showsPrec :: Int -> Item -> ShowS
$cshowsPrec :: Int -> Item -> ShowS
Show

data RosterUpdate = RosterUpdateRemove Jid
                  | RosterUpdateAdd Item -- ^ New or updated item
                  deriving Int -> RosterUpdate -> ShowS
[RosterUpdate] -> ShowS
RosterUpdate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RosterUpdate] -> ShowS
$cshowList :: [RosterUpdate] -> ShowS
show :: RosterUpdate -> String
$cshow :: RosterUpdate -> String
showsPrec :: Int -> RosterUpdate -> ShowS
$cshowsPrec :: Int -> RosterUpdate -> ShowS
Show

data QueryItem = QueryItem { QueryItem -> Maybe Bool
qiApproved :: Maybe Bool
                           , QueryItem -> Bool
qiAsk :: Bool
                           , QueryItem -> Jid
qiJid :: Jid
                           , QueryItem -> Maybe Text
qiName :: Maybe Text
                           , QueryItem -> Maybe Subscription
qiSubscription :: Maybe Subscription
                           , QueryItem -> [Text]
qiGroups :: [Text]
                           } deriving Int -> QueryItem -> ShowS
[QueryItem] -> ShowS
QueryItem -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QueryItem] -> ShowS
$cshowList :: [QueryItem] -> ShowS
show :: QueryItem -> String
$cshow :: QueryItem -> String
showsPrec :: Int -> QueryItem -> ShowS
$cshowsPrec :: Int -> QueryItem -> ShowS
Show

data Query = Query { Query -> Maybe Text
queryVer :: Maybe Text
                   , Query -> [QueryItem]
queryItems :: [QueryItem]
                   } deriving Int -> Query -> ShowS
[Query] -> ShowS
Query -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Query] -> ShowS
$cshowList :: [Query] -> ShowS
show :: Query -> String
$cshow :: Query -> String
showsPrec :: Int -> Query -> ShowS
$cshowsPrec :: Int -> Query -> ShowS
Show