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

Safe HaskellNone
LanguageHaskell2010

Algebra.LFST.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

(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

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

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

Returns the fuzzy set's support

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

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

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

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

Builds a fuzzy set from a list of pairs

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

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

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

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

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

Returns the complement of the specified fuzzy set

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

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

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

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