lfst-1.0.0: L-Fuzzy Set Theory implementation in Haskell

Safe HaskellNone
LanguageHaskell2010

FuzzySet

Description

If X is a collection of objects denoted generically by x, then a fuzzy set F(A) in X is a set of ordered pairs. Each of them consists of an element x and a membership function which maps x to the membership space M.

Synopsis

Documentation

newtype FuzzySet m i Source

FuzzySet type definition

Constructors

FS (Map i m) 

Instances

(BoundedLattice m, Eq m) => ExoFunctor (FuzzySet m) i Source

Defines a functor for the FuzzySet type which allows to implement the Extension principle prop> fmap (^2) (fromList [(-1, Godel 0.5), (0, Godel 0.8), (1, Godel 1.0), (2, Godel 0.4)]) == fromList [(0, Godel 0.8), (1, Godel 1.0), (4, Godel 0.4)] prop> fmap (^2) (fromList [(-1, Goguen 0.5), (0, Goguen 0.8), (1, Goguen 1.0), (2, Goguen 0.4)]) == fromList [(0, Goguen 0.8), (1, Goguen 1.0), (4, Goguen 0.4)] prop> fmap (^2) (fromList [(-1, Lukas 0.5), (0, Lukas 0.8), (1, Lukas 1.0), (2, Lukas 0.4)]) == fromList [(0, Lukas 0.8), (1, Lukas 1.0), (4, Lukas 0.4)]

(Eq m, Eq i) => Eq (FuzzySet m i) Source 
(Ord m, Ord i) => Ord (FuzzySet m i) Source 
(Ord i, BoundedLattice m, Show i, Show m) => Show (FuzzySet m i) Source 
type SubCatConstraintI (FuzzySet m) i = Ord i Source 
type SubCatConstraintJ (FuzzySet m) j = Ord j Source 

preimage :: (Eq i, Eq j) => (i -> j) -> j -> [i] -> [i] Source

Returns the preimage of the given set in input prop> preimage (^2) 25 [1..5] == [5]

empty :: (Ord i, BoundedLattice m) => FuzzySet m i Source

Returns an empty fuzzy set

add :: (Ord i, Eq m, BoundedLattice m) => FuzzySet m i -> (i, m) -> FuzzySet m i Source

Inserts a new pair (i, m) to the fuzzy set prop> add godel1 (i, L.bottom) == godel1 prop> add goguen1 (i, L.bottom) == goguen1 prop> add lukas1 (i, L.bottom) == lukas1

support :: (Ord i, BoundedLattice m) => FuzzySet m i -> [i] Source

Returns the fuzzy set's support prop> support godel1 == [1, 2] prop> support goguen1 == [1, 2] prop> support lukas1 == [1, 2]

mu :: (Ord i, BoundedLattice m) => FuzzySet m i -> i -> m Source

Returns the element i's membership if i belongs to the support returns its membership, otherwise returns bottom lattice value prop> mu godel1 1 == Godel 0.2 prop> mu godel1 10 == L.bottom prop> mu goguen1 1 == Goguen 0.2 prop> mu goguen1 10 == L.bottom prop> mu lukas1 1 == Lukas 0.2 prop> mu lukas1 10 == L.bottom

core :: (Ord i, Eq m, BoundedLattice m) => FuzzySet m i -> [i] Source

Returns the crisp subset of given fuzzy set consisting of all elements with membership equals to one prop> core (fromList [(-1, Godel 0.5), (0, Godel 0.8), (1, Godel 1.0), (2, Godel 0.4)]) == [1] prop> core (fromList [(-1, Goguen 0.5), (0, Goguen 0.8), (1, Goguen 1.0), (2, Goguen 0.4)]) == [1] prop> core (fromList [(-1, Lukas 0.5), (0, Lukas 0.8), (1, Lukas 1.0), (2, Lukas 0.4)]) == [1]

alphaCut :: (Ord i, Ord m, BoundedLattice m) => FuzzySet m i -> m -> [i] Source

Returns those elements whose memberships are greater or equal than the given alpha prop> alphaCut (fromList [(-1, Godel 0.5), (0, Godel 0.8), (1, Godel 1.0), (2, Godel 0.4)]) (Godel 0.5) == [-1, 0, 1] prop> alphaCut (fromList [(-1, Goguen 0.5), (0, Goguen 0.8), (1, Goguen 1.0), (2, Goguen 0.4)]) (Goguen 0.5) == [-1, 0, 1] prop> alphaCut (fromList [(-1, Lukas 0.5), (0, Lukas 0.8), (1, Lukas 1.0), (2, Lukas 0.4)]) (Lukas 0.5) == [-1, 0, 1]

fromList :: (Ord i, Eq m, BoundedLattice m) => [(i, m)] -> FuzzySet m i Source

Builds a fuzzy set from a list of pairs prop> fromList [(1, Godel 0.2)] == add empty (1, Godel 0.2) prop> fromList [(1, Goguen 0.2)] == add empty (1, Goguen 0.2) prop> fromList [(1, Lukas 0.2)] == add empty (1, Lukas 0.2)

map1 :: (Ord i, Eq m, BoundedLattice m) => (m -> m) -> FuzzySet m i -> FuzzySet m i Source

Applies a unary function to the specified fuzzy set prop> map1 (*2) godel1 == fromList [(1, Godel 0.4), (2, Godel 1.0)] prop> map1 (*2) goguen1 == fromList [(1, Goguen 0.4), (2, Goguen 1.0)] prop> map1 (*2) lukas1 == fromList [(1, Lukas 0.4), (2, Lukas 1.0)]

