{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE OverloadedStrings #-} -- | Example that tweets from a "Madlibs" file. module Web.Toboggan ( act , program , TwitterBot (..) ) where import Text.Madlibs import qualified Data.Text as T import Web.Tweet import Control.Monad import System.Directory import Options.Generic import Data.Maybe -- | Data type for a twitter bot: configuration options and a CLI option data TwitterBot = TwitterBot { config :: FilePath "Path to the .mad template" , cred :: Maybe FilePath "Path to credentials file (default ~/.cred)" , cron :: Bool "Display example crontab for a twitter bot" , extras :: [String] "Extra inputs from command line" } deriving (Generic) instance ParseRecord TwitterBot -- | The command-line executable act :: IO () act = do twitterBot <- getRecord "Twitter bot generator" program twitterBot -- | Turn a `TwitterBot` into an IO action program :: TwitterBot -> IO () program twitterBot = do homeDir <- getHomeDirectory let configR = unHelpful . config $ twitterBot let ins = map T.pack $ unHelpful . extras $ twitterBot generatedText <- runFile ins configR let credR = fromMaybe (homeDir ++ "/.cred") . unHelpful . cred $ twitterBot if (unHelpful . cron $ twitterBot) then do dir <- getCurrentDirectory putStrLn (cronStr ++ "~/.local/bin/toboggan --cred " ++ dir ++ "/" ++ credR ++ " --config " ++ dir ++ "/" ++ configR ++ "\n") else pure () void $ basicTweet (T.unpack generatedText) credR -- | helper string for printing the crontab cronStr :: String cronStr = "\n# m h dom mon dow command\ \ 0 13 * * * "