Code might help :P

import qualified Data.Set as Set
import Data.Set (Set)
import Data.List (partition,delete)
import Data.Maybe (isJust,fromJust)

-- A snippet for working out minimal complete definitions.

num =
	[
	("plus",Nothing),
	("times",Nothing),
	("abs",Nothing),
	("minus",Just ["negate"]),
	("negate",Just ["minus"]),
	("signum",Nothing),
	("fromInteger",Nothing)
	]

ord = 
	[
	("compare",Just ["<="]),
	("<",Just ["compare"]),
	("<=",Just ["compare"]),
	(">",Just ["compare"]),
	(">=",Just ["compare"]),
	("max",Just ["<="]),
	("min",Just ["<="])
	]

-- a nice example from a comment in GHC's GHC.Classes
wrongOrd = 
	[
	("compare",Just ["<"]),
	("<",Just ["compare"]),
	("<=",Just ["compare"]),
	(">",Just ["compare"]),
	(">=",Just ["compare"]),
	("max",Just ["<="]),
	("min",Just ["<="])
	]

-- given a list of:
-- (thing, depends upon)
-- * depends upon can be Nothing if no implementation is defined (i.e.
--   you *always* have to implement it
-- * depends upon can be Just [] if the implementation depends on nothing else
-- * otherwise the depends upon is Just [a] where it lists the things it depends upon
--
-- returns:
-- (a list of what you must always implement, and lists of minimal dependencies)
-- doDependencies :: [(a, Maybe [a])] -> (a,[[a]])
doDependencies xs = (mustImplementNames,Set.toList . Set.fromList $ map (Set.toList . Set.fromList) $ doDependencies' maybeImplement'')
	where
	(maybeImplement,mustImplement) = partition (isJust . snd) xs
	mustImplementNames = map fst mustImplement
	maybeImplement' = map (\(x,y)->(x,fromJust y)) maybeImplement
	maybeImplement'' = foldr eliminateDepends maybeImplement' mustImplementNames

eliminateDepends :: (Ord a, Eq a) => a -> [(a,[a])] -> [(a,[a])]
eliminateDepends x xs
	| null removeUs = stillHere
	| otherwise = foldr eliminateDepends stillHere (map fst removeUs)
	where (removeUs,stillHere) = partition (null . snd) $ map (\(it,depends) -> (it, delete x depends)) xs

doDependencies' :: (Ord a, Eq a) => [(a,[a])] -> [[a]]
doDependencies' eqs = dd eqs []
	where 
	dd [] solution = [solution]
	dd eqs solution =
		[concat $ dd (eliminateDepends dependency eqs) (dependency:solution)
		|dependency<-rhs]
		where
			rhs = concatMap snd eqs

Attachment: signature.asc
Description: This is a digitally signed message part

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to