POV-Ray : Newsgroups : povray.off-topic : Logic programming : More code Server Time
1 Oct 2024 15:22:17 EDT (-0400)
  More code  
From: Invisible
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

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