DIRECTORY BoolOps, Atom USING [MakeAtom, GetPName], RefTab, Convert, IO, Rope; BoolOpsImplA: CEDAR PROGRAM IMPORTS RefTab, Convert, IO, Rope, Atom EXPORTS BoolOps = BEGIN OPEN BoolOps; TokenTypes: TYPE = {Id, SubTree, Not, And, Or, LParen, RParen, End, Null}; precedence: ARRAY TokenTypes OF Rope.ROPE _ [ -- Id -- "..>>>>>>.", --Subt-- ".........", --Not -- "<.<>><>>.", --And -- "<.<=><>>.", --Or -- "<.<<=<>>.", --LPar-- "<.<<<<=..", --RPar-- "..>>>.>>.", --End -- "<.<<<<...", --Null-- "........." ]; tokenNames: ARRAY TokenTypes OF Rope.ROPE _ ["", "", "~", "AND", "OR", "(", ")", "", ""]; Error: PUBLIC ERROR[ec: ErrorCode, msg: Rope.ROPE] = CODE; RopeToTree: PUBLIC PROC [expr: Rope.ROPE] RETURNS [tree: Tree] = BEGIN Token: TYPE = RECORD [ type: TokenTypes, name: Rope.ROPE _ NIL, value: SubTree _ NIL ]; Input: TYPE = RECORD [ value: Rope.ROPE, index: CARDINAL _ 0 ]; Stack: TYPE = LIST OF Token; NextToken: PROC [in: IO.STREAM] RETURNS[Token] = BEGIN tok: Rope.ROPE; eof: BOOL _ FALSE; [ , tok, ] _ IO.GetCedarTokenRope[in ! IO.Error => {eof _ TRUE; CONTINUE}; IO.EndOfStream => {eof _ TRUE; CONTINUE} ]; IF eof THEN RETURN[[$End, ""]]; FOR t: TokenTypes IN TokenTypes DO IF Rope.Equal[tok, tokenNames[t]] THEN RETURN[[t, tok]]; ENDLOOP; RETURN[[$Id, tok]]; END; Push: PROC [s: Stack, t: Token] RETURNS[Stack] = BEGIN RETURN[CONS[t, s]]; END; Pop: PROC [s: Stack] RETURNS[Stack, Token] = BEGIN IF s = NIL THEN RETURN[NIL, [$Null, "(Stack underflow)", NIL]]; RETURN[s.rest, s.first]; END; Peek: PROC [s: Stack] RETURNS[Token] = BEGIN IF s = NIL THEN RETURN[[$Null, "(Stack underflow)", NIL]]; RETURN[s.first]; END; PeekUnder: PROC [s: Stack] RETURNS[Token] = BEGIN FOR tlist: Stack _ s, tlist.rest WHILE tlist # NIL DO IF tlist.first.type # $SubTree THEN RETURN[tlist.first]; ENDLOOP; RETURN[[$Null, "(Stack underflow)", NIL]]; END; Precedence: PROC [tokl, tokr: TokenTypes] RETURNS[CHAR] = BEGIN RETURN[Rope.Fetch[precedence[tokl], ORD[tokr]]]; END; in: IO.STREAM _ IO.RIS[expr]; s: Stack _ NIL; p, curToken: Token; s _ Push[s, [$End, NIL]]; curToken _ [$Null, NIL, NIL]; DO IF curToken.type = $Null THEN curToken _ NextToken[in]; p _ PeekUnder[s]; SELECT Precedence[p.type, curToken.type] FROM '<, '= => { -- shift s _ Push[s, curToken]; curToken.type _ $Null; }; '> => { -- reduce top, rp: Token; topOp: Token _ [$Null, NIL, NIL]; newt: Token; haveOp: BOOL _ FALSE; op: Operator; opId: TokenTypes; numArgs: CARDINAL _ 0; newt.type _ $SubTree; DO [s, top] _ Pop[s]; IF top.type # SubTree THEN topOp _ top; SELECT top.type FROM $Id => { newt.value _ NEW[Leaf]; NARROW[newt.value, REF Leaf].var _ Atom.MakeAtom[top.name]; }; $SubTree => { IF newt.value = NIL THEN newt.value _ NEW[Expression]; NARROW[newt.value, REF Expression].children _ CONS[top.value, NARROW[newt.value, REF Expression].children]; numArgs _ numArgs + 1; }; $Or, $And, $Not => { newOp: Operator; SELECT top.type FROM $Or => newOp _ $Or; $And => newOp _ $And; $Not => newOp _ $Not; ENDCASE => newOp _ $None; IF haveOp THEN { IF op # newOp OR op = $Not THEN ERROR Error[InternalError, "Parser screwup."]; } ELSE { haveOp _ TRUE; op _ newOp; opId _ top.type; }; }; ENDCASE; rp _ Peek[s]; IF rp.type # $SubTree AND topOp.type # $Null THEN { SELECT Precedence[rp.type, topOp.type] FROM '< => EXIT; '= => NULL; '> => ERROR; ENDCASE => GOTO syntax; }; ENDLOOP; IF haveOp THEN { IF numArgs < 1 THEN GOTO syntax; IF op = $Not AND numArgs > 1 THEN GOTO syntax; NARROW[newt.value, REF Expression].op _ op; } ELSE { IF numArgs > 1 THEN GOTO syntax; IF ISTYPE[newt.value, REF Expression] THEN { e: REF Expression _ NARROW[newt.value, REF Expression]; IF e # NIL AND e.children # NIL THEN newt.value _ e.children.first; }; }; IF curToken.type = $End AND Peek[s].type = $End THEN RETURN[newt.value]; s _ Push[s, newt]; }; ENDCASE => GOTO syntax; ENDLOOP; EXITS syntax => ERROR Error[SyntaxError, "Syntax error in expression."]; END; TreeToRope: PUBLIC PROC [tree: Tree] RETURNS [Rope.ROPE] = BEGIN result: Rope.ROPE _ NIL; IF tree = NIL THEN RETURN[""]; WITH tree SELECT FROM l: REF Leaf => { IF l.neg THEN RETURN[Rope.Concat[tokenNames[$Not], Atom.GetPName[l.var]]] ELSE RETURN[Atom.GetPName[l.var]]; }; e: REF Expression => { opName: Rope.ROPE; haveArg: BOOL _ FALSE; SELECT e.op FROM $Not => opName _ tokenNames[$Not]; $Or => opName _ tokenNames[$Or]; $And => opName _ tokenNames[$And]; $None => opName _ ""; ENDCASE => ERROR Error[UnknownOperator, "Unknown operator in expression tree."]; IF e.op = $Not THEN result _ opName ELSE result _ ""; FOR st: LIST OF SubTree _ e.children, st.rest WHILE st # NIL DO stName: Rope.ROPE; stName _ TreeToRope[st.first]; IF ~ISTYPE[st.first, REF Leaf] THEN stName _ Rope.Cat["(", stName, ")"]; IF e.op = $Not THEN result _ Rope.Cat[result, " ", stName] ELSE { IF haveArg THEN result _ Rope.Cat[result, " ", opName, " ", stName] ELSE result _ Rope.Cat[result, stName]; }; haveArg _ TRUE; ENDLOOP; RETURN[result]; }; ENDCASE => ERROR Error[BadPointer, "Tree is malformed, a pointer points to something other than a subtree or a node."]; END; AppendTreeLists: PROC [l1, l2: LIST OF SubTree] RETURNS [LIST OF SubTree] = BEGIN t: LIST OF SubTree _ l1; FOR tl: LIST OF SubTree _ l2, tl.rest WHILE tl # NIL DO t _ CONS[tl.first, t]; ENDLOOP; RETURN[t]; END; SOPNot: PUBLIC PROC [tree: Tree] RETURNS [Tree] = BEGIN IF tree = NIL THEN ERROR Error[TreeIsNil, "Tree is NIL."]; WITH tree SELECT FROM l: REF Leaf => { l2: REF Leaf _ NEW[Leaf _ l^]; l2.neg _ ~l2.neg; RETURN[l2]; }; e: REF Expression => { finalt: Tree _ NIL; IF e.children = NIL OR e.children.first = NIL THEN ERROR Error[EmptyExpression, "Empty expression."]; SELECT e.op FROM $Not => { RETURN[e.children.first]; }; $Or, $And => { finalt: Tree _ NIL; IF e.children.rest = NIL THEN -- only one term RETURN[SOPNot[e.children.first]]; FOR tl: LIST OF Tree _ e.children, tl.rest WHILE tl # NIL DO t: SubTree; t _ TreeToSOP[tl.first]; t _ SOPNot[t]; IF e.op = $And THEN finalt _ SOPOr[finalt, t] ELSE finalt _ SOPAnd[finalt, t]; ENDLOOP; RETURN[finalt]; }; $None => { RETURN[SOPNot[e.children.first]]; }; ENDCASE => ERROR Error[UnknownOperator, "Unknown operator."]; }; ENDCASE => ERROR Error[BadPointer, "Tree is malformed, a pointer points to something other than a subtree or a node."]; END; SOPAnd: PUBLIC PROC [tree1, tree2: Tree] RETURNS [Tree] = BEGIN e: REF Expression _ NEW[Expression]; l1, l2: LIST OF SubTree; IF tree1 = NIL THEN RETURN[tree2]; IF tree2 = NIL THEN RETURN[tree1]; e.op _ $Or; e.children _ NIL; IF ISTYPE[tree1, REF Expression] AND NARROW[tree1, REF Expression].op = $Or THEN l1 _ NARROW[tree1, REF Expression].children ELSE l1 _ CONS[tree1, NIL]; IF ISTYPE[tree2, REF Expression] AND NARROW[tree2, REF Expression].op = $Or THEN l2 _ NARROW[tree2, REF Expression].children ELSE l2 _ CONS[tree2, NIL]; FOR list1: LIST OF SubTree _ l1, list1.rest WHILE list1 # NIL DO FOR list2: LIST OF SubTree _ l2, list2.rest WHILE list2 # NIL DO and: REF Expression _ NEW[Expression]; and.op _ $And; IF ISTYPE[list1.first, REF Expression] AND NARROW[list1.first, REF Expression].op = $And THEN { and.children _ AppendTreeLists[NARROW[list1.first, REF Expression].children, and.children]; } ELSE { and.children _ CONS[list1.first, and.children]; }; IF ISTYPE[list2.first, REF Expression] AND NARROW[list2.first, REF Expression].op = $And THEN { and.children _ AppendTreeLists[NARROW[list2.first, REF Expression].children, and.children]; } ELSE { and.children _ CONS[list2.first, and.children]; }; e.children _ CONS[and, e.children]; ENDLOOP; ENDLOOP; RETURN[e]; END; SOPOr: PUBLIC PROC [tree1, tree2: Tree] RETURNS [Tree] = BEGIN e: REF Expression _ NEW[Expression]; IF tree1 = NIL THEN RETURN[tree2]; IF tree2 = NIL THEN RETURN[tree1]; e.op _ $Or; e.children _ NIL; IF ISTYPE[tree1, REF Expression] AND NARROW[tree1, REF Expression].op = $Or THEN { e.children _ AppendTreeLists[NARROW[tree1, REF Expression].children, e.children]; } ELSE { e.children _ CONS[tree1, e.children]; }; IF ISTYPE[tree2, REF Expression] AND NARROW[tree2, REF Expression].op = $Or THEN { e.children _ AppendTreeLists[NARROW[tree2, REF Expression].children, e.children]; } ELSE { e.children _ CONS[tree2, e.children]; }; RETURN[e]; END; TreeToSOP: PUBLIC PROC [tree: Tree] RETURNS [Tree] = BEGIN IF tree = NIL THEN ERROR Error[TreeIsNil, "Tree is NIL."]; WITH tree SELECT FROM l: REF Leaf => RETURN[tree]; e: REF Expression => { IF e.children = NIL OR e.children.first = NIL THEN ERROR Error[EmptyExpression, "Empty expression."]; SELECT e.op FROM $Not => { t: Tree; t _ TreeToSOP[e.children.first]; t _ SOPNot[t]; RETURN[t]; }; $Or, $And => { finalt: Tree _ NIL; FOR tl: LIST OF Tree _ e.children, tl.rest WHILE tl # NIL DO t: SubTree; t _ TreeToSOP[tl.first]; IF e.op = $Or THEN finalt _ SOPOr[finalt, t] ELSE finalt _ SOPAnd[finalt, t]; ENDLOOP; RETURN[finalt]; }; $None => { RETURN[TreeToSOP[e.children.first]]; }; ENDCASE => ERROR Error[UnknownOperator, "Unknown operator."]; }; ENDCASE => ERROR Error[BadPointer, "Tree is malformed, a pointer points to something other than a subtree or a node."]; END; SOPToTT: PUBLIC PROC [inputs: LIST OF ATOM, equations: LIST OF Tree] RETURNS [TruthTable] = BEGIN MakeTerm: PROC [ins, outs: CARDINAL, outputNumber: CARDINAL, inAtoms: RefTab.Ref, nv: LIST OF Leaf] RETURNS [REF PTerm] = BEGIN term: REF PTerm _ NEW[PTerm[ins + outs]]; FOR i: INT IN [0 .. ins + outs) DO IF i < ins THEN term[i] _ $NC ELSE term[i] _ $Zero; ENDLOOP; FOR var: LIST OF Leaf _ nv, var.rest WHILE var # NIL DO val: REF; num: REF INT; found: BOOL; [found, val] _ RefTab.Fetch[inAtoms, var.first.var]; IF ~found THEN ERROR Error[VariableNotAnInput, "Variable is not an input."]; num _ NARROW[val]; IF var.first.neg THEN term[num^] _ $Zero ELSE term[num^] _ $One; ENDLOOP; term[ins + outputNumber] _ $One; RETURN[term]; END; AddVar : PROC [t: Tree, v: LIST OF Leaf] RETURNS[LIST OF Leaf] = BEGIN WITH t SELECT FROM l: REF Leaf => { RETURN[CONS[l^, v]]; }; ENDCASE => GOTO notSOP; EXITS notSOP => ERROR Error[NotSOP, "Expression is not in Sum-Of-Products form."]; END; AddTerm: PROC [t: Tree, v: LIST OF Leaf] RETURNS[LIST OF Leaf] = BEGIN WITH t SELECT FROM l: REF Leaf => { v _ AddVar[t, v]; }; e: REF Expression => { IF e.children = NIL OR e.children.first = NIL THEN ERROR Error[EmptyExpression, "Empty expression."]; SELECT e.op FROM $And => { FOR ch: LIST OF Tree _ e.children, ch.rest WHILE ch # NIL DO v _ AddVar[ch.first, v]; ENDLOOP; }; ENDCASE => GOTO notSOP; }; ENDCASE => ERROR Error[BadPointer, "Tree is malformed, a pointer points to something other than a subtree or a node."]; RETURN[v]; EXITS notSOP => ERROR Error[NotSOP, "Expression is not in Sum-Of-Products form."]; END; ins, outs, pterms: INT _ 0; termList: LIST OF REF PTerm _ NIL; outputNumber: INT _ 0; atomTab: RefTab.Ref _ RefTab.Create[150]; -- maps ATOMS -> input positions tt: TruthTable _ NIL; FOR inp: LIST OF ATOM _ inputs, inp.rest WHILE inp # NIL DO IF ~RefTab.Store[atomTab, inp.first, NEW[INT _ ins]] THEN ERROR Error[DoubleInputs, "Same input appears more than once."]; ins _ ins + 1; ENDLOOP; FOR out: LIST OF Tree _ equations, out.rest WHILE out # NIL DO outs _ outs + 1; ENDLOOP; FOR out: LIST OF Tree _ equations, out.rest WHILE out # NIL DO t: Tree _ out.first; nv: LIST OF Leaf _ NIL; WITH t SELECT FROM l: REF Leaf => { nv _ AddVar[t, NIL]; termList _ CONS[MakeTerm[ins, outs, outputNumber, atomTab, nv], termList]; pterms _ pterms + 1; }; e: REF Expression => { IF e.children = NIL OR e.children.first = NIL THEN ERROR Error[EmptyExpression, "Empty expression."]; SELECT e.op FROM $And => { nv _ AddTerm[t, NIL]; termList _ CONS[MakeTerm[ins, outs, outputNumber, atomTab, nv], termList]; pterms _ pterms + 1; }; $Or => { FOR term: LIST OF Tree _ e.children, term.rest WHILE term # NIL DO nv _ AddTerm[term.first, NIL]; termList _ CONS[MakeTerm[ins, outs, outputNumber, atomTab, nv], termList]; pterms _ pterms + 1; ENDLOOP; }; ENDCASE => GOTO notSOP; }; ENDCASE => ERROR Error[BadPointer, "Tree is malformed, a pointer points to something other than a subtree or a node."]; outputNumber _ outputNumber + 1; ENDLOOP; tt _ NEW[TruthTableRec[pterms]]; tt.numInputs _ ins; tt.numOutputs _ outs; tt.numPTerms _ pterms; FOR i: INT DECREASING IN [0..pterms) DO tt.pterms[i] _ termList.first; termList _ termList.rest; ENDLOOP; RETURN[tt]; EXITS notSOP => ERROR Error[NotSOP, "Expression is not in Sum-Of-Products form."]; END; TTToStream: PUBLIC PROC [tt: TruthTable, out: IO.STREAM] = BEGIN IF tt = NIL THEN ERROR Error[TTIsNil, "NIL truth table."]; FOR i: INT IN [0..tt.numPTerms) DO FOR j: INT IN [0..tt.numInputs+tt.numOutputs) DO IF j = tt.numInputs THEN IO.PutRope[out, " | "]; SELECT tt.pterms[i].bits[j] FROM $One => IO.PutChar[out, '1]; $Zero => IO.PutChar[out, '0]; $NC => IO.PutChar[out, 'x]; ENDCASE => ERROR Error[UnknownTTBit, "Strange bit in truth table"]; ENDLOOP; IO.PutChar[out, '\n]; ENDLOOP; END; BerkeleyTTToStream: PUBLIC PROC [tt: TruthTable, out: IO.STREAM] = BEGIN IF tt = NIL THEN ERROR Error[TTIsNil, "NIL truth table."]; IO.PutF[out, ".i %g\n.o %g\n.p %g\n", IO.int[tt.numInputs], IO.int[tt.numOutputs], IO.int[tt.numPTerms]]; FOR i: INT IN [0..tt.numPTerms) DO FOR j: INT IN [0..tt.numInputs+tt.numOutputs) DO IF j = tt.numInputs THEN IO.PutRope[out, " "]; SELECT tt.pterms[i].bits[j] FROM $One => IO.PutChar[out, '1]; $Zero => IO.PutChar[out, '0]; $NC => IO.PutChar[out, 'x]; ENDCASE => ERROR Error[UnknownTTBit, "Strange bit in truth table"]; ENDLOOP; IO.PutChar[out, '\n]; ENDLOOP; IO.PutF[out, ".e\n"]; END; StreamToTT: PUBLIC PROC [in: IO.STREAM] RETURNS [TruthTable] = BEGIN ins, outs, pterms: INT _ 0; termList: LIST OF REF PTerm _ NIL; r: Rope.ROPE; tTable: TruthTable; haveDotE: BOOL _ FALSE; eof: BOOL _ FALSE; DO index: INT; term: REF PTerm; r _ IO.GetLineRope[in ! IO.EndOfStream => {eof _ TRUE; CONTINUE}]; IF eof THEN EXIT; IF Rope.Length[r] < 1 OR Rope.Fetch[r, 0] = '# THEN LOOP; IF pterms = 0 THEN { numBits: INT _ 0; FOR j: INT IN [0..Rope.Length[r]) DO ch: CHAR _ Rope.Fetch[r, j]; SELECT ch FROM '| => ins _ numBits; ' , '\n, '\t => LOOP; '0, '1, '., '-, 'x, 'X => numBits _ numBits + 1; ENDCASE => { ERROR Error[SyntaxError, Rope.Cat["Bad character ", Convert.RopeFromChar[ch], " in truth table."]]; }; ENDLOOP; outs _ numBits - ins; IF ins < 1 OR outs < 1 THEN GOTO shortTerm; }; term _ NEW[PTerm[ins + outs]]; index _ 0; FOR j: INT IN [0..Rope.Length[r]) DO ch: CHAR _ Rope.Fetch[r, j]; SELECT ch FROM '| => { IF ins < index THEN GOTO longTerm ELSE { IF ins > index THEN GOTO shortTerm; }; LOOP; }; ' , '\n, '\t => LOOP; '0 => { IF index >= ins + outs THEN GOTO longTerm; term.bits[index] _ $Zero; }; '1 => { IF index >= ins + outs THEN GOTO longTerm; term.bits[index] _ $One; }; '., '-, 'x, 'X => { IF index >= ins + outs THEN GOTO longTerm; term.bits[index] _ $NC; }; ENDCASE => { ERROR Error[SyntaxError, Rope.Cat["Bad character ", Convert.RopeFromChar[ch], " in truth table."]]; }; index _ index + 1; ENDLOOP; IF index # ins + outs THEN GOTO shortTerm; termList _ CONS[term, termList]; pterms _ pterms + 1; ENDLOOP; IF pterms < 1 THEN GOTO earlyEnd; tTable _ NEW[TruthTableRec[pterms]]; tTable.numInputs _ ins; tTable.numOutputs _ outs; tTable.numPTerms _ pterms; FOR i: INT DECREASING IN [0..pterms) DO tTable.pterms[i] _ termList.first; termList _ termList.rest; ENDLOOP; RETURN[tTable]; EXITS earlyEnd => ERROR Error[SyntaxError, "Truth table ends early."]; longTerm => ERROR Error[SyntaxError, "Product term is too long."]; shortTerm => ERROR Error[SyntaxError, "Product term is too short."]; END; BerkeleyStreamToTT: PUBLIC PROC [in: IO.STREAM] RETURNS [TruthTable] = BEGIN ins, outs, pterms: INT _ 0; termList: LIST OF REF PTerm _ NIL; r: Rope.ROPE; tTable: TruthTable; haveDotE: BOOL _ FALSE; eof: BOOL _ FALSE; GetInt: PROC [r: Rope.ROPE, pos: INT] RETURNS [INT] = BEGIN i: INT; bad: BOOL _ FALSE; i _ Convert.IntFromRope[Rope.Substr[r, pos] !Convert.Error => bad _ TRUE]; IF bad THEN ERROR Error[SyntaxError, "Could not understand one of the '.' directives."]; RETURN[i]; END; DO index: INT; done: BOOL _ FALSE; term: REF PTerm; DO r _ IO.GetLineRope[in ! IO.EndOfStream => {eof _ TRUE; CONTINUE}]; IF eof THEN EXIT; IF Rope.Length[r] < 1 OR Rope.Fetch[r, 0] = '# THEN LOOP; IF Rope.Fetch[r, 0] = '. OR Rope.Fetch[r, 0] = '- THEN { SELECT Rope.Fetch[r, 1] FROM 'i => IF ins < 1 THEN ins _ GetInt[r, 2] ELSE GOTO directive; 'o => IF outs < 1 THEN outs _ GetInt[r, 2] ELSE GOTO directive; 'p => NULL; 'e => done _ TRUE; ENDCASE => GOTO directive; } ELSE EXIT; ENDLOOP; IF done THEN EXIT; IF ins < 1 OR outs < 1 THEN ERROR Error[SyntaxError, "Bad number of inputs or outputs."]; term _ NEW[PTerm[ins + outs]]; index _ 0; FOR j: INT IN [0..Rope.Length[r]) DO ch: CHAR _ Rope.Fetch[r, j]; SELECT ch FROM ' , '\n, '\t => LOOP; '0 => { IF index >= ins + outs THEN GOTO longTerm; term.bits[index] _ $Zero; }; '1 => { IF index >= ins + outs THEN GOTO longTerm; term.bits[index] _ $One; }; '-, 'x, 'X => { IF index >= ins + outs THEN GOTO longTerm; term.bits[index] _ $NC; }; ENDCASE => { ERROR Error[SyntaxError, Rope.Cat["Bad character ", Convert.RopeFromChar[ch], " in truth table."]]; }; index _ index + 1; ENDLOOP; IF index # ins + outs THEN GOTO shortTerm; termList _ CONS[term, termList]; pterms _ pterms + 1; ENDLOOP; IF pterms < 1 THEN GOTO earlyEnd; tTable _ NEW[TruthTableRec[pterms]]; tTable.numInputs _ ins; tTable.numOutputs _ outs; tTable.numPTerms _ pterms; FOR i: INT DECREASING IN [0..pterms) DO tTable.pterms[i] _ termList.first; termList _ termList.rest; ENDLOOP; RETURN[tTable]; EXITS earlyEnd => ERROR Error[SyntaxError, "Truth table ends early."]; longTerm => ERROR Error[SyntaxError, "Product term is too long."]; shortTerm => ERROR Error[SyntaxError, "Product term is too short."]; directive => ERROR Error[SyntaxError, "Could not understand one of the '.' directives."]; END; END. jFile: BoolOpsImplA.mesa Copyright c 1984 by Xerox Corporation. All rights reserved. Created by: Mayo, July 16, 1984 4:44:25 pm PDT Last Edited by: Mayo, August 30, 1984 6:07:55 pm PDT Bertrand Serlet May 27, 1986 3:17:13 pm PDT -- ISNAOLREN -- duonrPPnu -- btd aadl Convert a rope into an expresion tree. Use an operator precedence parser to parse our expressions: (straight out of Aho & Ullman) E -> id E -> NOT E E -> (E) E -> E AND E E -> E OR E -- return the first terminal token on the stack newt.name _ ""; newt.name _ top.name; newt.name _ Rope.Cat[" (", top.name, ")", newt.name]; -- parser design error: two $Nots or more than one operator for a set of variables newt.name _ Rope.Cat[tokenNames[opId], newt.name]; Convert an expression tree into a rope. Perform logical operations on SOP trees to produce another tree in SOP form. -- use DeMorgan's law -- create two lists of things to be ANDed together. -- now form the cross product of the lists -- create one AND term Convert an arbitrary expression tree into sum-of-products form. -- record inputs -- make the product terms -- create the truth table -- get product terms first pterm, count number of inputs and outputs -- fill in bits of product term -- make the truth table from our list of product terms -- get product terms -- make the truth table from our list of product terms Κe˜– "Cedar" stylešœ™Jšœ Οmœ1™Jšœžœžœ ˜$Jšžœ žœžœžœ˜"Jšžœ žœžœžœ˜"J˜ Jšœ žœ˜šžœžœžœ žœžœžœžœ˜RJšœžœžœ#˜QJ˜—šžœ˜Jšœ žœ˜%J˜—šžœžœžœ žœžœžœžœ˜RJšœžœžœ#˜QJ˜—šžœ˜Jšœ žœ˜%J˜—Jšžœ˜ Jšžœ˜J˜—J˜J™?š £ œžœžœžœ ž˜:Jšžœžœžœžœ"˜:šžœžœž˜Jšœžœ žœ˜šœžœ˜Jš žœžœžœžœžœžœ-˜ešžœž˜šœ ˜ J–[]šœ˜Jšœ ˜ J˜Jšžœ˜ Jšœ˜—šœ˜J–[]šœžœ˜š žœžœžœžœžœž˜Jšœžœ˜—š žœžœžœžœžœž˜>J˜Jšœžœžœžœ˜šžœžœž˜šœžœ ˜Jšœžœ˜Jšœ žœ;˜JJ˜Jšœ˜—šœžœ˜Jš žœžœžœžœžœžœ-˜ešžœž˜˜ Jšœžœ˜Jšœ žœ;˜JJ˜J˜—˜š žœžœžœžœžœž˜BJšœžœ˜Jšœ žœ;˜JJ˜Jšžœ˜—J˜—Jšžœžœ˜—J˜—Jšžœžœg˜w—Jšœ ˜ Jšžœ˜—J™J™Jšœžœ˜ Jšœ˜Jšœ˜Jšœ˜š žœžœž œžœ žœ˜(J˜J˜Jšžœ˜—Jšžœ˜ J˜šž˜Jšœ žœ=˜L—Jšžœ˜J™—š £ œžœžœžœžœž˜@Jšžœžœžœžœ$˜:šžœžœžœž˜"šžœžœžœ!ž˜0Jšžœžœžœ˜2šžœž˜ Jšœžœ˜Jšœ žœ˜Jšœžœ˜Jšžœžœ3˜C—Jšžœ˜—Jšžœ˜Jšžœ˜—Jšžœ˜J˜—š £œžœžœžœžœž˜HJšžœžœžœžœ$˜:Jšžœ$žœžœžœ˜išžœžœžœž˜"šžœžœžœ!ž˜0Jšžœžœžœ˜/šžœž˜ Jšœžœ˜Jšœ žœ˜Jšœžœ˜Jšžœžœ3˜C—Jšžœ˜—Jšžœ˜Jšžœ˜—Jšžœ˜Jšžœ˜J˜—š £ œžœžœžœžœžœž˜DJšœžœ˜Jš œ žœžœžœ žœ˜"Jšœžœ˜ J˜Jšœ žœžœ˜Jšœžœžœ˜J™šž˜Jšœžœ˜ Jšœžœ˜Jš œžœΠkrΟr œ žœžœ˜BJšžœžœžœ˜Jšžœžœžœžœ˜9Jšœ/™/šžœ žœ˜Jšœ žœ˜šžœžœžœž˜$Jšœžœ˜šžœž˜Jšœ˜Jšœžœ˜Jšœ0˜0šžœ˜ Jšžœ_˜dJ˜——Jšžœ˜—Jšœ˜Jšžœ žœ žœžœ ˜,J˜—J™Jšœžœ˜J˜ šžœžœžœž˜$Jšœžœ˜šžœž˜šœ˜šžœ žœ˜Jšžœ ˜—šžœ˜šžœ ž˜Jšžœ ˜—J˜—Jšžœ˜J˜—Jšœžœ˜˜Jšžœžœžœ ˜*J˜J˜—˜Jšžœžœžœ ˜*J˜J˜—˜Jšžœžœžœ ˜*J˜J˜—šžœ˜ Jšžœ_˜dJ˜——J˜Jšžœ˜—Jšžœžœžœ ˜*Jšœ žœ'˜6Jšžœ˜—J™6Jšžœ žœžœ ˜!Jšœ žœ˜$J˜J˜Jšœ˜š žœžœž œžœ žœ˜(J˜"J˜Jšžœ˜—Jšžœ ˜šž˜Jšœ žœ/˜@Jšœ žœ1˜BJšœ žœ2˜D—Jšžœ˜J˜—š £œžœžœžœžœžœž˜LJšœžœ˜Jš œ žœžœžœ žœ˜"Jšœžœ˜ J˜Jšœ žœžœ˜Jšœžœžœ˜J™š £œžœ žœžœžœžœž˜;Jšœžœ˜Jšœžœžœ˜JšœDžœ˜JJšžœžœžœG˜XJšžœ˜ Jšžœ˜J˜—J™šž˜Jšœžœ˜ Jšœžœžœ˜Jšœžœ˜šž˜Jš œžœ₯¦ œ žœžœ˜BJšžœžœžœ˜Jšžœžœžœžœ˜9šžœžœžœ˜8šžœž˜Jš œžœ žœžœžœ ˜=Jš œžœ žœžœžœ ˜?Jšœžœ˜ Jšœ žœ˜Jšžœžœ ˜—J˜—šž˜Jšžœ˜—Jšžœ˜—Jšžœžœžœ˜Jšžœ žœ žœžœ8˜YJšœžœ˜J˜ šžœžœžœž˜$Jšœžœ˜šžœž˜Jšœžœ˜˜Jšžœžœžœ ˜*J˜J˜—˜Jšžœžœžœ ˜*J˜J˜—˜Jšžœžœžœ ˜*J˜J˜—šžœ˜ Jšžœ_˜dJ˜——J˜Jšžœ˜—Jšžœžœžœ ˜*Jšœ žœ'˜6Jšžœ˜—J™6Jšžœ žœžœ ˜!Jšœ žœ˜$J˜J˜Jšœ˜š žœžœž œžœ žœ˜(J˜"J˜Jšžœ˜—Jšžœ ˜šž˜Jšœ žœ/˜@Jšœ žœ1˜BJšœ žœ2˜DJšœ žœG˜Y—Jšžœ˜J˜—Jšžœ˜——…—EΨh§