map2 :: (Ord i, Eq m, BoundedLattice m) => (m -> m -> m) -> FuzzySet m i -> FuzzySet m i -> FuzzySet m i Source

Applies a binary function to the two specified fuzzy sets prop> map2 (+) godel1 godel2 == fromList [(1, Godel 0.2), (2, Godel 0.7), (3, Godel 0.2)] prop> map2 (+) goguen1 goguen2 == fromList [(1, Goguen 0.2), (2, Goguen 0.7), (3, Goguen 0.2)] prop> map2 (+) lukas1 lukas2 == fromList [(1, Lukas 0.2), (2, Lukas 0.7), (3, Lukas 0.2)]

union :: (Ord i, Eq m, BoundedLattice m) => FuzzySet m i -> FuzzySet m i -> FuzzySet m i Source

Returns the union between the two specified fuzzy sets prop> union godel1 godel2 == fromList [(1, Godel 0.2), (2, Godel 0.5), (3, Godel 0.2)] prop> union goguen1 goguen2 == fromList [(1, Goguen 0.2), (2, Goguen 0.6), (3, Goguen 0.2)] prop> union lukas1 lukas2 == fromList [(1, Lukas 0.2), (2, Lukas 0.7), (3, Lukas 0.2)]

intersection :: (Ord i, Eq m, BoundedLattice m) => FuzzySet m i -> FuzzySet m i -> FuzzySet m i Source

Returns the intersection between the two specified fuzzy sets prop> intersection godel1 godel2 == fromList [(2, Godel 0.2)] prop> intersection goguen1 goguen2 == fromList [(2, Goguen 0.1)] prop> intersection lukas1 lukas2 == empty

complement :: (Ord i, Num m, Eq m, BoundedLattice m) => FuzzySet m i -> FuzzySet m i Source

Returns the complement of the specified fuzzy set prop> complement godel1 == fromList [(1, Godel 0.8), (2, Godel 0.5)] prop> complement goguen1 == fromList [(1, Goguen 0.8), (2, Goguen 0.5)] prop> complement lukas1 == fromList [(1, Lukas 0.8), (2, Lukas 0.5)]

algebraicSum :: (Ord i, Eq m, Num m, BoundedLattice m) => FuzzySet m i -> FuzzySet m i -> FuzzySet m i Source

Returns the algebraic sum between the two specified fuzzy sets prop> algebraicSum godel1 godel2 == fromList [(1, Godel 0.2), (2, Godel 0.7), (3, Godel 0.2)] prop> algebraicSum goguen1 goguen2 == fromList [(1, Goguen 0.2), (2, Goguen 0.7), (3, Goguen 0.2)] prop> algebraicSum lukas1 lukas2 == fromList [(1, Lukas 0.2), (2, Lukas 0.7), (3, Lukas 0.2)]

algebraicProduct :: (Ord i, Eq m, Num m, BoundedLattice m) => FuzzySet m i -> FuzzySet m i -> FuzzySet m i Source

Returns the algebraic product between the two specified fuzzy sets prop> algebraicProduct godel1 godel2 == fromList [(2, Godel 0.1)] prop> algebraicProduct goguen1 goguen2 == fromList [(2, Goguen 0.1)] prop> algebraicProduct lukas1 lukas2 == fromList [(2, Lukas 0.1)]

generalizedProduct :: (Ord i, Ord j, Eq m, BoundedLattice m) => (m -> m -> m) -> FuzzySet m i -> FuzzySet m j -> FuzzySet m (i, j) Source

Returns the cartesian product between two fuzzy sets using the specified function prop> generalizedProduct (+) godel1 godel2 == fromList [((1, 2), Godel 0.4), ((1, 3), Godel 0.4), ((2, 2), Godel 0.7), ((2, 3), Godel 0.7)] prop> generalizedProduct (+) goguen1 goguen2 == fromList [((1, 2), Goguen 0.4), ((1, 3), Goguen 0.4), ((2, 2), Goguen 0.7), ((2, 3), Goguen 0.7)] prop> generalizedProduct (+) lukas1 lukas2 == fromList [((1, 2), Lukas 0.4), ((1, 3), Lukas 0.4), ((2, 2), Lukas 0.7), ((2, 3), Lukas 0.7)]

class ExoFunctor f i where Source

Defines a mapping between sub-categories preserving morphisms

Associated Types

type SubCatConstraintI f i :: Constraint Source

type SubCatConstraintJ f j :: Constraint Source

Methods

fmap :: (SubCatConstraintI f i, SubCatConstraintJ f j) => (i -> j) -> f i -> f j Source

Instances

(BoundedLattice m, Eq m) => ExoFunctor (FuzzySet m) i Source

Defines a functor for the FuzzySet type which allows to implement the Extension principle prop> fmap (^2) (fromList [(-1, Godel 0.5), (0, Godel 0.8), (1, Godel 1.0), (2, Godel 0.4)]) == fromList [(0, Godel 0.8), (1, Godel 1.0), (4, Godel 0.4)] prop> fmap (^2) (fromList [(-1, Goguen 0.5), (0, Goguen 0.8), (1, Goguen 1.0), (2, Goguen 0.4)]) == fromList [(0, Goguen 0.8), (1, Goguen 1.0), (4, Goguen 0.4)] prop> fmap (^2) (fromList [(-1, Lukas 0.5), (0, Lukas 0.8), (1, Lukas 1.0), (2, Lukas 0.4)]) == fromList [(0, Lukas 0.8), (1, Lukas 1.0), (4, Lukas 0.4)]