{-| Module : CsvData Description : Writing to csv file format Copyright : Copyright (C) 2019 S. Kamps License : -- This file is distributed under the terms of the Apache License 2.0. For more information, see the file "LICENSE", which is included in the distribution. Stability : experimental -} {-# LANGUAGE OverloadedStrings #-} module CsvData (encodeItemsToFile ,appendItemToFile ,appendDistToFile ,appendPopToFile ,MetricInfo (..) ,DistPair (..) ) where -- bytestring import Data.ByteString.Lazy (ByteString) import qualified Data.ByteString.Lazy as ByteString import FileOperation -- cassava import Data.Csv ( DefaultOrdered(headerOrder) , Header , ToField(toField) , ToNamedRecord(toNamedRecord) , ToRecord (toRecord) , (.:) , (.=) ) import qualified Data.Csv as Cassava import qualified Data.Text as Text import qualified Data.Text.Encoding as TextEnc import Data.Vector (Vector) import qualified Data.Vector as Vector import Settings (Settings) -- | Contains the metric information data MetricInfo = MetricInfo { identifier :: !String -- ^ The unique identifier of this data (TODO would be nice if this could be a list) , relationKey :: !String -- ^ The key to this specific metric relation (E.g., LCOM) , value :: !Double -- ^ The actual value associated with the identifier. } deriving (Show) instance Num MetricInfo where (MetricInfo id1 k1 v1) * (MetricInfo _ _ v2) = MetricInfo id1 k1 (v1 * v2) newtype DistPair = DistPair { getPair :: (Int, Int) } deriving (Show) ---------------------------cassava instances metric info on program level instance ToRecord MetricInfo where toRecord (MetricInfo identifier relationKey value) = Cassava.record [ toField identifier , toField relationKey , toField value ] instance ToNamedRecord MetricInfo where toNamedRecord (MetricInfo identifier relationKey value) = Cassava.namedRecord [ "Id" .= Text.pack identifier , "Metric" .= Text.pack relationKey , "Value" .= value ] instance DefaultOrdered MetricInfo where headerOrder _ = Cassava.header [ "Id" , "Metric" , "Value" ] ---------------------------encode metric info on program level -- | encode MetricInfo item to csv formatted ByteSting without header encodeItems :: [MetricInfo] -> ByteString encodeItems = Cassava.encode -- | encode MetricInfo item to csv formatted ByteSting with header encodeHeaderItems :: [MetricInfo] -> ByteString encodeHeaderItems = Cassava.encodeDefaultOrderedByName -- | Creates a new file and writes supplied MetricInfo data. encodeItemsToFile :: Settings -- ^ File system settings. -> String -- ^ A name. E.g., LCOM, Gini -> [MetricInfo] -- ^ Contains the metric information -> IO () encodeItemsToFile settings metricName mis = do let outputFile = metricOutputFile settings metricName ByteString.writeFile outputFile $ encodeHeaderItems mis -- | Append MetricInfo to file. If supplied file does not exist, one will be created. appendItemToFile :: Settings -- ^ File system settings. -> String -- ^ A name. E.g., LCOM, Gini -> [MetricInfo] -- ^ Contains the metric information -> IO () appendItemToFile settings metricName mi = do let outputFile = metricOutputFile settings metricName ft <- isFileThere outputFile if ft then ByteString.appendFile outputFile $ encodeItems mi else ByteString.writeFile outputFile $ encodeHeaderItems mi ---------------------------cassava instances metric distribution instance ToNamedRecord DistPair where toNamedRecord pair = Cassava.namedRecord [ "Frequentie" .= fst (getPair pair) , "Value" .= snd (getPair pair) ] instance DefaultOrdered DistPair where headerOrder _ = Cassava.header [ "Frequentie" , "Value" ] instance ToRecord DistPair where toRecord pair = Cassava.record [toField (fst $ getPair pair) ,toField (snd $ getPair pair) ] ---------------------------encode metric distribution -- | encode DistPair item to csv formatted ByteSting without header encodeDist :: [DistPair] -> ByteString encodeDist = Cassava.encode -- | encode DistPair item to csv formatted ByteSting with header encodeHeaderDist :: [DistPair] -> ByteString encodeHeaderDist = Cassava.encodeDefaultOrderedByName -- | Creates a new file and writes supplied DistInfo data. encodeDistToFile :: Settings -- ^ File system settings. -> String -- ^ A name. E.g., LCOM, CBO, LOC -> DistPair -- ^ Contains the metric distribution information -> IO () encodeDistToFile settings metricName dis = do let outputFile = metricOutputFile settings metricName ByteString.writeFile outputFile $ encodeHeaderDist [dis] -- | Append DistInfo to file. If supplied file does not exist, one will be created. appendDistToFile :: Settings -- ^ File system settings. -> String -- ^ A name. E.g., LCOM, CBO, LOC -> DistPair -- ^ Contains the metric distribution information -> IO () appendDistToFile settings metricName di = do let outputFile = metricOutputFile settings metricName ft <- isFileThere outputFile if ft then ByteString.appendFile outputFile $ encodeDist [di] else ByteString.writeFile outputFile $ encodeHeaderDist [di] ---------------------------cassava instances metric population instance ToRecord Int where toRecord v = Cassava.record [toField v] ---------------------------encode metric population -- | encode Int item to csv formatted ByteSting without header encodePop :: [Int] -> ByteString encodePop = Cassava.encode -- | Creates a new file and writes supplied Int data. encodePopToFile :: Settings -- ^ File system settings. -> String -- ^ A name. E.g., LCOM, CBO, LOC -> Int -- ^ Contains the metric metric value -> IO () encodePopToFile settings metricName pop = do let outputFile = metricOutputFile settings metricName ByteString.writeFile outputFile $ encodePop [pop] -- | Append Int to file. If supplied file does not exist, one will be created. appendPopToFile :: Settings -- ^ File system settings. -> String -- ^ A name. E.g., LCOM, CBO, LOC -> Int -- ^ Contains the metric value -> IO () appendPopToFile settings metricName pop = do let outputFile = metricOutputFile settings metricName ft <- isFileThere outputFile if ft then ByteString.appendFile outputFile $ encodePop [pop] else ByteString.writeFile outputFile $ encodePop [pop]