AI-ExpertSystem-Advanced

 view release on metacpan or  search on metacpan

META.yml  view on Meta::CPAN

---
abstract: 'Expert System with backward, forward and mixed algorithms'
author:
  - 'Pablo Fischer (pablo@pablo.com.mx).'
build_requires:
  ExtUtils::MakeMaker: 6.42
configure_requires:
  ExtUtils::MakeMaker: 6.42
distribution_type: module
generated_by: 'Module::Install version 0.91'
license: perl
meta-spec:
  url: http://module-build.sourceforge.net/META-spec-v1.4.html
  version: 1.4
name: AI-ExpertSystem-Advanced
no_index:
  directory:
    - examples
    - inc
requires:
  Class::Factory: 1.05
  List::MoreUtils: 0.22
  Moose: 0.87
  YAML::Syck: 1.07
resources:
  license: http://dev.perl.org/licenses/
  repository: http://github.com/pfischer/AI-ExpertSystem-Advanced
version: 0.03

Makefile.PL  view on Meta::CPAN

use inc::Module::Install;

# Define metadata
name        'AI-ExpertSystem-Advanced';
all_from    'lib/AI/ExpertSystem/Advanced.pm';

# Specific dependencies
requires    'Moose'             => '0.87';
requires    'YAML::Syck'        => '1.07';
requires    'List::MoreUtils'   => '0.22';
requires    'Class::Factory'    => '1.05';

no_index directory => 'examples';

repository 'http://github.com/pfischer/AI-ExpertSystem-Advanced';

WriteAll;



README  view on Meta::CPAN

NAME
    AI::ExpertSystem::Advanced - Expert System with backward, forward and
    mixed algorithms

DESCRIPTION
    Inspired in AI::ExpertSystem::Simple but with additional features:

    *   Uses backward, forward and mixed algorithms.

    *   Offers different views, so user can interact with the expert system
        via a terminal or with a friendly user interface.

    *   The knowledge database can be stored in any format such as YAML, XML
        or databases. You just need to choose what driver to use and you are
        done.

README  view on Meta::CPAN


Constants
    * FACT_SIGN_NEGATIVE
        Used when a fact is negative, aka, a fact doesn't happen.

    * FACT_SIGN_POSITIVE
        Used for those facts that happen.

    * FACT_SIGN_UNSURE
        Used when there's no straight answer of a fact, eg, we don't know if
        an answer will change the result.

Methods
  shoot($rule, $algorithm)
    Shoots the given rule. It will do the following verifications:

    *   Each of the facts (causes) will be compared against the
        initial_facts_dict, inference_facts and asked_facts (in this order).

    *   If any initial, inference or asked fact matches with a cause but
        it's negative then all of its goals (usually only one by rule) will

README  view on Meta::CPAN


  copy_to_inference_facts($facts, $sign, $algorithm, $rule)
    Copies the given $facts (a dictionary, usually goal(s) of a rule) to the
    inference_facts dictionary. All the given goals will be copied with the
    given $sign.

    Additionally it will add the given $algorithm and $rule to the inference
    facts. So later we can know how we got to a certain inference fact.

  compare_causes_with_facts($rule)
    Compares the causes of the given $rule with:

    *   Initial facts

    *   Inference facts

    *   Asked facts

    It will be couting the matches of all of the above dictionaries, so for
    example if we have four causes, two make match with initial facts, other
    with inference and the remaining one with the asked facts, then it will

README  view on Meta::CPAN

        $ai->forward();
        $ai->summary();

    The forward chaining algorithm is one of the main methods used in Expert
    Systems. It starts with a set of variables (known as initial facts) and
    reads the available rules.

    It will be reading rule by rule and for each one it will compare its
    causes with the initial, inference and asked facts. If all of these
    causes are in the facts then the rule will be shoot and all of its goals
    will be copied/converted to inference facts and will restart reading
    from the first rule.

  backward()
        use AI::ExpertSystem::Advanced;
        use AI::ExpertSystem::Advanced::KnowledgeDB::Factory;

        my $yaml_kdb = AI::ExpertSystem::Advanced::KnowledgeDB::Factory->new('yaml',
            {
                filename => 'examples/knowledge_db_one.yaml'
                });

