{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE DeriveGeneric #-} module File where import Data.ItCli import Data.List (intersperse, splitAt, sortOn) import Control.Applicative import Data.Monoid import Data.Yaml import qualified Data.ByteString.Lazy.Char8 as BS8 instance FromJSON IssueMeta where parseJSON = withObject "IssueMeta" $ \o -> IssueMeta <$> o .: "title" <*> o .: "closed" <*> o .: "date" instance FromJSON CommentMessage where parseJSON = fmap commentMessageFromString . parseJSON instance FromJSON Comment where parseJSON = withObject "Comment" $ \o -> Comment <$> o .: "date" <*> o .: "name" <*> o .: "mesg" instance FromJSON Comments where parseJSON = fmap Comments . parseJSON instance ToJSON IssueMeta where toJSON meta = object [ "title" .= (_issueTitle meta) , "closed" .= (_issueClosed meta) , "date" .= (_issueDate meta) ] instance ToJSON CommentMessage where toJSON (CommentMessage c) = toJSON c toJSON (FileAttachment c) = toJSON c instance ToJSON Comment where toJSON com = object [ "date" .= (_commentDate com) , "name" .= (_commentName com) , "mesg" .= (_commentMessage com) ] instance ToJSON Comments where toJSON (Comments cs) = toJSON cs printMeta :: IssueMeta -> String printMeta meta = (_issueTitle meta) ++ "\n" ++ (show $_issueDate meta) ++ "\n" ++ (printClosed $ _issueClosed meta) where printClosed False = "Open" printClosed True = "Closed" printComments :: Comments -> String printComments = concat . intersperse "\n\n" . fmap printComment . sortOn (_commentDate) . fromComments printComment :: Comment -> String printComment com = (_commentName com) ++ " - " ++ (show . _commentDate $ com) ++ "\n" ++ (comMsg . _commentMessage $ com) where comMsg (FileAttachment f) = f comMsg (CommentMessage m) = m