-- | A network notification utility to work with Growl . -- -- An application must register itself by sending a registrationPacket. Then, to send -- a notification, send a notificationPacket. Any packet must have an md5sum tacked on -- to the end before being sent. module Network.GrowlNotify ( registrationPacket , notificationPacket , addMD5Sum , sendMessage ) where import Data.Word import Data.Binary.Put import qualified Data.ByteString.Lazy as B import qualified Char import Data.Digest.MD5 import Network.Socket import Network.BSD growl_udp_port=9887 growl_protocol_version=1 growl_type_registration=0 growl_type_notification=1 makeBS s = B.pack $ map (fromIntegral . Char.ord) s putString :: String -> Put putString = do putLazyByteString . makeBS -- | register this application and its notification with growl -- | any notifications will be on by default registrationPacket :: String -- ^ The name of this application -> [String] -- ^ A list of notifications -> B.ByteString -- ^ The packet registrationPacket appName notiNames = runPut $ do putWord8 growl_protocol_version putWord8 growl_type_registration putWord16be $ fromIntegral $ length appName putWord8 $ fromIntegral $ lengthnames putWord8 $ fromIntegral $ lengthnames putString appName mapM_ addNotification notiNames mapM_ putWord8 [0..(fromIntegral lengthnames)-1] where addNotification :: String -> Put addNotification s = do putWord16be $ fromIntegral $ length s putLazyByteString $ makeBS s lengthnames = length notiNames -- | Create a notification packet notificationPacket :: Bool -- ^ True iff the notification should be sticky -> String -- ^ The name of this application -> String -- ^ The notification name -> String -- ^ The title of this notification -> String -- ^ The notification text -> B.ByteString -- ^ The packet notificationPacket sticky appName notification title description = runPut $ do putWord8 growl_protocol_version putWord8 growl_type_notification putWord16be $ if sticky then 1 else 0 putLength notification putLength title putLength description putLength appName putString notification putString title putString description putString appName where putLength = putWord16be . fromIntegral . length -- | Tack on the md5sum to the end of the message, with a (possibly empty) password addMD5Sum :: String -- ^ The password -> B.ByteString -- ^ The packet (from notificationPacket or registrationPacket) -> B.ByteString -- ^ The message with appended md5sum, ready for sendMessage addMD5Sum password message = B.append message s where s = B.pack $ hash $ map fromIntegral $ B.unpack $ B.append message bspassword bspassword = makeBS password -- | Send the packet sendMessage :: String -- ^ The server (an IP address or hostname) -> B.ByteString -- ^ The message (with md5sum) to send -> IO () sendMessage server m = do server' <- getHostByName server let d = map (Char.chr . fromIntegral) $ B.unpack m s <- socket AF_INET Datagram 0 write (hostAddress server') s d sClose s write :: HostAddress -> Socket -> String -> IO () write addr sock s = do sendTo sock s (SockAddrInet (fromIntegral growl_udp_port) addr) return ()