
I have a Question about haskell 1. is a something more complicated and I need some help with it if possible.. In order to check the satisfiability of a formula in a given model we propagate the effects of assigning a truth value to an atom in a formula. Assume an atom to which we assign the value True. The following effects can be applied to the formula: - The positive literals have the same True value and, therefore, any clauses that contain them are removed from the formula. This is to indicate that these clauses could be satisfied and hence no longer affect the satisfiability of the formula. - The negated literals have a value of False and are, therefore, removed from any clause they are in. This is to indicate that these clauses are still not satisfied and can only be made true by one of the other literals obtaining a value of True. In the case where False is assigned to the atom, the positive literals will now be false and should be removed from their clauses while the negative literals will become true and have their clauses removed from the formula. For example, in the formula (P _ Q _ R) ^ (:P _ Q _ :R) ^ (P _ :Q), assume we assign True to P. Then the clauses containing P, ie. (P _ Q _ R) and (P _ :Q) are removed from the formula, whereas :P is removed from any clause it is in, ie. (:P _ Q _ :R). This results in the formula (Q _ :R). On the other hand, if we assign False to P, we then remove (:P _ Q _ :R) from the formula and P from its clauses, thus obtaining (Q _ R) ^ (:Q). The overall formula is satisfiable if it can be reduced to the empty list since in this case all the clauses were satisfied. If there is an empty list within the overall formula then that means that a clause was not satisfied and hence the formula can not be satisfied with the assignment that led to this state. -assign :: (Atom,Bool)->Formula->Formula The assign function should take an (Atom,Bool) pair and a formula and propagate the effects of assigning the given truth value to the atom in the formula as described above The code(on which I received help from here also): module Algorithm where import System.Random import Data.Maybe import Data.List type Atom = String type Literal = (Bool,Atom) type Clause = [Literal] t ype Formula = [Clause] type Model = [(Atom, Bool)] t ype Node = (Formula, ([Atom], Model)) atomsClause :: Clause -> [Atom] -This function takess a Clause and return the set of Atoms of that Clause. atomsClause = nub . map snd atoms :: Formula -> [Atom] atoms = nub . map snd -----This function takes a Formula returns the set of Atoms of a Formula isLiteral :: Literal -> Clause -> Bool isLiteral = isLiteral = any . (==)----This function returns True if the given Literal can be found within the Clause. flipSymbol :: Model -> Atom -> Model--- f lipSymbol m a = map f m - where f (atom, value) = if a == atom then (atom, not value) else (atom, value)-this function takes a Model and an Atom and flip the truthvalue of the atom in the model assign :: (Atom,Bool)->Formula->Formula assign = undefined--------any advice here? Thank you -- View this message in context: http://haskell.1045720.n5.nabble.com/Haskell-function-help-tp3365994p3365994... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Let me see if I understand that correctly. On Tuesday 01 February 2011 12:18:06, Houdini wrote:
module Algorithm where
import System.Random import Data.Maybe import Data.List
type Atom = String type Literal = (Bool,Atom)
(True "P") correspnds to "P", (False, "P") to "not P"?
type Clause = [Literal]
A Clause is the disjunction of the literals appearing in it? So [(True,"P"),(False,"Q")] translates to (p || not q) ?
type Formula = [Clause]
A Formula is the conjunction of its Clauses? [[(True,"P"),(False,"Q")],[(True,"R")]] translates to (p || not q) && r ?
type Model = [(Atom, Bool)]
type Node = (Formula, ([Atom], Model))
No idea what that would mean
atomsClause :: Clause -> [Atom] --This function takess a Clause and return the set of Atoms of that
Clause.
atomsClause = nub . map snd
atoms :: Formula -> [Atom] atoms = nub . map snd
Doesn't type check, should be atoms = nub . map snd . concat
--This function takes a Formula returns the set of Atoms of a Formula
isLiteral :: Literal -> Clause -> Bool isLiteral = isLiteral = any . (==) --This function returns True if the given Literal can be found within the Clause.
flipSymbol :: Model -> Atom -> Model flipSymbol m a = map f m where f (atom, value) = if a == atom then (atom, not value) else (atom, value) -- this function takes a Model and an Atom and flip the truthvalue of the atom in the model
assign :: (Atom,Bool)->Formula->Formula assign = undefined--------any advice here? Thank you
You have to find what should happen on - Literals - Clauses - Formulae (not necessarily in that order) If the Formula is empty, I suppose nothing should be done, assign _ [] = [] if there are Clauses, assign (atom,value) (clause:rest) should do the assignment in the Clause and depending on the outcome, remove the (modified) Clause and assign in the rest, or prepend the modified Clause to the result of assigning in the rest, assign (atom,value) (clause:rest) = case assignClause (atom,value) clause of Nothing -> assign (atom,value) rest Just cl -> cl : assign (atom,value) rest Now for assigning in a Clause. You get a trivially satisfied Clause, which we'll indicate by a Nothing return value, or a reduced Clause (which may be empty and hence unsatisfiable). assignClause :: (Atom,Bool) -> Clause -> Maybe Clause assignClause (atom,value) clause = case partition ((== atom) . snd) clause of -- the atom doesn't appear in the clause, nothing to do ([],_) -> Just clause -- the atom appears in the clause, we have see whether -- assigning produces a True or only False (ms,cs) -- a True, clause is satisfied | any (satisfied value) (map fst ms) -> Nothing -- all occurrences lead to a False, we have to keep the other Literals | otherwise -> Just cs Now, what happens for Literals? We only call this for matching Atoms, so we need only care for the Bools. If the Literal has the form (True,p), we get value, otherwise we get (not value): satisfied :: Bool -> Bool -> Bool satisfied value True = value -- Literal in positive form staisfied value False = not value -- the Literal was negated Now we can write satisfied shorter: satisfied = (==) Or better, now we know what it is supposed to do, remove it altogether and make the guard condition in assignClause (ms,cs) | any (== value) (map fst ms) -> Nothing | otherwise -> Just cs

