module Main where -- (c) 2007 Hans van Thiel -- Version 0.1 License GPL import System.Environment (getArgs ) import CSVParse (getTable ) import Codec (avArr, avCod ) import Aux (redAtt, selavN, gtAtec ) import CSVTable ( red2Table ) import Data.Array main = do [fname] <- getArgs tb <- getTable fname let attvarr = avArr tb consN <- getConsAtt attvarr let src = avCod tb cons = selavN consN attvarr redres = redAtt cons src indls = gtAtec (fst (head cons)) attvarr outTable = red2Table attvarr indls redres writeFile (consN ++ ".csv") outTable ----------------------------------------- -- print the list of attribute names shAtts :: Array Int [String] -> IO () shAtts attvar = print als where als = [ head x | x <- elems attvar ] -- get the consequent attribute from the user getConsAtt :: Array Int [String] -> IO String getConsAtt attvarr = do { putStrLn "Select the consequent attribute /n ( ? to see all)" ; answ <- getLine ; if answ == "?" then do { shAtts attvarr; getConsAtt attvarr } else return answ } -------------------------------------------