home *** CD-ROM | disk | FTP | other *** search
- Path: sparky!uunet!munnari.oz.au!goanna!ok
- From: ok@goanna.cs.rmit.oz.au (Richard A. O'Keefe)
- Newsgroups: comp.lang.prolog
- Subject: Re: Help on problem needed!
- Keywords: help
- Message-ID: <14219@goanna.cs.rmit.oz.au>
- Date: 27 Aug 92 07:29:44 GMT
- References: <meskes.713709771@ulysses> <1992Aug25.074623.25450@greco-prog.fr>
- Organization: Comp Sci, RMIT, Melbourne, Australia
- Lines: 39
-
- In article <1992Aug25.074623.25450@greco-prog.fr>, billaud@greco-prog.fr (Michel BILLAUD) writes:
- > In article <meskes.713709771@ulysses> meskes@ulysses.informatik.rwth-aachen.de (Michael Meskes) writes:
- >
- > >Can you program a IF...THEN...ELSE in Prolog without using the cut?
- >
- > No. a proof by contradiction:
-
- Well, a lot depends on what goes in the gaps. If the stuff to go in the
- gaps is logical formulas, the proof goes through. But with suitable
- restrictions it is possible. For example, define
- <test> ::= <expression> <a.relop> <expression>
- | <term> <t.relop> <term>
- | NOT <test>
- | <test> AND <test>
- | <test> OR <test>
- where the understanding is that the arithmetic expressions whose values
- are to be compared and the terms which are to be compared must be ground.
- (NU-Prolog-style 'when' declarations for comparison predicates can do this.)
- Then we can negate a formula:
- NOT(E1 a.R E2) => E1 NOT(a.R) E2 e.g. NOT(<) = >=
- NOT(T1 t.R T2) => T1 NOT(t.R) T2 e.g. NOT(@<) = @>=
- NOT(NOT(T)) => T
- NOT(X1 AND X2) => NOT(X1) OR NOT(X2)
- NOT(X1 OR X2) => NOT(X1) AND NOT(X2)
- and something of the form
- IF <test> THEN <true> ELSE <false>
- can be converted to
- ( <test>, <true>
- ; NOT(<test>), <false>
- )
- Note that SB-Prolog already recognises some special cases of this pattern,
- so that ( X < 0, a ; X >= 0, b ) will be compiled as an if-then-else.
-
- If you are writing an interpreter for some other language (e.g. a pure
- functional programming language) you can _interpret_ an if-then-else in
- that language without a Prolog cut.
-
- --
- You can lie with statistics ... but not to a statistician.
-