{- | Emping 0.5 (provisional) Module Aux provides some general purpose functions, which are used by other modules. Fri 04 Apr 2008 07:20:22 PM CEST -} module Aux where import Data.List ( partition, sortBy ) -- | AVp is the type of an attribute-value tuple. type AVp = (Int, Int) {- | Ant is the type of the Antedent in a rule. Warning: A fact is also a list of Int tuples, and so is a disjunction of attribute-value pairs. Use only when it really reprecents an Antedent of a rule. -} type Ant = [AVp] -- | Rule is the type of a rule, a tuple of an Ant and a AVp type Rule = (Ant,AVp) -- | checks whether the elements of the first list are all in the second list isSub :: Eq a => [a] -> [a] -> Bool isSub [] _ = True isSub (x:xs) y | not (x `elem` y) = False | otherwise = isSub xs y -- | checks whether two lists are equal as sets (regardless of order) isEq :: Eq a => [a] -> [a] -> Bool isEq x y = isSub x y && isSub y x -- | returns x if it's elements are all in y, otherwise y minLs :: Eq a => [a] -> [a] -> [a] minLs x y | x `isSub` y = x | otherwise = y -- | partitions a list according to an equivalence relation partitionBy :: (a -> a -> Bool) -> [a] -> [[a]] partitionBy _ [] = [] partitionBy eq ls = x:(partitionBy eq y) where (x,y) = partition ((head ls) `eq`) ls -- | sort a list of (reduced) rules according to antecedent length, shortest antecedents first sortByValNum :: [Rule] -> [Rule] sortByValNum (x:[]) = [x] -- only one rule in list (usually equivalence list) sortByValNum rls = sortBy lengthcmp rls where lengthcmp (x,_) (y,_) | (length x) > (length y) = GT | (length x) == (length y) = EQ | otherwise = LT -- | sort a list of SORTED equivalence classes. Then head is always shortest. sortListEqs :: [[Rule]] -> [[Rule]] sortListEqs equivls = sortBy eqvcmp equivls where eqvcmp x y | (myln x) > (myln y) = GT | (myln x) == (myln y) = EQ | otherwise = LT myln = length . fst . head