module CSVTable ( red2Table ) where -- (c) 2007 Hans van Thiel -- Version 0.1 License GPL -- module: convert reduction result to CSV -- format that can be read by Open Office Calc import Data.Char (isDigit ) import Data.List ( delete ) import Data.Array ---------- some auxiliary functions ---------------- -- check whether a string is a number or text allDigit :: String -> Bool allDigit [] = True allDigit (x:xs) | isDigit x = allDigit xs | otherwise = False -- convert string or number to OO Calc format toCalc :: String -> String toCalc x | allDigit x = x | otherwise = "\"" ++ x ++ "\"" -- get the value string of an attribute-value tuple strVal :: Array Int [String] -> (Int,Int) -> String strVal attvarr x = toCalc $ (attvarr ! (fst x)) !! (snd x) -- get the attribute string from an index strAtt :: Array Int [String] -> Int -> String strAtt attvarr ix = head (attvarr ! ix) -- insert a separator s between two strings inSep :: String -> String -> String -> String inSep s x y = x ++ s ++ y ---------------------------------------------- -- show the value of the attribute index or a blank indStr :: Array Int [String] -> [(Int,Int)] -> Int-> String indStr attvarr [] x = " " indStr attvarr (y:ys) x | x == fst y = strVal attvarr y | otherwise = indStr attvarr ys x -- turn antecedent into CSV string ant2Str :: Array Int [String] -> [Int]-> [(Int,Int)]-> String ant2Str attvarr indls redlin = foldl1 (inSep ",") y where y = map (indStr attvarr redlin ) indls -- get consequent value string and newline cns2Str :: Array Int [String] -> (Int,Int) -> String cns2Str attvarr cons = ",\" is \"," ++ (strVal attvarr cons) ++ "\n" -- get the table antecedent header ahd2Str :: Array Int [String] -> [Int] -> String ahd2Str attvarr indls = foldl1 (inSep ",") y where y = [ strAtt attvarr z | z <- indls ] -- get consequent attribute string and newline chd2Str :: Array Int [String] -> Int -> String chd2Str attvarr ati = ", ," ++ (toCalc (head (attvarr ! ati))) ++ "\n" -- show the table header in csv format hd2csv :: Array Int [String] -> ([Int], Int) -> String hd2csv attvarr hdp = (ahd2Str attvarr (fst hdp)) ++ (chd2Str attvarr (snd hdp)) --------------------------------------------------- -- show a reduction for a consequent value in csv red2csv :: Array Int [String] -> [Int] -> ([[(Int,Int)]], (Int,Int)) -> [String] red2csv attvarr indls rstp = map ( ++ cns2Str attvarr (snd rstp)) redstr where redstr = map (ant2Str attvarr indls) (fst rstp) -- show the reduction results for an attribute in csv all2csv :: Array Int [String] -> [Int] -> [([[(Int,Int)]], (Int,Int))] -> String all2csv attvarr indls redres = concat $ concatMap (red2csv attvarr indls) redres -- output a csv table from the array of attribute-value names, -- the antecedent attributes and consequent, and the -- zip of the reduction results and the consequent values red2Table :: Array Int [String] -> ([Int],Int)-> [([[(Int,Int)]], (Int,Int))] -> String red2Table attvarr indls redres = (hd2csv attvarr indls) ++ (all2csv attvarr (fst indls) redres)