POV-Ray : Newsgroups : povray.off-topic : Logic programming Server Time
1 Oct 2024 13:18:16 EDT (-0400)
  Logic programming (Message 59 to 68 of 68)  
<<< Previous 10 Messages Goto Initial 10 Messages
From: Jim Henderson
Subject: Re: Logic programming
Date: 30 Mar 2008 12:44:15
Message: <47efd16f@news.povray.org>
On Sat, 29 Mar 2008 19:38:39 -0700, Chambers wrote:

> Jim Henderson wrote:
>> On Thu, 27 Mar 2008 00:23:52 -0700, Chambers wrote:
>> 
>>> Jim Henderson wrote:
>>>> Language is a funny thing.  I heard the construct "is was" the other
>>>> day.  The context was "the question is was this the question?" (not
>>>> exactly, but in that structure).  Funny to listen to....
>>> This is unstructured grammar.  You need to implement the structured /
>>> modular paradigm in order to improve legibility, efficacy, and general
>>> communicative success :)
>>>
>>> In other words, "The question is, 'was this a question?'"
>> 
>> Well, yeah, but unless your name is Victor Borge, punctuation isn't
>> something you hear (per se).
>> 
>> Jim
> 
> You mean it's not something you say, per se!
> 
> I'm pretty sure anyone can *hear* phonetic punctuation :)

Well, yes, I was thinking that you can discern the pauses and whatnot, 
but that doesn't equate to hearing the punctuation itself.  But you're 
right, I got that mixed up a little.  Can I claim it was late?  Or 
early?  Or that I had a bone in my leg? ;-)

Jim


Post a reply to this message

From: Chambers
Subject: Re: Logic programming
Date: 30 Mar 2008 14:12:26
Message: <47efe61a$1@news.povray.org>
scott wrote:
> I think that the people in this ng are the people who are most likely in 
> the whole world to even consider writing a ray tracer.  And even then, I 
> wouldn't imagine that many have actually written one, and even fewer 
> gone beyond the basic coloured spheres on a plane test.

Exhibit A, your honor: I *tried* to write one for a high school physics 
project, and failed horribly :)

-- 
...Ben Chambers
www.pacificwebguy.com


Post a reply to this message

From: Invisible
Subject: Some code
Date: 2 Apr 2008 04:00:00
Message: <47f34b10$1@news.povray.org>
So what does this look like when implemented in Haskell?

 > module Logic where

Well, the program basically takes a predicate, and returns an
answer which says either:

- The predicate cannot be satisfied.

- The predicate can be satisfied, and this set of variable
   bindings satisfies is.

We can store the variable bindings in a key/value dictionary.
To do that, let's import the requisit Haskell module:

 > import qualified Data.Map

Now let's define a variable bindinds table type:

 > type Table = Data.Map.Map Var Expression

 > empty_table = Data.Map.empty

As I say, an "answer" is either a "no" or a "yes, and here's
the bindings". In Haskell, we can use the pre-defined "Maybe"
type for this.

 > type Answer = Maybe Table

Now let's define what an "expression" is. Let's say that an
expression can be a number, a variable, or a list. (I'll
define lists recursively so that predicates can recurse
over them.)

 > data Expression =
 >     Number      Integer               |
 >     Variable    Var                   |
 >     ListNode    Expression Expression |
 >     ListEndNode
 >   deriving (Eq, Show)

I'm going to have two types of variable - named ones that the
programmer creates, and numbered ones that are auto-generated
by the "exists" predicate later on:

 > data Var = Named String | Numbered Integer deriving (Eq, Ord, Show)

Let's continue now by defining the unification algorithm.


Remember, unification takes two expressions and determins
whether it is possible to make them the same by setting
some variable bindings. We start with an empty bindings
table, and proceed by adding new bindings.

 > unify :: Table -> Expression -> Expression -> Answer

