Re: [Haskell-cafe] Minimal complete definitions

2008-12-15 Thread George Pollard
Sorry about the triple-post, but I forgot to note it only goes to one
'depth' of OR; in reality the MCD for wrongOrd should be (< OR ((<=) AND
(compare OR <)) OR compare). This requires a slightly more complicated
type than [[a]] :)


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


Re: [Haskell-cafe] Minimal complete definitions

2008-12-15 Thread George Pollard
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


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


[Haskell-cafe] Minimal complete definitions

2008-12-15 Thread George Pollard
Good afternoon Café,

I've written a little bit of code to calculate minimal complete
definitions for a class given which of its functions use which other
functions.

As an example:

doDependencies ord =
([],[["<="],["compare"]])

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

The first part of the pair is those functions which must *always* be
implemented, the second part is a list of possible minimal complete
definitions available for the provided list.

This can help catch mistakes; a comment in the GHC source for
GHC.Classes notes that compare must be implemented using (<=) and not
(<) in order to give the minimal complete definition (<= OR compare). If
we use the incorrect (<) then my code calculates the MCD as:

doDependencies wrongOrd =
([],[["<"],["<","<=","compare"],["compare"]])

That is, the MCD is (< OR (< AND <= AND compare) OR compare).

Now I have two questions:

1) Is my code correct? ;)
2) Could this be incorporated into GHC in order to detect when someone
hasn't provided a sufficient definition for a class? As an example, it
could detect this:

> ~$ cat test2.hs
> data Die d = Die d
> instance Eq (Die d) where
> main = do
> let i = Die "stack overflow"
> print (i == i)
> ~$ ghc -Wall test2.hs --make
> ~$ ./test2
> Stack space overflow: current size 8388608 bytes.
> Use `+RTS -Ksize' to increase it.

Given the following:

doDependencies [("==", Just ["/="]),("/=", Just ["=="])] =
([],[["/="],["=="]])

GHC could warn that either (==) or (/=) must be implemented.

Thanks,
- George


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