README  view on Meta::CPAN

        marked (added) to the list of visited rules (visited_rules) and also
        all of its causes will be added to the top of the
        goals_to_check_dict and it will start reading again all the goals.

        If there's the case where the goal doesn't exist as a goal in the
        rules then it will ask the user (via ask_about()) for the existence
        of it. If user is not sure about it then the algorithm ends.

  mixed()
    As its name says, it's a mix of forward() and backward() algorithms, it
    requires to have at least one initial fact.

    The first thing it does is to run the forward() algorithm (hence the
    need of at least one initial fact). If the algorithm fails then the
    mixed algorithm also ends unsuccessfully.

    Once the first *run* of forward() algorithm happens it starts looking
    for any positive inference fact, if only one is found then this ends the
    algorithm with the assumption it knows what's happening.

    In case no positive inference fact is found then it will start reading

README  view on Meta::CPAN

    something to do with our first initial facts).

    Once all the rules are read then it verifies if there are intuitive
    facts, if no facts are found then it ends with the intuition, otherwise
    it will run the backward() algorithm for each one of these facts (eg,
    each fact will be converted to a goal). After each *run* of the
    backward() algorithm it will verify for any positive inference fact, if
    just one is found then the algorithm ends.

    At the end (if there are still no positive inference facts) it will run
    the forward() algorithm and restart (by looking again for any positive
    inference fact).

    A good example to understand how this algorithm is useful is: imagine
    you are a doctor and know some of the symptoms of a patient. Probably
    with the first symptoms you have you can get to a positive conclusion
    (eg that a patient has *X* disease). However in case there's still no
    clue, then a set of questions (done by the call of backward()) of
    symptons related to the initial symptoms will be asked to the user. For
    example, we know that that the patient has a headache but that doesn't
    give us any positive answer, what if the patient has flu or another
    disease? Then a set of these *related* symptons will be asked to the
    user.

  summary($return)
    The main purpose of any expert system is the ability to explain: what is
    happening, how it got to a result, what assumption(s) it required to
    make, the fatcs that were excluded and the ones that were used.

    This method will use the viewer (or return the result) in YAML format of
    all the rules that were shot. It will explain how it got to each one of
    the causes so a better explanation can be done by the viewer.

    If $return is defined (eg, it got any parameter) then the result wont be
    passed to the viewer, instead it will be returned as a string.

SEE ALSO
    Take a look AI::ExpertSystem::Simple too.

AUTHOR
    Pablo Fischer (pablo@pablo.com.mx).

COPYRIGHT
    Copyright (C) 2010 by Pablo Fischer.

inc/Module/Install.pm  view on Meta::CPAN






# Whether or not inc::Module::Install is actually loaded, the
# $INC{inc/Module/Install.pm} is what will still get set as long as
# the caller loaded module this in the documented manner.
# If not set, the caller may NOT have loaded the bundled version, and thus
# they may not have a MI version that works with the Makefile.PL. This would
# result in false errors or unexpected behaviour. And we don't want that.
my $file = join( '/', 'inc', split /::/, __PACKAGE__ ) . '.pm';
unless ( $INC{$file} ) { die <<"END_DIE" }

Please invoke ${\__PACKAGE__} with:

	use inc::${\__PACKAGE__};

not:

	use ${\__PACKAGE__};

END_DIE





