module Huzzy.Base.Systems where import Huzzy.Base.Sets newtype FRule a => RuleBase a = RB [a] class Fuzzy a => FRule a where type Antecedent a (=*>) :: Antecedent a -> a -> a (=|>) :: Antecedent a -> a -> a weight :: a -> Double -> a instance FRule Double where type Antecedent Double = Double (=*>) a b = a * b (=|>) a b = a `min` b weight a b = a * b instance FRule b => FRule (a -> b) where type Antecedent (a -> b) = Antecedent b (=*>) a b = \x -> a =*> b x (=|>) a b = \x -> a =|> b x weight a b = \x -> a x `weight` b instance FRule (MF a) where type Antecedent (MF a) = Double (=*>) a (MF f) = MF (\x -> a =*> f x) (=|>) a (MF f) = MF (\x -> a =|> f x) weight (MF f) b = MF (\x -> f x `weight` b) class FRule a => Defuzzifier a where type Result a centroid :: a -> Result a aggregate :: FRule a => RuleBase a -> (a -> a -> a) -> a aggregate (RB rules) agg = foldr1 agg rules