campfire-0.1.1: Haskell implementation of the Campfire API

Portabilityportable
Stabilityprovisional
MaintainerMichael Xavier <michael@michaelxavier.net>

Web.Campfire

Description

Toplevel module for the Campfire API operating in the CamfireM monad. Covers the entire campfire API excluding the streaming and file upload APIs. Might include support for these features in the future.

 {-# LANGUAGE OverloadedStrings #-}
 import Web.Campfire
 import Web.Campfire.Monad
 import Web.Campfire.Types
 import Control.Monad.Reader
 import Data.Text (unpack)
 
 doStuff :: CampfireM ()
 doStuff = do
   (room:_) <- getRooms
   let rid = roomId room
   joinRoom rid
   speak rid stmt
   leaveRoom rid
   return ()
           where stmt = TextStatement { statementBody = "ATTENTION: I have nothing important to say" }
 
 main :: IO ()
 main = do
   runReaderT (unCampfireM doStuff) env
   me <- runReaderT (unCampfireM getMe) env
   putStrLn "Hello, my name is:"
   putStrLn . unpack $ userName me
        where env  = CampfireEnv { cfKey = "MYKEY", cfSubDomain = "mysubdomain"}

Synopsis

Documentation

getRooms :: CampfireM [Room]Source

Get a list of rooms visible to the authenticated user.

getRoomSource

Arguments

:: Id

Room ID

-> CampfireM Room 

Get a specific room by Room ID.

getPresence :: CampfireM [Room]Source

Get a list of rooms in which the authenticated user is present.

setRoomTopicSource

Arguments

:: Id

Room ID

-> Text

New topic

-> CampfireM (Int, ByteString)

Status code and body (may change)

Change the topic of a particular room.

setRoomNameSource

Arguments

:: Id

Room ID

-> Text

New room name

-> CampfireM (Int, ByteString)

Status code and body (may change)

Change the name of a particular room.

joinRoomSource

Arguments

:: Id

Room ID

-> CampfireM (Int, ByteString)

Status code and body (may change)

Causes the authenticated user to join a particular room.

leaveRoomSource

Arguments

:: Id

Room ID

-> CampfireM (Int, ByteString)

Status code and body (may change)

Causes the authenticated user to leave a particular room.

lockRoomSource

Arguments

:: Id

Roomd ID

-> CampfireM (Int, ByteString)

Status code and body (may change)

Locks a particular room.

unlockRoomSource

Arguments

:: Id

Room ID

-> CampfireM (Int, ByteString)

Status code and body (may change)

Unlocks a particular room.

getMe :: CampfireM UserSource

Get information about the currently authenticated user.

getUserSource

Arguments

:: Id

User ID

-> CampfireM User 

Get information about the requested user.

speakSource

Arguments

:: Id

The room ID in which to speak

-> Statement

The statement to send to the room

-> CampfireM (Int, ByteString)

Status code and body (may change)

Say something in a room as the currently authenticated user.

highlightMessageSource

Arguments

:: Id

Message ID

-> CampfireM (Int, ByteString)

Status code and body (may change)

Put a star next to a message. That message will then show up in that day's highlights.

unhighlightMessageSource

Arguments

:: Id

Message ID

-> CampfireM (Int, ByteString)

Status code and body (may change)

Remove the star next to a message.

getRecentMessagesSource

Arguments

:: Id

Room ID

-> Maybe Integer

Optional limit. Default is 100

-> Maybe Integer

Optional message ID. Setting this will retreive messages since that message was received.

-> CampfireM [Message] 

Receive a list of recent messages in a particular room.

getUploadsSource

Arguments

:: Id

Room ID

-> CampfireM [Upload] 

Get a list of up to 5 recent uploads to a given room

getUploadSource

Arguments

:: Id

Room ID

-> Id

Upload ID

-> CampfireM Upload 

Retrieve a particular upload from a room.

searchSource

Arguments

:: Text

Search string

-> CampfireM [Message] 

Search for messages matching a given term.

getTodayTranscriptSource

Arguments

:: Id

Room ID

-> CampfireM [Message] 

Get a transcript of all messages in a room for the day.

getTranscriptSource

Arguments

:: Id

Room ID

-> Day

Day from which to retrieve the transcript

-> CampfireM [Message] 

Get a transcript of all messages in a room for a particular day