24% The various fuzzy algebras ae implemented as modules that impose
   25% CHR constraints on tnorm/2
   26% This module implements lukasiewicz algebra
   27
   28
   29:- module( alg_lukasiewicz, [fmt_range/2,
   30			     is_fuzzy_degree/1,
   31			     less_fuzzy/2, equally_fuzzy/2,
   32			     check_less_fuzzy/2,
   33			     check_equally_fuzzy/2,
   34			     check_clause_degree/2,
   35			     get_max/2,
   36			     tnorm/3, tnorm/4] ).   37:- use_module( library(clpr) ).   38
   39% If In happens to be instantiated and not a variable,
   40% an instantiation_error/2 is thrown. In such a case,
   41% abstract restrictions are meaningless
   42
   43fmt_range( In, Out ) :-
   44	length( In, 1 ),
   45	!,
   46	catch( dump(In,[d],Out),
   47	       instantiation_error(dump([D],[d],_),1),
   48	       Out=[(d=D)] ).
   49fmt_range( In, Out ) :-
   50	length( In, 2 ),
   51	!,
   52	catch( dump( In, [x,d], Out ),
   53	       instantiation_error(dump([X,D],[x,d],_),1),
   54	       Out=[(x=X),(d=D)] ).
   55fmt_range( _, [] ).
   56
   57is_fuzzy_degree( Deg ) :-
   58	{ Deg >= 0.0 },
   59	{ Deg =< 1.0 }.
   63/*
   64less_fuzzy( x, Deg2, X, Deg2 ) :- !,
   65	{ X >= Deg2 }.
   66less_fuzzy( Deg1, x, Deg1, X ) :- !,
   67	{ Deg1 >= X }.
   68*/
   69less_fuzzy( Deg1, Deg2 ) :-
   70	{ Deg1 >= Deg2 }.
   71
   72check_less_fuzzy( Deg1, Deg2 ) :-
   73	entailed( Deg1 >= Deg2 ).
   74
   75check_clause_degree( [Deg], Value ) :-
   76	!,
   77	entailed( Deg =:= Value ).
   78check_clause_degree( [_,Deg], Value ) :-
   79	!,
   80	entailed( Deg =:= Value ).
   81
   82equally_fuzzy( Deg1, Deg2 ) :-
   83	{ Deg1 =:= Deg2 }.
   84
   85check_equally_fuzzy( Deg1, Deg2 ) :-
   86	entailed( Deg1 =:= Deg2 ).
   87
   88get_max( Deg, Max ) :-
   89	sup( Deg, Max ).
   90
   91tnorm( complement, X, Res ) :-
   92	{ Res =:= 1 - X }.
   93
   94tnorm( conjunction, X, Y, Res ) :-
   95	{ Res =:= max(0.0, X + Y - 1.0) }.
   96
   97tnorm( disjunction, X, Y, Res ) :-
   98	{ Res =:= min(1.0, X + Y) }.
   99
  100tnorm( implication, X, Y, Res ) :-
  101	{ Res =:= min(1.0, 1.0 - X + Y) }.
  102
  103tnorm( weakconjunction, X, Y, Res) :-
  104	{ Res =:= min(X, Y) }.
  105
  106tnorm( weakdisjunction, X, Y, Res) :-
  107	{ Res =:= max(X, Y) }.
  108
  109
  110% modus ponens: ( (H <- B) and B ) -> H
  111% fuzzy degree of        X and Y   -> R
  112% is calculated according to algebra above,
  113% under the requirement that the implication holds at degree 1.0.
  114
  115tnorm( mp, X, Y, Res ) :-
  116	{
  117	 X + Y >= 1.0,
  118	 Res =:= X + Y - 1
  119	}