Firstly, let's apply the current set of bindings to the
two input expressions before proceeding. This ensures that
any variables already bound are eliminated from the
expressions.

 > unify t e0 e1 = case (apply t e0, apply t e1) of

Now we take the possibilities case by case. For example,
if we have to unify a number against a number, we check
whether the numbers are equal. If they're not, unification
fails. If they are, unification suceeds (and the table
remains unchanged).

 >   (Number x, Number y) -> if x == y then Just t else Nothing

A variable matches anything. Well no, not quite. A variable
matches any expression not containing that variable. (E.g.,
you can't unify x = 2*x.) Assuming that condition holds, just
add the binding to the table.

 >   (Variable x, e) -> if e `contains` x
 >                        then Nothing
 >                        else Just (bind t x e)
 >   (e, Variable x) -> if e `contains` x
 >                        then Nothing
 >                        else Just (bind t x e)

Lists are slightly more tricky. Obviously an empty list
matches an empty list

 >   (ListEndNode, ListEndNode) -> Just t

For a non-empty list, we want to unify the list heads,
and then (using the binding table) continue unifying the
list tails. Oh, but if the first part fails, skip
the second part...

Fortunately, Haskell's much-feared "monad" concept implements
exactly this behaviour:

 >   (ListNode x xs, ListNode y ys) -> do
 >     t' <- unify t x y
 >     unify t' xs ys

That is, unify x against y using table t, thus generating a
new table t'. Then unify xs against ys using t' as the table
(thus generating a new table, which is the final result).

Oh, and finally, any combination that doesn't match one of
the above patterns (e.g., unify a number against a list)
causes unification to fail:

 >   (_, _) -> Nothing

Now we just need to implement that "apply" function:

 > apply :: Table -> Expression -> Expression
 > apply t (Variable v) = case Data.Map.lookup v t of
 >   Nothing -> Variable v
 >   Just e  -> e
 > apply t (ListNode x xs) = ListNode (apply t x) (apply t xs)
 > apply t e = e

And also the "contains" function:

 > contains :: Expression -> Var -> Bool
 > (Variable v)    `contains` v0 = v == v0
 > (ListNode x xs) `contains` v0 = x `contains` v0 || xs `contains` v0
 > _               `contains` v0 = False

Finally, the "bind" function. In principle this just inserts
a binding into the table - but actually I've made it rescan all
the existing bound expressions and apply any applicable expansions
to them as well to eliminate intermediate temporary variables.

 > bind :: Table -> Var -> Expression -> Table
 > bind t v e = Data.Map.map (apply t) (Data.Map.insert v e t)

Now we have unification. You can try out an example such as

   unify
     empty_table
     (ListNode (Number 1) (ListNode (Number 2) ListEndNode)
     (ListNode (Variable (Named "x")) (ListNode (Number 2) ListEndNode)

which yields the result

   Just (fromList [(Named "x",Number 1)]

In other words, "[1,2]" unified against "[x,2]" yields "x=1".

We can implement this as a predicate. But first we need to decide
what a "predicate" actually is. In my implementation, a predicate
is a function that takes a current bindings table and returns
a list of all possible bindings tables (starting from the given
one) that satisfy the predicate:

 > type State = (Table,Integer)

 > type Predicate = State -> [State]

What the heck is that integer there for? Well, it's used by
"exists", as we'll see a bit later. Let's now write a "run"
function:

 > run_pred :: Predicate -> [State]
 > run_pred p = p (empty_table, 1)

Anyway, the equality predicate is quite easy:

 > pred_equals :: Expression -> Expression -> Predicate
 > pred_equals x y (t,n) = case unify t x y of
 >   Nothing -> []
 >   Just t' -> [(t',n)]

If unification fails, return an empty list. If unification
succeeds, return a 1-element list containing the new
bindings table.

Implementing an OR predicate is similarly simple:

 > pred_OR :: Predicate -> Predicate -> Predicate
 > pred_OR p1 p2 (t,n) = p1 (t,n) ++ p2 (t,n)

In other words, run the first predicate, run the second
predicate, and then just JOIN the two answer lists thus
produced!

Implementing AND is moderately harder. We want to run the
first predicate, and then for EVERY result produced, run
the second predicate starting from that answer. Once again,
Haskell's monad structure leaps to the rescue:

 > pred_AND :: Predicate -> Predicate -> Predicate
 > pred_AND p1 p2 s0 = return s0 >>= p1 >>= p2

And finally, the "exists" predicate. It takes a function
that accepts a temp variable and returns a predicate.

 > pred_exists :: (Expression -> Predicate) -> Predicate
 > pred_exists fn (t,n) = (fn (Variable (Numbered n))) (t,n+1)

Now, to prove all this works, let's have that "join"
predicate:

 > pred_join :: Expression -> Expression -> Expression -> Predicate
 > pred_join xs ys zs =
 >   (
 >     (xs `pred_equals` ListEndNode) `pred_AND`
 >     (ys `pred_equals` zs)
 >   )
 >   `pred_OR`
 >   (
 >     pred_exists $ \t ->
 >     pred_exists $ \ts0 ->
 >     pred_exists $ \ts1 ->
 >     (xs `pred_equals` ListNode t ts0) `pred_AND`
 >     (zs `pred_equals` ListNode t ts1) `pred_AND`
 >     (pred_join ts0 ys ts1)
 >   )

To see it in action, you need to do quite a bit of typing,
unfortunately:

   run_pred $
     pred_join
       (Variable "xs")
       (Variable "ys")
       (ListNode (Number 1) (ListNode (Number 2) ListEndNode))

Should give you the following:

[(fromList [(Named "xs",ListEndNode),(Named "ys",ListNode (Number 1) 
(ListNode (Number 2) ListEndNode))],1),(fromList [(Named "xs",ListNode 
(Number 1) ListEndNode),(Named "ys",ListNode (Number 2) 
ListEndNode),(Numbered 1,Number 1),(Numbered 2,ListEndNode),(Numbered 
3,ListNode (Number 2) ListEndNode)],4),(fromList [(Named "xs",ListNode 
(Number 1) (ListNode (Number 2) ListEndNode)),(Named 
"ys",ListEndNode),(Numbered 1,Number 1),(Numbered 2,ListNode (Number 2) 
ListEndNode),(Numbered 3,ListNode (Number 2) ListEndNode),(Numbered 
4,Number 2),(Numbered 5,ListEndNode),(Numbered 6,ListEndNode)],7)]

which, if you unscramble it, translates as

   xs = [], ys = [1,2]
   xs = [1], ys = [2], ?1? = 1, ?2? = [], ?3? = [2],
   xs = [1,2], ys = [], ?1? = 1, ?2? = [2], ?3? = [2], ?4? = 2, ?5? = 
[], ?6? = []

Ignoring all the temp variables, that's basically

   xs = [], ys = [1,2]
   xs = [1], ys = [2]
   xs = [1,2], ys = []

Which is, indeed, all possible ways to construct the list [1,2].

Now, to make it properly fun, implement a small parser than can take
an expression such as "[x,y,z]" and construct the appropriate
Haskell data structure, and a pretty printer that takes the
result and prints it in human-readable form. ;-)

Oh, by the way, if you take this entire post and save it to disk as
"Logic.lhs", you can load it into any Haskell-98 compliant compiler
or interpretter and run it. This is actual source code!

[Alternatively, if you want to just delete all lines not starting
with ">", that'll give you the raw Haskell code, so you can
inspect it without my comments interspersed.]

-- 
http://blog.orphi.me.uk/
http://www.zazzle.com/MathematicalOrchid*


Post a reply to this message

From: Darren New
Subject: Re: Some code
Date: 2 Apr 2008 09:49:40
Message: <47f39d04$1@news.povray.org>
Invisible wrote:
> So what does this look like when implemented in Haskell?

Very cool. Thank you.  I'm tempted to try to translate this into Erlang 
to see how different it would be. :-)