it's atoms = atomsClause.concat -- View this message in context: http://haskell.1045720.n5.nabble.com/Haskell-function-help-tp3365994p3366134... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

thank you for the reply -- View this message in context: http://haskell.1045720.n5.nabble.com/Haskell-function-help-tp3365994p3366135... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

that is really.....complicated...hmm -- View this message in context: http://haskell.1045720.n5.nabble.com/Haskell-function-help-tp3365994p3366154... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Am 01.02.11 14:05, schrieb Houdini:
that is really.....complicated...hmm
Maybe you find assign :: (Atom,Bool)->Formula->Formula assign _ [] = [] assign (a,b) (c:cs) | (b,a) `elem` c = cs' | otherwise = filter ((/= a).snd) c : cs' where cs' = assign (a,b) cs easier to read. With example :: Formula example = [[p,q,r],[n p,q,n r],[p,n q]] where p = l "P" q = l "Q" r = l "R" l a = (True, a) n (b,a) = (not b, a) we get *Algorithm> example [[(True,"P"),(True,"Q"),(True,"R")],[(False,"P"),(True,"Q"),(False,"R")],[(True,"P"),(False,"Q")]] *Algorithm> assign ("P", True) example [[(True,"Q"),(False,"R")]] *Algorithm> assign ("P", False) example [[(True,"Q"),(True,"R")],[(False,"Q")]] But note that we also get *Algorithm> assign ("P", False) [[(True,"P"),(True,"Q"),(True,"R")],[(False,"P"),(True,"Q"),(False,"R")],[(True,"P")]] [[(True,"Q"),(True,"R")],[]] So this is not reduced to [[]]. hth C.

How about this...? assign :: (Atom,Bool) -> Formula -> Formula assign (a,b) = map . (map f) where f (x,b) = (x,(x==a)&&b) -- View this message in context: http://haskell.1045720.n5.nabble.com/Haskell-function-help-tp3365994p3366965... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

I did,obvioulsy....and it works,....thank you all for your help...you gave me inspiration.There has to be a way to test this function for a higher amount of inputs with only a couple of lines in ghci,isn't it? -- View this message in context: http://haskell.1045720.n5.nabble.com/Haskell-function-help-tp3365994p3367113... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

I didn't write it like that...because since I'm using the dot notation I can specify aguments for the function...I rectified that...sorry I forgot to mention -- View this message in context: http://haskell.1045720.n5.nabble.com/Haskell-function-help-tp3365994p3368000... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

*can't -- View this message in context: http://haskell.1045720.n5.nabble.com/Haskell-function-help-tp3365994p3368001... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
participants (3)
-
Carsten Schultz
-
Daniel Fischer
-
Houdini