# If the script that is loading Module::Install is from the future,
# then make will detect this and cause it to re-run over and over
# again. This is bad. Rather than taking action to touch it (which
# is unreliable on some platforms and requires write permissions)
# for now we should catch this and refuse to run.
if ( -f $0 ) {
	my $s = (stat($0))[9];

	# If the modification time is only slightly in the future,
	# sleep briefly to remove the problem.
	my $a = $s - time;
	if ( $a > 0 and $a < 5 ) { sleep 5 }

	# Too far in the future, throw an error.

inc/Module/Install.pm  view on Meta::CPAN

	File::Find::find( sub {
		my $file = $File::Find::name;
		return unless $file =~ m!^\Q$path\E/(.+)\.pm\Z!is;
		my $subpath = $1;
		return if lc($subpath) eq lc($self->{dispatch});

		$file = "$self->{path}/$subpath.pm";
		my $pkg = "$self->{name}::$subpath";
		$pkg =~ s!/!::!g;

		# If we have a mixed-case package name, assume case has been preserved
		# correctly.  Otherwise, root through the file to locate the case-preserved
		# version of the package name.
		if ( $subpath eq lc($subpath) || $subpath eq uc($subpath) ) {
			my $content = Module::Install::_read($subpath . '.pm');
			my $in_pod  = 0;
			foreach ( split //, $content ) {
				$in_pod = 1 if /^=\w/;
				$in_pod = 0 if /^=cut/;
				next if ($in_pod || /^=cut/);  # skip pod text
				next if /^\s*#/;               # and comments
				if ( m/^\s*package\s+($pkg)\s*;/i ) {

inc/Module/Install/Fetch.pm  view on Meta::CPAN

        $args{url} = $args{ftp_url}
            or (warn("LWP support unavailable!\n"), return);
        ($scheme, $host, $path, $file) =
            $args{url} =~ m|^(\w+)://([^/]+)(.+)/(.+)| or return;
    }

    $|++;
    print "Fetching '$file' from $host... ";

    unless (eval { require Socket; Socket::inet_aton($host) }) {
        warn "'$host' resolve failed!\n";
        return;
    }

    return unless $scheme eq 'ftp' or $scheme eq 'http';

    require Cwd;
    my $dir = Cwd::getcwd();
    chdir $args{local_dir} or return if exists $args{local_dir};

    if (eval { require LWP::Simple; 1 }) {

inc/Module/Install/Makefile.pm  view on Meta::CPAN

	}

	# Make sure we have a new enough MakeMaker
	require ExtUtils::MakeMaker;

	if ( $perl_version and $self->_cmp($perl_version, '5.006') >= 0 ) {
		# MakeMaker can complain about module versions that include
		# an underscore, even though its own version may contain one!
		# Hence the funny regexp to get rid of it.  See RT #35800
		# for details.
		$self->build_requires( 'ExtUtils::MakeMaker' => $ExtUtils::MakeMaker::VERSION =~ /^(\d+\.\d+)/ );
		$self->configure_requires( 'ExtUtils::MakeMaker' => $ExtUtils::MakeMaker::VERSION =~ /^(\d+\.\d+)/ );
	} else {
		# Allow legacy-compatibility with 5.005 by depending on the
		# most recent EU:MM that supported 5.005.
		$self->build_requires( 'ExtUtils::MakeMaker' => 6.42 );
		$self->configure_requires( 'ExtUtils::MakeMaker' => 6.42 );
	}

	# Generate the MakeMaker params
	my $args = $self->makemaker_args;
	$args->{DISTNAME} = $self->name;
	$args->{NAME}     = $self->module_name || $self->name;
	$args->{VERSION}  = $self->version;
	$args->{NAME}     =~ s/-/::/g;
	if ( $self->tests ) {
		$args->{test} = { TESTS => $self->tests };

inc/Module/Install/Makefile.pm  view on Meta::CPAN

	if ( eval($ExtUtils::MakeMaker::VERSION) >= 6.10 ) {
		$args->{NO_META} = 1;
	}
	if ( eval($ExtUtils::MakeMaker::VERSION) > 6.17 and $self->sign ) {
		$args->{SIGN} = 1;
	}
	unless ( $self->is_admin ) {
		delete $args->{SIGN};
	}

	# Merge both kinds of requires into prereq_pm
	my $prereq = ($args->{PREREQ_PM} ||= {});
	%$prereq = ( %$prereq,
		map { @$_ }
		map { @$_ }
		grep $_,
		($self->configure_requires, $self->build_requires, $self->requires)
	);

	# Remove any reference to perl, PREREQ_PM doesn't support it
	delete $args->{PREREQ_PM}->{perl};

	# merge both kinds of requires into prereq_pm
	my $subdirs = ($args->{DIR} ||= []);
	if ($self->bundles) {
		foreach my $bundle (@{ $self->bundles }) {
			my ($file, $dir) = @$bundle;
			push @$subdirs, $dir if -d $dir;
			delete $prereq->{$file};
		}
	}

	if ( my $perl_version = $self->perl_version ) {

inc/Module/Install/Metadata.pm  view on Meta::CPAN

	module_name
	abstract
	author
	version
	distribution_type
	tests
	installdirs
};

my @tuple_keys = qw{
	configure_requires
	build_requires
	requires
	recommends
	bundles
	resources
};

my @resource_keys = qw{
	homepage
	bugtracker
	repository
};

my @array_keys = qw{
	keywords
};

sub Meta              { shift          }
sub Meta_BooleanKeys  { @boolean_keys  }
sub Meta_ScalarKeys   { @scalar_keys   }
sub Meta_TupleKeys    { @tuple_keys    }
sub Meta_ResourceKeys { @resource_keys }
sub Meta_ArrayKeys    { @array_keys    }

foreach my $key ( @boolean_keys ) {
	*$key = sub {
		my $self = shift;
		if ( defined wantarray and not @_ ) {
			return $self->{values}->{$key};
		}
		$self->{values}->{$key} = ( @_ ? $_[0] : 1 );
		return $self;

inc/Module/Install/Metadata.pm  view on Meta::CPAN

foreach my $key ( @array_keys ) {
	*$key = sub {
		my $self = shift;
		return $self->{values}->{$key} if defined wantarray and !@_;
		$self->{values}->{$key} ||= [];
		push @{$self->{values}->{$key}}, @_;
		return $self;
	};
}

foreach my $key ( @resource_keys ) {
	*$key = sub {
		my $self = shift;
		unless ( @_ ) {
			return () unless $self->{values}->{resources};
			return map  { $_->[1] }
			       grep { $_->[0] eq $key }
			       @{ $self->{values}->{resources} };
		}
		return $self->{values}->{resources}->{$key} unless @_;
		my $uri = shift or die(
			"Did not provide a value to $key()"
		);
		$self->resources( $key => $uri );
		return 1;
	};
}

foreach my $key ( grep { $_ ne "resources" } @tuple_keys) {
	*$key = sub {
		my $self = shift;
		return $self->{values}->{$key} unless @_;
		my @added;
		while ( @_ ) {
			my $module  = shift or last;
			my $version = shift || 0;
			push @added, [ $module, $version ];
		}
		push @{ $self->{values}->{$key} }, @added;
		return map {@$_} @added;
	};
}

# Resource handling
my %lc_resource = map { $_ => 1 } qw{
	homepage
	license
	bugtracker
	repository
};

sub resources {
	my $self = shift;
	while ( @_ ) {
		my $name  = shift or last;
		my $value = shift or next;
		if ( $name eq lc $name and ! $lc_resource{$name} ) {
			die("Unsupported reserved lowercase resource '$name'");
		}
		$self->{values}->{resources} ||= [];
		push @{ $self->{values}->{resources} }, [ $name, $value ];
	}
	$self->{values}->{resources};
}

# Aliases for build_requires that will have alternative
# meanings in some future version of META.yml.
sub test_requires     { shift->build_requires(@_) }
sub install_requires  { shift->build_requires(@_) }

# Aliases for installdirs options
sub install_as_core   { $_[0]->installdirs('perl')   }
sub install_as_cpan   { $_[0]->installdirs('site')   }
sub install_as_site   { $_[0]->installdirs('site')   }
sub install_as_vendor { $_[0]->installdirs('vendor') }

sub dynamic_config {
	my $self = shift;
	unless ( @_ ) {

inc/Module/Install/Metadata.pm  view on Meta::CPAN

    lgpl         => 'http://opensource.org/licenses/lgpl-license.php',
    lgpl2        => 'http://opensource.org/licenses/lgpl-2.1.php',
    lgpl3        => 'http://opensource.org/licenses/lgpl-3.0.html',
    bsd          => 'http://opensource.org/licenses/bsd-license.php',
    gpl          => 'http://opensource.org/licenses/gpl-license.php',
    gpl2         => 'http://opensource.org/licenses/gpl-2.0.php',
    gpl3         => 'http://opensource.org/licenses/gpl-3.0.html',
    mit          => 'http://opensource.org/licenses/mit-license.php',
    mozilla      => 'http://opensource.org/licenses/mozilla1.1.php',
    open_source  => undef,
    unrestricted => undef,
    restrictive  => undef,
    unknown      => undef,
);

sub license {
	my $self = shift;
	return $self->{values}->{license} unless @_;
	my $license = shift or die(
		'Did not provide a value to license()'
	);
	$self->{values}->{license} = $license;

	# Automatically fill in license URLs
	if ( $license_urls{$license} ) {
		$self->resources( license => $license_urls{$license} );
	}

	return 1;
}

sub all_from {
	my ( $self, $file ) = @_;

	unless ( defined($file) ) {
		my $name = $self->name or die(

inc/Module/Install/Metadata.pm  view on Meta::CPAN

		dist_name    => $self->name,
		dist_version => $self->version,
		license      => $self->license,
	);
	$self->provides( %{ $build->find_dist_packages || {} } );
}

sub feature {
	my $self     = shift;
	my $name     = shift;
	my $features = ( $self->{values}->{features} ||= [] );
	my $mods;

	if ( @_ == 1 and ref( $_[0] ) ) {
		# The user used ->feature like ->features by passing in the second
		# argument as a reference.  Accomodate for that.
		$mods = $_[0];
	} else {
		$mods = \@_;
	}

	my $count = 0;
	push @$features, (
		$name => [
			map {
				ref($_) ? ( ref($_) eq 'HASH' ) ? %$_ : @$_ : $_
			} @$mods
		]
	);

	return @$features;
}

sub features {
	my $self = shift;
	while ( my ( $name, $mods ) = splice( @_, 0, 2 ) ) {
		$self->feature( $name, @$mods );
	}
	return $self->{values}->{features}
		? @{ $self->{values}->{features} }
		: ();
}

sub no_index {
	my $self = shift;
	my $type = shift;
	push @{ $self->{values}->{no_index}->{$type} }, @_ if $type;
	return $self->{values}->{no_index};
}

inc/Module/Install/Metadata.pm  view on Meta::CPAN

	if ( @links > 1 ) {
		warn "Found more than on rt.cpan.org link in $_[0]\n";
		return 0;
	}

	# Set the bugtracker
	bugtracker( $links[0] );
	return 1;
}

sub requires_from {
	my $self     = shift;
	my $content  = Module::Install::_readperl($_[0]);
	my @requires = $content =~ m/^use\s+([^\W\d]\w*(?:::\w+)*)\s+([\d\.]+)/mg;
	while ( @requires ) {
		my $module  = shift @requires;
		my $version = shift @requires;
		$self->requires( $module => $version );
	}
}

sub test_requires_from {
	my $self     = shift;
	my $content  = Module::Install::_readperl($_[0]);
	my @requires = $content =~ m/^use\s+([^\W\d]\w*(?:::\w+)*)\s+([\d\.]+)/mg;
	while ( @requires ) {
		my $module  = shift @requires;
		my $version = shift @requires;
		$self->test_requires( $module => $version );
	}
}

# Convert triple-part versions (eg, 5.6.1 or 5.8.9) to
# numbers (eg, 5.006001 or 5.008009).
# Also, convert double-part versions (eg, 5.8)
sub _perl_version {
	my $v = $_[-1];
	$v =~ s/^([1-9])\.([1-9]\d?\d?)$/sprintf("%d.%03d",$1,$2)/e;
	$v =~ s/^([1-9])\.([1-9]\d?\d?)\.(0|[1-9]\d?\d?)$/sprintf("%d.%03d%03d",$1,$2,$3 || 0)/e;

inc/Module/Install/Metadata.pm  view on Meta::CPAN


	# We need Parse::CPAN::Meta to load the file
	unless ( eval { require Parse::CPAN::Meta; 1; } ) {
		return undef;
	}

	# Merge the perl version into the dependencies
	my $val  = $self->Meta->{values};
	my $perl = delete $val->{perl_version};
	if ( $perl ) {
		$val->{requires} ||= [];
		my $requires = $val->{requires};

		# Canonize to three-dot version after Perl 5.6
		if ( $perl >= 5.006 ) {
			$perl =~ s{^(\d+)\.(\d\d\d)(\d*)}{join('.', $1, int($2||0), int($3||0))}e
		}
		unshift @$requires, [ perl => $perl ];
	}

	# Load the advisory META.yml file
	my @yaml = Parse::CPAN::Meta::LoadFile('META.yml');
	my $meta = $yaml[0];

	# Overwrite the non-configure dependency hashs
	delete $meta->{requires};
	delete $meta->{build_requires};
	delete $meta->{recommends};
	if ( exists $val->{requires} ) {
		$meta->{requires} = { map { @$_ } @{ $val->{requires} } };
	}
	if ( exists $val->{build_requires} ) {
		$meta->{build_requires} = { map { @$_ } @{ $val->{build_requires} } };
	}

	return $meta;
}

1;

inc/Module/Install/Win32.pm  view on Meta::CPAN


  http://download.microsoft.com/download/vc15/Patch/1.52/W95/EN-US/Nmake15.exe
      or
  ftp://ftp.microsoft.com/Softlib/MSLFILES/Nmake15.exe

Please download the file manually, save it to a directory in %PATH% (e.g.
C:\WINDOWS\COMMAND\), then launch the MS-DOS command line shell, "cd" to
that directory, and run "Nmake15.exe" from there; that will create the
'nmake.exe' file needed by this module.

You may then resume the installation process described in README.

-------------------------------------------------------------------------------
END_MESSAGE

}

1;

lib/AI/ExpertSystem/Advanced.pm  view on Meta::CPAN

# Author(s): Pablo Fischer (pfischer@cpan.org)
# Created: 11/29/2009 18:28:30 CST 18:28:30
package AI::ExpertSystem::Advanced;

=head1 NAME

AI::ExpertSystem::Advanced - Expert System with backward, forward and mixed algorithms

=head1 DESCRIPTION

Inspired in L<AI::ExpertSystem::Simple> but with additional features:

=over 4

=item *

Uses backward, forward and mixed algorithms.

=item *

Offers different views, so user can interact with the expert system via a

lib/AI/ExpertSystem/Advanced.pm  view on Meta::CPAN

=item * B<FACT_SIGN_POSITIVE>

Used for those facts that happen.

=cut
use constant FACT_SIGN_POSITIVE => '+';

=item * B<FACT_SIGN_UNSURE>

Used when there's no straight answer of a fact, eg, we don't know if an answer
will change the result.

=back

=cut
use constant FACT_SIGN_UNSURE   => '~';

=head1 Methods

=head2 B<shoot($rule, $algorithm)>

lib/AI/ExpertSystem/Advanced.pm  view on Meta::CPAN

                    sign => $sign,
                    factor => 0.0,
                    algorithm => $algorithm,
                    rule => $rule
                });
    }
}

=head2 B<compare_causes_with_facts($rule)>

Compares the causes of the given C<$rule> with:

=over 4

=item *

Initial facts

=item *

Inference facts

lib/AI/ExpertSystem/Advanced.pm  view on Meta::CPAN

    $ai->forward();
    $ai->summary();

The forward chaining algorithm is one of the main methods used in Expert
Systems. It starts with a set of variables (known as initial facts) and reads
the available rules.

It will be reading rule by rule and for each one it will compare its causes
with the initial, inference and asked facts. If all of these causes are in the
facts then the rule will be shoot and all of its goals will be copied/converted
to inference facts and will restart reading from the first rule.

=cut
sub forward {
    my ($self) = @_;

    confess "Can't do forward algorithm with no initial facts" unless
        $self->{'initial_facts_dict'};

    my ($more_rules, $current_rule) = (1, undef);
    while($more_rules) {

lib/AI/ExpertSystem/Advanced.pm  view on Meta::CPAN

                }
            }
        }
    }
    return 1;
}

=head2 B<mixed()>

As its name says, it's a mix of L<forward()> and L<backward()> algorithms, it
requires to have at least one initial fact.

The first thing it does is to run the L<forward()> algorithm (hence the need of
at least one initial fact). If the algorithm fails then the mixed algorithm
also ends unsuccessfully.

Once the first I<run> of L<forward()> algorithm happens it starts looking for
any positive inference fact, if only one is found then this ends the algorithm
with the assumption it knows what's happening.

In case no positive inference fact is found then it will start reading the

lib/AI/ExpertSystem/Advanced.pm  view on Meta::CPAN

our first initial facts).