-- 
   Darren New / San Diego, CA, USA (PST)
     "That's pretty. Where's that?"
          "It's the Age of Channelwood."
     "We should go there on vacation some time."


Post a reply to this message

From: Invisible
Subject: Re: Some code
Date: 2 Apr 2008 09:54:24
Message: <47f39e20@news.povray.org>
Darren New wrote:
> Invisible wrote:
>> So what does this look like when implemented in Haskell?
> 
> Very cool. Thank you.  I'm tempted to try to translate this into Erlang 
> to see how different it would be. :-)

Please, be my guest... I've never seen any non-trivial Erlang sources.

[Would you also like to see the parser and pretty printer? They're not 
much larger. ;-) ]

-- 
http://blog.orphi.me.uk/
http://www.zazzle.com/MathematicalOrchid*


Post a reply to this message

From: Darren New
Subject: Re: Some code
Date: 2 Apr 2008 10:54:04
Message: <47f3ac1c$1@news.povray.org>
Invisible wrote:
> Please, be my guest... I've never seen any non-trivial Erlang sources.

OK. Right now I'm working on a Jotto game. That's been my "second 
program" since high school on languages where I needed to figure out how 
they work.  (First being "hello world" of course.)

I'm happy to post that when I finish too.

I'm also trying to figure out in the back of my head how to translate a 
bunch of the SQL stuff at work to use Mnesia, which is Erlang's database 
system.  (Apparently, the name was originally "Amnesia" until one of the 
managers pointed out what a bad idea it was to name a database system 
"Amnesia." :-)

