module Huzzy.TypeOne.Sets where import Data.List(sortBy, nub, elemIndex) import Data.Maybe(fromJust) import Huzzy.Base.Sets data T1Set a = T1S { mf :: MF a , dom :: [a] } instance Fuzzy (T1Set a) where a ?&& b = a { mf = (mf a) ?&& (mf b)} a ?|| b = a { mf = (mf a) ?|| (mf b)} fnot a = a { mf = fnot (mf a)} instance FSet (T1Set a) where type Value (T1Set a) = a type Support (T1Set a) = [a] type Returned (T1Set a) = Double support s = filter (\x -> (x `is` s) > 0) d where d = dom s hedge p s = s {mf = MF (\x -> mf' x)} where (MF f) = mf s mf' x | f x == 0 = 0 | otherwise = f x ** p x `is` s = f x where (MF f) = mf s {- instance FSet (T1Set a) a a Double where support s = filter (\x -> (x `is` s) > 0) d where d = dom s hedge p s = s {mf = MF (\x -> mf' x)} where (MF f) = mf s mf' x | f x == 0 = 0 | otherwise = f x ** p x `is` s = f x where (MF f) = mf s -} -- Smart Constructors -- continuous :: a -> a -> a -> MF a -> T1Set a contT1 :: (Num a, Enum a) => a -> a -> a -> MF a -> T1Set a contT1 minB maxB res (MF mf) = case check of True -> error "Truth values must be in the range [0..1]" False -> T1S { mf = MF mf , dom = domain } where domain = [minB, minB+res .. maxB] check = any (\x -> x > 1 || x < 0) (map mf domain) discT1 :: [a] -> MF a -> T1Set a discT1 dom (MF mf) = case check of True -> error "Truth values must be in the range [0..1]" False -> T1S { mf = MF mf , dom = dom } where check = any (\x -> x > 1 || x < 0) (map mf dom) trustedCont :: (Num a, Enum a) => a -> a -> a -> MF a -> T1Set a trustedCont minB maxB res mf = T1S { mf = mf , dom = [minB, minB+res .. maxB] } trustedDisc :: [a] -> MF a -> T1Set a trustedDisc dom mf = T1S { mf = mf , dom = dom } unsafeMkT1 :: [a] -> MF a -> T1Set a unsafeMkT1 = trustedDisc alpha :: Double -> T1Set a -> [a] alpha d s = filter (\x -> f x >= d) (dom s) where (MF f) = mf s findCuts :: Ord a => T1Set a -> Double -> (a, a) findCuts s d = (l, r) where as = alpha d s l = maximum as li = fromJust $ elemIndex l as r = maximum (snd $ splitAt li as)