-- http://en.wikipedia.org/wiki/Cron module Entry3rdCrontab ( Crontab(Crontab), Entry(Entry), Comment(CommentLine, BlankLine) , Field(List, Range, All, EveryNth) ) where import Text.ParserCombinators.Parsec import List(intersperse) data Crontab = Crontab { entries :: [Entry], endOfCrontabComments :: [Comment] } deriving Eq data Entry = Entry { comment :: [Comment] , minutes :: Field , hours :: Field , dayOfMonth :: Field , month :: Field , dayOfWeek :: Field , command :: String } deriving Eq data Comment = CommentLine String | BlankLine deriving Eq data Field = List [Int] -- 1,2,6 | Range Int Int -- 3-6 | All -- * | EveryNth Int -- */3 deriving Eq -------------- Show instances -------------------------------- instance Show Crontab where show (Crontab es cs) = unlines $ map show es ++ map show cs instance Show Entry where show e = (concat $ map (++ "\n") $ map show (comment e)) ++ (concat $ intersperse "\t" $ map show [minutes e, hours e, dayOfMonth e, month e, dayOfWeek e]) ++ "\t" ++ command e instance Show Comment where show (CommentLine s) = '#':s show BlankLine = "" instance Show Field where show (List xs) = concat $ intersperse "," (map show xs) show (Range l r) = show l ++ "-" ++ show r show All = "*" show (EveryNth x) = "*/" ++ show x ------------- Parser and Read instance ------------------------ instance Read Crontab where readsPrec _ serialzedText = [crontabParser serialzedText] crontabParser xs = let (Right (crontab, unconsumed)) = parse parsecParser "" xs in (crontab, unconsumed) where parsecParser = do xs <- many (try crontabEntry) endComment <- many parseComment unconsumed <- many anyChar return (Crontab xs endComment, unconsumed) crontabEntry = do comment' <- many parseComment minute <- parseField hour <- parseField dayOfMonth <- parseField month <- parseField dayOfWeek <- parseField command <- untilEOL return $ Entry comment' minute hour dayOfMonth month dayOfWeek command -- Field functions parseField = let tryAll [] = pzero tryAll (x:xs) = try (do x' <- x whitespace return x') <|> tryAll xs in tryAll [range, star, everyNth, list] list = do x <- digits xs <- many (do char ',' digits) return $ List $ map read (x:xs) range = do low <- digits char '-' high <- digits return $ Range (read low) (read high) star = do char '*' return All everyNth = do char '*' char '/' digits >>= return . EveryNth . read digits = many1 digit whitespace = many1 $ oneOf " \t" -- parseComment = do char '#' untilEOL >>= return . CommentLine <|> do blanks <- whitespace char '\n' return BlankLine untilEOL = manyTill anyChar ((do char '\n' >> return ()) <|> eof)