> [Would you also like to see the parser and pretty printer? They're not 
> much larger. ;-) ]

Sure. Erlang has such built in (for Erlang literals, at least), but 
sure. :-)

Incidentally, any reason you can see why this with 5600 lines of input 
would take 10 seconds and with 100,000 lines of input (20 times as big) 
it would take more than an hour?  Am I doing something stupidly N^2 or 
is it the memory management doing something odd?


load_file_words(IO, Acc) ->
     % Read one space-delimited string from the IO chan with no prompt
     Read = io:fread(IO, [], "~s"),
     case Read of
         {ok, [[]]} -> load_file_words(IO, Acc); % blank line
         {ok, [Word]} -> load_file_words(IO, [Word|Acc]); % found word
         eof -> Acc; % End of file, return accumulated answers
         {error, What} -> erlang:error(What) % crash out
     end.

Isn't this how you're supposed to do the functional programming loop bit? :)

-- 
   Darren New / San Diego, CA, USA (PST)
     "That's pretty. Where's that?"
          "It's the Age of Channelwood."
     "We should go there on vacation some time."


Post a reply to this message

From: Invisible
Subject: Re: Some code
Date: 3 Apr 2008 07:12:59
Message: <47f4c9cb$1@news.povray.org>
Darren New wrote:

> OK. Right now I'm working on a Jotto game. That's been my "second 
> program" since high school on languages where I needed to figure out how 
> they work.  (First being "hello world" of course.)
> 
> I'm happy to post that when I finish too.

What is "Jotto"?

> I'm also trying to figure out in the back of my head how to translate a 
> bunch of the SQL stuff at work to use Mnesia, which is Erlang's database 
> system.  (Apparently, the name was originally "Amnesia" until one of the 
> managers pointed out what a bad idea it was to name a database system 
> "Amnesia." :-)

Er, yes... interesting name choice. (?!)

>> [Would you also like to see the parser and pretty printer? They're not 
>> much larger. ;-) ]
> 
> Sure. Erlang has such built in (for Erlang literals, at least), but 
> sure. :-)

Oh, it's trivial to get the compiler to write a parser for Haskell 
literals too. But the problem [in this case] is that the Haskell 
expressions are rather verbose and wordy, which makes it hard to type 
out non-trivial example expressions and so forth.

