-- |
-- * rotating_wallpaper
--
-- [@Author@] Yann Golanski.
--
-- [@Maintainer@] Yann Golanski <yann@kierun.org>
--
-- [@Description@] Wallpapers/Backdrop changer back end.
--
-- (c)2008 Yann Golanski, GPLv3 or above.
--
--  This program is free software: you can redistribute it and/or modify
--  it under the terms of the GNU General Public License as published by
--  the Free Software Foundation, either version 3 of the License, or
--  (at your option) any later version.
--
--  This program is distributed in the hope that it will be useful,
--  but WITHOUT ANY WARRANTY; without even the implied warranty of
--  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
--  GNU General Public License for more details.
--
--  You should have received a copy of the GNU General Public License
--  along with this program.  If not, see <http://www.gnu.org/licenses/>.
--
module Rotating_backdrop_logic where
import Distribution.Simple.Utils
import Control.Monad
import System.Random
import System.Process
import System.Exit
import System.Environment
import Control.Concurrent
import System.Time
import System.Log.Logger
import System.Log.Handler.Syslog
import Logger_logic

{------------------------------------------------------------------------------}
--main = onlyOnce "/home/yann/.rotate_wallpaper_list"
--main = doManyTimes "/home/yann/.rotate_wallpaper_list" 5
--main = mainLoop "./sample_wallpaper_list" 1


{------------------------------------------------------------------------------}
{-
onlyOnce :: FilePath -> IO ExitCode
onlyOnce path = do images <- parseImageFile path 
                   --mapM_ putStrLn images
                   n <- getRandomNumber (length images)
                   putStrLn $ "Picked images " ++ show n ++ " out of " ++ show ((length images)-1)
                   let (image, rest) = removeElement n images
                   putStrLn $ "Change desktop to image " ++ show image
                   changeDesktop image
-}

{------------------------------------------------------------------------------}
-- | Iterates over all the images, picking a random one each the time.
iterateImages :: [String] -- ^ The list of images.
              -> Int -- ^ A delay.
              -> IO () -- ^ An IO result -- in this case, a new backdrop.
iterateImages list s = do 
  n <- getRandomNumber (length list)
  let (image, rest) = removeElement n list
  changeDesktop image
  epoch <- getClockTime  
  logger INFO $ "Picked images " ++ show n ++ " out of " ++ show ((length list)-1) ++ ": " ++ show image
  let next = TimeDiff{tdYear=0, tdMonth=0, tdDay=0, tdHour=0, tdMin=0, tdSec=s, tdPicosec=0}
  logger INFO $ "Next backdrop change due on " ++  (show (addToClockTime next epoch))
  threadDelay (1000000 * s)
  if (length list) == 1
    then logger INFO "All done, re-reading master list"
    else iterateImages rest s


{------------------------------------------------------------------------------}
-- | Reads the list from the master file and starts iterating over it.
mainLoop :: FilePath -- ^ A path/name to the configuration file.
         -> Int -- ^ A delay.
         -> IO t -- ^ An exit code.
mainLoop path s = do 
  images <- parseImageFile path
  --let d = (if s == 0 then ((60*60*8.0)/(fromIntegral (length images))) else s)
  iterateImages images s
  mainLoop path s


{------------------------------------------------------------------------------}
{-
doManyTimes :: FilePath -- ^ 
            -> Int -- ^ 
            -> IO t -- ^
doManyTimes p s = do onlyOnce p
                     threadDelay (1000000 * s) -- microseconds!
                     --onlyOnce p
                     doManyTimes p s
-}


{------------------------------------------------------------------------------}
-- | Reads a file and return a list those elements are lines.
parseImageFile :: FilePath -- ^ The path/name to a configuration file.
                -> IO [String] -- ^ A list those elements are lines.
parseImageFile f = do inpStr <- readFile f
                      return $ filter (/="") (breaks (=='\n') inpStr)


{------------------------------------------------------------------------------}
-- | Gets a random number.
getRandomNumber :: Int -- ^ Maxium range (starts at 0)
                -> IO Int -- ^ A random number.
getRandomNumber n = getStdRandom $ randomR (0,n-1) 


{------------------------------------------------------------------------------}
-- | Removes an element from a list: Problem 20, 99 Haskell problems. 
removeElement :: Int --- ^ A random number.
              -> [a] -- ^ A list.
              -> (a, [a]) -- ^ A list of an entry and the rest of the original list.
removeElement k xs = case back of
                       [] -> error "removeAt: index too large"
                       x:rest -> (x, front ++ rest)
                     where (front, back) = splitAt k xs


{------------------------------------------------------------------------------}
-- | Changes the desktop image using qiv: http://www.klografx.net/qiv/index2.html
changeDesktop :: String -- ^ The path to an image.
              -> IO ExitCode -- ^ An exit code from the shell running qiv.
changeDesktop img = do ph <- runProcess "/usr/local/bin/qiv" ["-x", "-t", img] Nothing Nothing Nothing Nothing Nothing
                       --waitForProcess ph >>= print
                       waitForProcess ph