{-# LANGUAGE OverloadedStrings #-} module ConfigFiles where import Data.ByteString.Lazy.Char8 as L import System.Posix.User import System.Posix.Files (fileExist) import System.FilePath import System.Directory import System.IO -- import System.IO.Strict import System.IO.Error import Control.Exception import Control.Monad import Control.DeepSeq import ByteStringOperators () -- For NFData instance import ControlMaybe import Data.List (partition) import Data.Maybe (catMaybes,isJust) type User = ByteString configDir = ".presence" buddyFile = "buddies" subscriberFile = "subscribers" otherFile = "others" pendingFile = "pending" solicitedFile = "solicited" configPath :: User -> String -> IO String configPath user filename = do ue <- getUserEntryForName (unpack user) return $ (++("/"++configDir++"/"++filename)) $ homeDirectory ue createConfigFile tag path = do let dir = dropFileName path doesDirectoryExist dir >>= flip unless (do createDirectory dir ) withFile path WriteMode $ \h -> do L.hPutStrLn h tag addItem item tag path = let doit = do handle (\e -> when (isDoesNotExistError e) (createConfigFile tag path >> doit)) $ do exists <- fileExist path if exists then withFile path AppendMode $ \h -> L.hPutStrLn h item else withFile path WriteMode $ \h -> do L.hPutStrLn h tag L.hPutStrLn h item in doit modifyFile :: (ByteString,FilePath) -> ByteString -> (ByteString -> IO (Maybe ByteString)) -> Maybe ByteString -> IO Bool -- Returns True if test function ever returned Nothing modifyFile (tag,file) user test appending = configPath user file >>= doit where doit path = do handle (\e -> if (isDoesNotExistError e) then (createConfigFile tag path >> doit path) else return False) $ do exists <- fileExist path if exists then do xs <- withFile path ReadMode $ \h -> do contents <- L.hGetContents h case L.lines contents of x:xs -> mapM test xs _ -> return [] let (keepers,deleted) = partition isJust xs withFile path WriteMode $ \h -> do L.hPutStrLn h tag forM_ (catMaybes keepers) (L.hPutStrLn h) withJust appending (L.hPutStrLn h) return . not . Prelude.null $ deleted else do withFile path WriteMode $ \h -> do L.hPutStrLn h tag withJust appending (L.hPutStrLn h) return False modifySolicited = modifyFile ("" , solicitedFile) modifyBuddies = modifyFile ("" , buddyFile) modifyOthers = modifyFile ("" , otherFile) modifyPending = modifyFile ("" , pendingFile) modifySubscribers = modifyFile ("", subscriberFile) addBuddy :: User -> ByteString -> IO () addBuddy user buddy = configPath user buddyFile >>= addItem buddy "" addSubscriber :: User -> ByteString -> IO () addSubscriber user subscriber = configPath user subscriberFile >>= addItem subscriber "" addSolicited :: User -> ByteString -> IO () addSolicited user solicited = configPath user solicitedFile >>= addItem solicited "" getConfigList path = handle (\e -> if isDoesNotExistError e then (return []) else throw e) $ withFile path ReadMode $ L.hGetContents >=> return . Prelude.tail . L.lines >=> (\a -> seq (rnf a) (return a)) getBuddies :: User -> IO [ByteString] getBuddies user = configPath user buddyFile >>= getConfigList getSubscribers :: User -> IO [ByteString] getSubscribers user = configPath user subscriberFile >>= getConfigList getOthers :: User -> IO [ByteString] getOthers user = configPath user otherFile >>= getConfigList getPending :: User -> IO [ByteString] getPending user = configPath user pendingFile >>= getConfigList getSolicited :: User -> IO [ByteString] getSolicited user = configPath user solicitedFile >>= getConfigList