{-# LANGUAGE DoAndIfThenElse #-} {-# LANGUAGE RecordWildCards #-} -- | Common performance metrics which can be calculated using the confusion -- matrix. -- -- Fawcett, ROC Graphs: Notes and Practical Considerations for Researchers, -- 2004, Kluwer Academic Publishers module Statistics.PerformanceMetrics where import Control.Monad.Instances import Statistics.ConfusionMatrix -- | sensitivity sensitivity :: ConfusionMatrix -> WrappedDouble sensitivity ConfusionMatrix{..} = do tp <- tp fn <- fn if tp>0 then Right $ tp / (tp+fn) else Right 0 -- | specificity specificity :: ConfusionMatrix -> WrappedDouble specificity ConfusionMatrix{..} = do tp <- tp fp <- fp if tp>0 then Right $ tp / (tp+fp) else Right 0 -- | positive predictive value ppv :: ConfusionMatrix -> WrappedDouble ppv ConfusionMatrix{..} = do tp <- tp fp <- fp if tp>0 then Right $ tp / (tp+fp) else Right 0 -- | mathews correlation coefficient mcc :: ConfusionMatrix -> WrappedDouble mcc ConfusionMatrix{..} = do tp <- tp tn <- tn fp <- fp fn <- fn let d' = (tp+fp) * (tp+fn) * (tn+fp) * (tn+fn) let d = if d'==0 then 1 else sqrt d' return $ (tp*tn - fp*fn) / d -- | F-measure fmeasure :: ConfusionMatrix -> WrappedDouble fmeasure ConfusionMatrix{..} = do tp <- tp fp <- fp fn <- fn if tp>0 then Right $ 2*tp / (2*tp + fp + fn) else Right 0