I have the following code:
{-# LANGUAGE NoImplicitPrelude, OverloadedStrings, TypeFamilies #-}
module AI.Analysis.Rules where
import ClassyPrelude
-- Our set of rules
data RuleSet a = RuleSet [Rule a] [Rule a]
deriving (Eq)
mkRuleSet :: (Ord a) => [Rule a] -> RuleSet a
mkRuleSet rules = uncurry RuleSet (partition isStandard uniques)
where uniques = ordNub rules
isStandard x = case x of
Standard _ _ -> True
LastResort _ -> False
instance (Show a) => Show (RuleSet a) where
show (RuleSet s l) = unlines [toLines s, "----", toLines l]
where toLines = unlines . fmap show
instance (Ord a) => Monoid (RuleSet a) where
mempty = RuleSet [] []
mappend (RuleSet s1 l1) (RuleSet s2 l2) = RuleSet (ordNub (s1 ++ s2)) (ordNub (l1 ++ l2))
instance (Ord a) => Semigroup (RuleSet a) where
(<>) = mappend
type instance Element (RuleSet a) = (Rule a)
instance MonoFoldable (RuleSet a) --this is unhappy
-- A rule in our system
-- For now, we assume rules *individually* are always internally-consistent
data Rule a = Standard [a] a | LastResort a
deriving (Eq)
mkRule :: (Eq a, Ord a) => [a] -> a -> Rule a
mkRule as c = case as of
[] -> LastResort c
_ -> Standard ((sort . ordNub) as) c
-- Last-resort rules and standard rules cannot be compared for consistency
mutuallyConsistent :: (Eq a) => Rule a -> Rule a -> Maybe Bool
mutuallyConsistent (LastResort c1) (LastResort c2) = Just (c1 == c2)
mutuallyConsistent (Standard as1 c1) (Standard as2 c2) = Just ((as1 /= as2) || (c1 == c2))
mutuallyConsistent _ _ = Nothing
instance (Show a) => Show (Rule a) where
show x = case x of
Standard as c -> formatAnd as ++ " -> " ++ show c
LastResort c -> "-> " ++ show c
where formatAnd = unwords . intersperse "^" . map show . otoList
-- LastResort rules are always ordered smaller than standard ones
instance (Ord a) => Ord (Rule a) where
(<=) (LastResort _) (Standard _ _) = True
(<=) (Standard _ _) (LastResort _) = False
(<=) (LastResort c1) (LastResort c2) = c1 <= c2
(<=) (Standard as1 c1) (Standard as2 c2) = (as1 <= as2) || (c1 <= c2)
However, I get the following error from the compiler, whose meaning I am having trouble understanding:
/home/koz/documents/uni/research/summer-research-2015/clinical/rules-analysis/src/AI/Analysis/Rules.hs:47:10:
Couldn't match type ‘a’ with ‘Rule a’
‘a’ is a rigid type variable bound by
the instance declaration
at /home/koz/documents/uni/research/summer-research-2015/clinical/rules-analysis/src/AI/Analysis/Rules.hs:47:10
Expected type: Element (RuleSet a)
Actual type: a
Relevant bindings include
ofoldMap :: (Element (RuleSet a) -> m) -> RuleSet a -> m
(bound at /home/koz/documents/uni/research/summer-research-2015/clinical/rules-analysis/src/AI/Analysis/Rules.hs:47:10)
In the expression:
mono-traversable-0.10.0.1:Data.MonoTraversable.$gdmofoldMap
In an equation for ‘ofoldMap’:
ofoldMap
= mono-traversable-0.10.0.1:Data.MonoTraversable.$gdmofoldMap
In the instance declaration for ‘MonoFoldable (RuleSet a)’
Near as I can tell, my thinking seems to make sense - after all, a RuleSet
is just a container for Rule
s, which should allow for foldability, but the error message in question doesn't make any sense to me. Could someone please clarify what I failed to grasp here?
Have you tried actually implementing the class? It appears there is some oddity with the default definitions and your type family. If you define at least the below then the file type checks:
instance MonoFoldable (RuleSet a) where --this is unhappy
ofoldl1Ex' = undefined
ofoldr1Ex = undefined
ofoldl' = undefined
ofoldr = undefined
ofoldMap = undefined
EDIT: The classy prelude, which I now know I will never use, has default implementations and type signatures that include the constraints t a ~ mono, a ~ Element (t a)
. Working carefully since I had to think twice here. t a ~ RuleSet a0
so t == RuleSet
and a == a0
. Then a ~ Element (RuleSet a)
, which is your exact error in the message, would suggest a ~ Rule a
and that just isn't right.