module Codec ( avCod, avArr )where -- (c) 2007 Hans van Thiel -- Version 0.1 License GPL -- Note: extended Haskell because of dependent parameters {- module: code a table of strings into: attribute-value lists, with the attributes in the heads lists of tuples, fst indexing att, snd indexing val attribute indexes av-list of lists, start 0 value indexes value in av-list, start 1 string table has: attribute names in first line attribute values in following lines -} import Data.List (transpose, elemIndex) import Control.Monad.State import Data.Array -- get unique value-list and code strings as indices -- Note: index incremented by 1, index 0 is the attribute repl1 :: String -> [String] -> (Int, [String]) repl1 x tb = case elemIndex x tb of Nothing -> ((length tb) + 1, tb ++ [x] ) Just i -> (i + 1, tb) toState :: String -> State [String] Int toState x = State (repl1 x) getVals :: [String] -> ([Int],[String]) getVals x = (runState (getState x)) [] where getState = sequence . (map toState) getInds :: [String] -> [Int] getInds = fst . getVals getTb :: [String] -> [String] getTb = snd . getVals -- get attribute-value lists from the table -- Note: see comment at start for indexing scheme avLs :: [[String]] -> [[String]] avLs (x:xs) = zipWith (:) x (values xs) where values = (map getTb) . transpose -- replace table, except first line, with: -- tuples representing attribute-value pair -- Note: see comment at start for indexing scheme avCod :: [[String]] -> [[(Int, Int)]] avCod (x:xs) = map (zip [0..]) (values xs) where values = transpose . (map getInds) . transpose -- make an array of attribute-value lists from the -- table, instead of a list of lists of Strings avArr :: [[String]] -> Array Int [String] avArr tb = listArray (0, (length attvals) -1) attvals where attvals = avLs tb