Once all the rules are read then it verifies if there are intuitive facts, if
no facts are found then it ends with the intuition, otherwise it will run the
L<backward()> algorithm for each one of these facts (eg, each fact will be
converted to a goal). After each I<run> of the L<backward()> algorithm it will
verify for any positive inference fact, if just one is found then the algorithm
ends.

At the end (if there are still no positive inference facts) it will run the
L<forward()> algorithm and restart (by looking again for any positive inference
fact).

A good example to understand how this algorithm is useful is: imagine you are
a doctor and know some of the symptoms of a patient. Probably with the first
symptoms you have you can get to a positive conclusion (eg that a patient has
I<X> disease). However in case there's still no clue, then a set of questions
(done by the call of L<backward()>) of symptons related to the initial symptoms
will be asked to the user. For example, we know that that the patient has a
headache but that doesn't give us any positive answer, what if the patient has
flu or another disease? Then a set of these I<related> symptons will be asked

lib/AI/ExpertSystem/Advanced.pm  view on Meta::CPAN


    if (!$self->forward()) {
        $self->{'viewer'}->print_error("The first execution of forward failed");
        return 0;
    }

    use Data::Dumper;

    while(1) {
        # We are satisfied if only one inference fact is positive (eg, means we
        # got to our result)
        while(my $fact = $self->{'inference_facts'}->iterate) {
            my $sign = $self->{'inference_facts'}->get_value($fact, 'sign');
            if ($sign eq FACT_SIGN_POSITIVE) {
                $self->{'viewer'}->debug(
                        "We are done, a positive fact was found"
                        );
                return 1;
            }
        }

lib/AI/ExpertSystem/Advanced.pm  view on Meta::CPAN

                }
            }
        }
        $self->forward();
    }
}

=head2 B<summary($return)>

The main purpose of any expert system is the ability to explain: what is
happening, how it got to a result, what assumption(s) it required to make,
the fatcs that were excluded and the ones that were used.

This method will use the L<viewer> (or return the result) in YAML format of all
the rules that were shot. It will explain how it got to each one of the causes
so a better explanation can be done by the L<viewer>.

If C<$return> is defined (eg, it got any parameter) then the result wont be
passed to the L<viewer>, instead it will be returned as a string.

=cut
sub summary {
    my ($self, $return) = @_;

    # any facts we found via inference?
    if (scalar @{$self->{'inference_facts'}->{'stack'}} eq 0) {
        $self->{'viewer'}->print_error("No inference was possible");
    } else {



( run in 1.505 second using v1.01-cache-2.11-cpan-49f99fa48dc )