module IdeSession.Types.Progress (
    Progress(..)
  ) where
import Control.Applicative ((<$>), (<*>), (<|>))
import Data.Binary (Binary(..))
import Data.Text (Text)
import Data.Maybe (fromJust)
import GHC.Generics (Generic)
import qualified Data.Text as Text
import Text.Show.Pretty (PrettyVal)
import Data.Aeson.TH (deriveJSON, defaultOptions)
import IdeSession.Util () 
data Progress = Progress {
    
    
    
    
    
    
    progressStep :: Int
    
  , progressNumSteps :: Int
    
    
    
    
    
    
  , progressParsedMsg :: Maybe Text
    
  , progressOrigMsg :: Maybe Text
  }
  deriving (Eq, Ord, Generic)
instance PrettyVal Progress
instance Binary Progress where
  put (Progress {..}) = do put progressStep
                           put progressNumSteps
                           put progressParsedMsg
                           put progressOrigMsg
  get = Progress <$> get <*> get <*> get <*> get
instance Show Progress where
  show (Progress{..}) =
         "["
      ++ show progressStep
      ++ " of "
      ++ show progressNumSteps
      ++ "]"
      ++ fromJust (pad progressParsedMsg <|> pad progressOrigMsg <|> Just "")
    where
      pad :: Maybe Text -> Maybe String
      pad = fmap $ \t -> " " ++ Text.unpack t
$(deriveJSON defaultOptions ''Progress)