-----------------------------------------------------------------------------
-- Copyright 2019, Advise-Me project team. This file is distributed under 
-- the terms of the Apache License 2.0. For more information, see the files
-- "LICENSE.txt" and "NOTICE.txt", which are included in the distribution.
-----------------------------------------------------------------------------
-- |
-- Maintainer  :  bastiaan.heeren@ou.nl
-- Stability   :  provisional
-- Portability :  portable (depends on ghc)
--
-- An entry is created for each request that is diagnosed. It contains the diagnosis result for each made input.
-- At some later point it will also be filled with the assessment of the diagnosis.
--
-----------------------------------------------------------------------------

module Recognize.Data.Entry where

import Data.List
import Ideas.Common.Id
import Recognize.Data.DiagnoseError
import Recognize.Data.Approach
import Recognize.Data.Solution
import Recognize.Data.DiagnoseResult
import Ideas.Text.HTML
import Ideas.Text.HTML.W3CSS
import Ideas.Text.XML
import qualified Text.PrettyPrint.Leijen as PP

data Entry = Entry
   {
      diagnoses   :: [DiagnoseResult] -- ^ diagnose result for each input of the exercise
   }

instance Show Entry where
 show = show . PP.pretty

instance PP.Pretty Entry where
   pretty e = PP.vcat
      [ PP.string ("=== Diagnosis " ++ show i ++ " ===")
        PP.<$$> PP.indent 2 (PP.pretty d)
      | d <- diagnoses e
      , let i = getInputId (originalInput d)
      ]
    where
      pp s = maybe PP.empty (\x -> PP.string $ s ++ ": " ++ show x)

instance ToXML Entry where
 toXML e = makeXML "entry" $ mconcat
     [ element "diagnoses"
         (map
          (\v-> let k = getInputId (originalInput v)
                in element "input" ["id" .=. show k, builderXML v])
         (diagnoses e)
         )
     ]


instance ToHTML Entry where
   toHTML e = container $ background LightGray $ mconcat
      [ if null (diagnoses e)
        then string "(no diagnoses)"
        else toHTML (diagnoses e)
      ]

-- | Determine the category of the overal solution and then show it
categoryAsString :: Entry -> String
categoryAsString e
   | null (diagnoses e) = show Unknown
   | otherwise = intercalate ", " (map (show . approach) (diagnoses e))