> Incidentally, any reason you can see why this with 5600 lines of input 
> would take 10 seconds and with 100,000 lines of input (20 times as big) 
> it would take more than an hour?  Am I doing something stupidly N^2 or 
> is it the memory management doing something odd?
> 
> 
> load_file_words(IO, Acc) ->
>     % Read one space-delimited string from the IO chan with no prompt
>     Read = io:fread(IO, [], "~s"),
>     case Read of
>         {ok, [[]]} -> load_file_words(IO, Acc); % blank line
>         {ok, [Word]} -> load_file_words(IO, [Word|Acc]); % found word
>         eof -> Acc; % End of file, return accumulated answers
>         {error, What} -> erlang:error(What) % crash out
>     end.
> 
> Isn't this how you're supposed to do the functional programming loop 
> bit? :)

Without knowing Erlang well enough, I couldn't speculate. It looks to me 
light it ought to work, but hey...

-- 
http://blog.orphi.me.uk/
http://www.zazzle.com/MathematicalOrchid*


Post a reply to this message

From: Invisible
Subject: More code
Date: 3 Apr 2008 07:47:07
Message: <47f4d1cb$1@news.povray.org>
module Display where

import qualified Data.Map
import Logic

class Display d where
   display :: d -> String

instance Display Var where
   display (Named x) = x
   display (Numbered x) = "?" ++ show x ++ "?"

instance Display Expression where
   display (Number x) = show x
   display (Variable v) = display v
   display (ListNode x xs) = "(!" ++ display x ++ display xs ++ ")"
   display (ListEndNode) = "#"

print_results :: [State] -> IO ()
print_results = mapM_ (putStrLn . line)
   where
     line (t,n) = unwords $ map (\(v,e) -> display v ++ " = " ++ display 
e ++ ";") $ Data.Map.toList t



module Parse (parse_expression) where

import Text.ParserCombinators.Parsec
import Logic

trim = skipMany space

number = do
   ds <- many1 digit
   trim
   return (Number (read ds))

variable = do
   cs <- many1 letter
   trim
   return (Variable (Named cs))

list_node = do
   char '!'
   trim
   x  <- expression
   xs <- expression
   return (ListNode x xs)

list_end = do
   char '#'
   trim
   return ListEndNode

brackets = do
   char '('
   trim
   e <- expression
   char ')'
   trim
   return e

expression = do
   number <|> variable <|> list_node <|> list_end <|> brackets

parse_expression cs = case parse expression "" cs of
   Left  e -> error (show e)
   Right e -> e


Save the first one as Display.hs and the second as Parse.hs. Once you 
import Logic, Display and Parse, you should be able to convert a string 
such as "!1(!2(!3#))" into a logic expression by passing it to the 
parse_expression function. The result can be passed to the display 
method to turn it back into a string.

As far as I'm aware there are no bugs in the implementation, but I 
haven't tested extensively.

Now, let's try this:

   run_pred $
     pred_join
       (parse_expression "!1(!2(!3#))")
       (parse_expression "ys")
       (parse_expression "!1(!2(!3(!4(!5(!6)))))")

Unfortunately Haskell's class instance rules won't allow me to pretty 
print the predicate results without altering the rest of the code 
slightly... so I've written the print_results function instead.

-- 
http://blog.orphi.me.uk/
http://www.zazzle.com/MathematicalOrchid*


Post a reply to this message

From: Darren New
Subject: Re: Some code
Date: 3 Apr 2008 18:04:27
Message: <47f5627b@news.povray.org>
Invisible wrote:
> What is "Jotto"?

It's a word game, http://en.wikipedia.org/wiki/Jotto

Not unlike the "Mastermind" game, if you've ever played that.

I find it helpful as a first program because you have a bunch of things 
you need to do - prompt for and take input, remember previous guesses, 
store new words in a database or file somewhere, etc.

> Oh, it's trivial to get the compiler to write a parser for Haskell 
> literals too. But the problem [in this case] is that the Haskell 
> expressions are rather verbose and wordy, which makes it hard to type 
> out non-trivial example expressions and so forth.

I think the Haskell expressions are probably longer than the Erlang 
expressions would be because you're carrying the type around.

> Without knowing Erlang well enough, I couldn't speculate. It looks to me 
> light it ought to work, but hey...

I was just after whether it was a strange logic error or something. It 
works, it's just really slow, but the memory usage doesn't keep 
climbing. (I can see it GCing every few seconds, but it doesn't grow out 
of bounds and start paging or anything.)

Maybe I just haven't initialized the memory management to take advantage 
of enough memory to cut down the GCs.

Or maybe the file parsing stuff actually is written in Erlang, in which 
case it really *is* that slow.

The program to go thru and pick every 20'th word and write it out after 
reading it all in to memory in Tcl was faster by far than simply reading 
in the trimmed list in Erlang. Which is a bit worrysome, if I expect to 
be using this for production systems.


-- 
   Darren New / San Diego, CA, USA (PST)
     "That's pretty. Where's that?"
          "It's the Age of Channelwood."
     "We should go there on vacation some time."


Post a reply to this message

From: Darren New
Subject: Re: Some code
Date: 5 Apr 2008 01:28:49
Message: <47f71c21@news.povray.org>
Darren New wrote:
> I was just after whether it was a strange logic error or something. It 
> works, it's just really slow, 

It turns out that using the Erlang equivalent of fscanf("%s",...) is 
much slower than using the erlang equivalent of fgets(). Like, an hour 
versus a couple seconds to read and process the file. I haven't any idea 
why yet.

And I figured out what is throwing me about finding documentation. The 
language defines "modules" and "functions", where a "module" is all the 
functions in one source file.

But the top-level documentation is organized in terms of "applications", 
wherein each "application" is a collection of modules distributed 
together, but for which there's no real direct equivalent in the 
language itself. The runtime interpreter parses configuration values 
based on the application name (e.g., you can set the xyz configuration 
to pdq for the abc application by starting erlang with
   % erl -abc xyz pdq
), so the runtime knows about applications, and the libraries do, but 
they're nowhere in the TOC for the language manual.

Sort of like if you had to figure out whether what you want is in 
stdlib, stdio, STL, Boost, or POSIX before you could look up strlen or 
open() or something like that in the manual.

Yes, there are other indexes in the manual pages, but the documentation 
itself refers to the applications, so before you figure this out, it's 
way confusing. Especially since "application" doesn't *really* mean just 
"application".  Like, is spawning a new process in the "erlang" 
application, the "kernel" application, or the "stdlib" application? Is 
the function to dynamically load code in one of those, or is it in the 
"code" application or the "compiler" application or the "primitives" 
application? :-)

And then you package up "applications" into "releases", so just because 
you have a monitoring program, a database, and a web server, those could 
be three "applications" that make up one thing-the-user-runs, whatever 
you want to call them.

It doesn't help that you can fiddle with the syntax via macros, not 
unlike LISP. Except that the syntax fiddling is apparently (as far as 
I've been able to figure out) caused by something outside your modules. 
That is, you don't have to say anything inside your source code to get 
it modified dynamically during compilation. Instead, the thing that 
implements the parsing transformations is apparently configured in 
outside the system. The compiler must be reading a file somewhere saying 
"this list of modules implements parsing transformations" or some such. 
I haven't quite tracked that down yet, but now that I know the words...

Babble mumble mutter. Don't mind me.

-- 
   Darren New / San Diego, CA, USA (PST)
     "That's pretty. Where's that?"
          "It's the Age of Channelwood."
     "We should go there on vacation some time."


Post a reply to this message

<<< Previous 10 Messages Goto Initial 10 Messages

Copyright 2003-2023 Persistence of Vision Raytracer Pty. Ltd.