home *** CD-ROM | disk | FTP | other *** search
-
- %%%%%%%%%%%%%% auto generated declarations end here %%%%%%%%%%%%%%%%%%%
-
- :- module frame.
-
- /*--------------------------------------------------------------------------*/
- /*- FRAME LIBRARY -*/
- /*--------------------------------------------------------------------------*/
-
- /* by Chris Jay
- Instant Recall
- 5900 Walton Rd.
- Bethesda, Md. 20817
- (301) 530-0898
-
- This is a library of Prolog predicates for FRAMES.
- It is written in Arity Prolog, but uses few if any
- nonstandard features.
-
- For a discussion of frames in Prolog, see Chris Jay's
- "Expert's Toolbox" column in AI Expert Magazine.
-
- Instant Recall is the publisher of Prolog Tools, a source
- code library for Prolog programmers. Instant Recall also
- develops custom applications in Prolog.
-
- */
-
-
- /*--------------------------------------------------------------------------*/
- /*- COMPILER DECLARATIONS -*/
- /*--------------------------------------------------------------------------*/
- /*
-
- GENERAL DOCUMENTATION
-
- TYPED AND UNTYED FRAMES
-
- A typed frame is of the form
-
- TYPE( SLOT_LIST).
-
- An untyped frame is of the form
-
- SLOT_LIST.
-
- The predicates in this module are designed to work
- whether you pass them typed or untyped frames.
-
- */
- /*
- :- module frame.
-
- :- public
- test / 0 ,
- add_slot / 4 ,
- frame_slot_val / 3 ,
- test_display / 0 ,
- slot_intersect / 1 ,
- slot_intersect_with_unify / 1 ,
- field_display / 2 ,
- frame_intersect_with_unify / 3 ,
- slot_display / 2 ,
- slot_unify / 1 ,
- update_frame_slot_val / 4 .
-
- :- visible
- test / 0 ,
- add_slot / 4 ,
- frame_slot_val / 3 ,
- test_display / 0 ,
- slot_intersect / 1 ,
- slot_intersect_with_unify / 1 ,
- field_display / 2 ,
- frame_intersect_with_unify / 3 ,
- slot_display / 2 ,
- slot_unify / 1 .
-
-
-
- :- extrn trace_message / 1.
-
- */
- /*--------------------------------------------------------------------------*/
- /*- EXAMPLES OF FRAMES -*/
- /*--------------------------------------------------------------------------*/
- /* Here are some examples of frames, which illustrate the syntax of frames,
- and how they can be used to describe a complex object.
- */
-
- % /* This is a sample frame */
- % /* describing a resistor */
- % part([part_number : r0505x,
- % class : resistor,
- % value : ohms(1000),
- % rating : watts(0.5),
- % tolerance : percent(5)]).
- %
- % /* Sample frame describing a */
- % /* capacitor */
- % part([part_number : c10elx,
- % class : capacitor,
- % subclass : electrolytic,
- % value : microfarads(100),
- % rating : voltage(125),
- % tolerance : percent(10)]).
- %
- %
- % /* This sample frame */
- % /* partially describes an I.C. */
- % part([part_number : lm309,
- % class : ic,
- % device : set([op_amp]),
- % devices_on_chip : 4, /* Number of op amps on the chip */
- % pins : 16, /* Number of pins */
- %
- % /* Subframes describing each pin: */
- %
- % pin(1): pin([type : set([voltage_supply, positive]),
- % milliamps : [60, 120],
- % volts : [9, 14]
- % ]),
- % pin(2): pin([type : set([voltage_supply, negative]),
- % milliamps : [60, 120],
- % volts : [-9, -14]
- % ]),
- % pin(3): pin([device_number : 1, /* Number of the op amp to which */
- % /* this pin applies */
- % type : set([input, inverting]),
- % volts : [-3, 3],
- % milliamps : [0, 10]
- % ]),
- % pin(4): pin([device_number : 1,
- % type : set([input, non_inverting]),
- % volts : [-3, 3],
- % milliamps : [0, 10]
- % ]),
- % pin(5): pin([device_number : 1,
- % type : set([output]),
- % milliamps : [0, 100],
- % volts : [-7, 7]
- % ])
- % /* The rest of the pins aren't */
- % /* yet described. */
- % ]).
-
-
- /*--------------------------------------------------------------------------*/
- /*- FRAME HANDLING UTILITIES -*/
- /*--------------------------------------------------------------------------*/
-
- /*-------------------- is_frame -------------------------------------------*/
-
- /* This is true if its arg. is a frame, and false otherwise. */
-
- is_frame( Term ) :-
- is_typed_frame( Term).
-
- is_frame( Term ) :-
- is_slot_list( Term ).
-
- /*-------------------- is_typed_frame -------------------------------------*/
-
- /* This is true if its arg. is a typed frame, and false otherwise. */
-
- is_typed_frame( Term ) :-
- % make sure arity is 1
- functor( Term, _, 1),
- arg( 1, Term, X) ,
- is_slot_list(X).
-
-
- /*-------------------- is_slot_list ----------------------------------------*/
-
- /* This predicate succeeds when its argument is a frame slot list.
- */
-
-
- is_slot_list( X ) :- var(X), !, fail.
- is_slot_list( [ _ : _ | X]) :-
- is_slot_list_hlpr(X).
-
- is_slot_list_hlpr([]):-!.
- is_slot_list_hlpr(X):- is_slot_list(X).
-
- /*-------------------- frame_info ------------------------------------------*/
-
- /* frame_info finds the class name and slot list of a frame,
- given the frame itself. (The slot list is a list of
- <slot_name : slot_value> pairs
- */
-
- frame_info(Frame, Class_name, Slot_list):-
- is_typed_frame( Frame ),
- % then find its functor and argument
- Frame =.. [Class_name, Slot_list].
-
-
- frame_info(Frame, untyped, Frame ):-
- is_slot_list( Frame ).
-
-
-
- /*-------------------- frame_slots -----------------------------------------*/
-
- /* frame_slots returns the list of slots in a frame. */
-
- frame_slots( Frame, Slots ) :-
- frame_info( Frame, _ , Slot_list ),
- frame_slots_hlpr( Slot_list, Slots ).
-
- frame_slots_hlpr( [ ] , [ ] ) :- !.
- frame_slots_hlpr( [S : _ | T ] , [ S | T1 ] ) :-
- frame_slots_hlpr( T , T1 ).
-
- /*-------------------- build_untyped_frame ---------------------------------*/
-
- /* build_untyped_frame builds a slot list give a list of slots and a list of
- values. It pairs correspondng list elements. when it runs out of
- either slots or values, it quits, returning the pairs built.
-
- Examples
-
- Call : build_untyped_frame( [ 1, 2, 3], [ a, b, c], X ).
- Return : X = [ 1 : a, 2 : b, 3 : c ]
-
- Call : build_untyped_frame( [ 1, 2 ], [ a, b, c], X ).
- Return : X = [ 1 : a, 2 : b ]
-
- */
-
- build_untyped_frame( [] , _, [] ) :- !.
-
- build_untyped_frame( _, [] , [] ) :- !.
-
- build_untyped_frame( [ Slot | Slots ] ,
- [ Val | Vals ] ,
- [ Slot : Val | Rest ] ) :-
- build_untyped_frame( Slots, Vals, Rest).
-
- /*-------------------- frame_slot_val --------------------------------------*/
-
- /* frame_slot_val extracts the value of the slot named Tag from frame Frame.
- It fails if the value is not there.
- */
- frame_slot_val(Tag, Frame, Slot_val):-
- % get slot list
- frame_info(Frame, _, Slot_list),
- % get value of Tag
- slot_list_val(Tag, Slot_list, Slot_val).
-
- % get value when list starts with slot having Tag
- slot_list_val(Tag, [Tag : Slot_val | _], Slot_val):- !.
-
- % recurse
- slot_list_val(Tag, [_ : _ | Slot_list], Slot_val):-
- slot_list_val(Tag, Slot_list, Slot_val).
-
- /*------------ update_frame_slot_val --------------------------------------*/
-
- /* updates the value of a slot in a frame, adding slot if it is not there. */
-
- update_frame_slot_val( Tag, New_val, Old_frame, New_frame) :-
- frame_info( Old_frame, Class_name, Old_slots),
- update_frame_slot_val_hlpr( Tag, New_val, Old_slots, New_slots),
- ( Class_name == untyped,
- !,
- New_frame = New_slots
- ; New_frame =..[ Class_name, New_slots]).
-
- update_frame_slot_val_hlpr( Tag, New_value, [], [ Tag : New_value] ) :- !.
- update_frame_slot_val_hlpr( Tag,
- New_value,
- [ Tag : _ | Rest ],
- [ Tag : New_value | Rest ] ) :- !.
- update_frame_slot_val_hlpr( Tag,
- New_value,
- [ Pair | Rest ],
- [ Pair | Rest2 ] ) :-
- update_frame_slot_val_hlpr( Tag,
- New_value,
- Rest,
- Rest2 ).
-
- /*-------------------- frame_slot_val_with_default -------------------------*/
-
- /* frame_slot_val extracts the value of the slot named Tag from frame Frame.
- It fails if the value is not there.
- */
-
- frame_slot_val_with_default(Tag, Frame, Default, Slot_val):-
- % get slot list
- frame_info(Frame, _, Slot_list),
- % get value of Tag
- slot_list_val(Tag, Slot_list, Default, Slot_val).
-
- % default when there is no more pairs in slot list
- slot_list_val( _, [], Default, Default ):- !.
-
- % get value when list starts with slot having Tag
- slot_list_val(Tag, [Tag : Slot_val | _], _ , Slot_val):- !.
-
- % recurse
- slot_list_val(Tag, [_ : _ | Slot_list], Default, Slot_val):-
- slot_list_val(Tag, Slot_list, Default, Slot_val).
-
- /*-------------------- frame_map -------------------------------------------*/
-
- /* frame_map applies Goal to each Tag : Slot_val pair in Frame.
-
- Here Goal is a Prolog goal with an implicit Tag : Slot_val first
- argument (in the same way that DCGs suppress the input and left-over
- variables of grammar terms).
-
- For example, to write the fields of Frame starting at col. N, we
- could call
-
- frame_map(Frame, field_display( N ))
-
- where field_display is defined like this:
-
- field_display( Tag : Slot_val, N ):-
- logt_tab(N),
- log_write(Tag),
- log_write($ : $),
- log_write( Slot_val),
- log_nl.
- */
-
-
-
- frame_map(Frame, Predicate):-
- % get slot list
- frame_info(Frame, _, Slot_list),
- % map it
- slot_list_map(Slot_list, Predicate).
-
- slot_list_map([Tag : Slot_val | Slot_list], Predicate):-
- /* Call Predicate with */
- /* Tag:Slot_val as its 1st arg.; */
- /* append other arg.'s passed: */
- make_call_term(Predicate, Tag : Slot_val, Term),
- call(Term),
- !,
- slot_list_map(Slot_list, Predicate). % recurse
- slot_list_map([], _).
-
- /*-------------------- frame_display ---------------------------------------*/
-
- /* frame_display 'pretty print's a frame
- */
-
-
- frame_display(Frame):-
- is_frame( Frame ),
- frame_display0(Frame, 0).
-
- frame_display0(Frame, Start_col):-
- frame_info(Frame, Frame_name, _),
- log_nl,
- log_tab(Start_col),
- log_write('FRAME '),
- log_write(Frame_name),
-
- frame_map(Frame, slot_display(Start_col)),
-
- log_nl,
- log_tab(Start_col),
- log_write('END_FRAME'),
- !.
- frame_display0(Frame, _):-
- log_nl,
- log_write('Syntactically invalid frame:'),
- log_nl,
- log_write(Frame).
-
- slot_display(Tag : Slot_val, Start_col):-
- log_nl,
- log_tab(Start_col),
- slot_display0(Tag : Slot_val, Start_col).
-
- slot_display0(Tag : Slot_val, Start_col):-
- is_frame( Slot_val ),
- !,
- log_write(Tag),
- log_write(' :'),
- New_start_col is Start_col + 3,
- frame_display0(Slot_val, New_start_col).
- slot_display0(Tag : Slot_val, _):-
- log_write(Tag : Slot_val).
-
- /*-------------------- slot_remove ----------------------------------------*/
-
- /* slot_remove(Tag,
- Old_slot_list,
- New_slot_list)
-
- removes the slot with Tag from Old_slot_list.
- Puts resulting slot list in New_slot_list.
- Puts value of Tag in Slot_val.
- FAILS if Tag is not a tag in Old_slot_list.
- */
-
- slot_remove( Tag, Old_frame, New_frame) :-
- frame_info( Old_frame, Class_name, Old_slots),
- slot_remove_hlpr( Tag, Old_slots, New_slots),
- ( Class_name == untyped,
- !,
- New_frame = New_slots
- ; New_frame =..[ Class_name, New_slots]).
-
-
- slot_remove_hlpr(Tag, [Tag : _ | Slot_list], Slot_list):-
- !.
- slot_remove_hlpr(Tag,
- [Tag1 : Slot_val1 | Slot_list],
- [Tag1 : Slot_val1 | New_slot_list]):-
- slot_remove_hlpr(Tag, Slot_list, New_slot_list).
-
-
- /*-------------------- remove_if_slot --------------------------------------*/
-
- /* remove_if_slot(Tag,
- Slot_list,
- New_slot_list)
-
- removes the slot with Tag from Slot_list if such a slot exists.
- Puts resulting slot list in New_slot_list.
- New_slot_list = Slot_list when no slot has Tag.
- Always succeeds.
- */
-
-
- remove_if_slot(Tag, Slot_list, New_slot_list):-
- slot_remove(Tag, Slot_list, New_slot_list),
- !.
- remove_if_slot(_, Slot_list, Slot_list).
-
-
- /*-------------------- frame_merge ----------------------------------------*/
-
- /* frame_merge(Frame1,
- Frame2,
- New_frame,
- Slot_merge_pred,
- Slot_append_pred),
-
- merges Frame1 and Frame2 into New_frame, where Slot_merge_pred
- is used to create the output slot.
-
-
- */
-
-
- frame_merge(Frame1, Frame2, New_frame, Slot_merge_pred):-
- /* 2 frames must have same name: */
- frame_info(Frame1, Class_name, Slot_list1),
- frame_info(Frame2, Class_name, Slot_list2),
- /* Merge the tag/slot lists: */
- slot_list_merge(Slot_list1, Slot_list2, New_slot_list, Slot_merge_pred),
- /* Construct the new frame: */
- New_frame =.. [Class_name, New_slot_list],
- !.
-
-
- /*-------------------- slot_list_merge -------------------------------------*/
-
- /* slot_list_merge( Slot_list1,
- Slot_list2,
- New_slot_list,
- Slot_merge_pred )
-
- merges a pair of slot lists, where Slot_merge_pred is used to
- merge the individual slots.
-
-
-
- */
-
- % Terminate the recursion when both input lists are empty
- slot_list_merge( [],
- [],
- [],
- _ ) :- !.
-
- % If both frames contain a slot with Tag, then use Slot_merge_pred
- % to unify them. Make slot_list_merge fail if Slot_merge_pred
- % sets FailFlag to fail. This lets us distinguish between
- % two slot values failing to merge but wanting to go on, and
- % wanting to quit when merge fails on the slot values.
- %
- % In particular, Slot_merge_pred's behavior is related to what
- % slot_list_merge should do in the following way:
- %
- % What slot_list_merge does What Slot_merge_pred does
- % when slot values fail to when slot values fail to
- % merge merge
- %
- % fail set FailFlag to fail and succeed
- %
- % leave out the slot fail
- %
-
- slot_list_merge( [Tag : Slot_val1 | Slot_list1],
- Slot_list2,
- [Tag : New_slot_val | New_slot_list],
- Slot_merge_pred):-
- % create a term which will try to merge the
- % slot with Tag in the slot list in arg. 1, with
- % some frame in the slot list in arg. 2
- make_call_term(Slot_merge_pred,
- [Tag : Slot_val1, Slot_list2, New_slot_val, FailFlag],
- Term),
- call(Term), % call that term
- !,
- % cut, fail if FailFlag == fail
- FailFlag \== fail,
- % remove the slot that merges from the 2nd. slot list
- remove_if_slot(Tag, Slot_list2, New_slot_list2),
- % recurse
- slot_list_merge(Slot_list1,
- New_slot_list2,
- New_slot_list,
- Slot_merge_pred).
-
- % Skip Tag:Slot_val1 if Slot_merge_pred failed.
- slot_list_merge([_ | Slot_list1],
- Slot_list2,
- New_slot_list,
- Slot_merge_pred):-
- slot_list_merge(Slot_list1,
- Slot_list2,
- New_slot_list,
- Slot_merge_pred).
-
- % When the first slot list is exhausted, switch the slot list
- % arguments, and recurse.
- slot_list_merge([],
- [Slot | Slot_list],
- New_slot_list,
- Slot_merge_pred):-
- slot_list_merge([Slot | Slot_list],
- [],
- New_slot_list,
- Slot_merge_pred).
-
-
- /*-------------------- frame_unify -----------------------------------------*/
-
- /* Unifies two frames. Slots that are present in one frame and not in
- another are added to the unification, as if the slot had appeared in
- the frame where it was absent with a variable value.
- */
-
- /* frame_unify */
- frame_unify(Frame1, Frame2, Unification ):-
- % use frame_merge to implement frame_unify
- frame_merge(Frame1, Frame2, Unification, slot_unify).
-
-
-
- % slot_unify([Tag : Slot_val1, Slot_list2, Result, Fail_Flag ])
- %
- % unifies a slot with Tag with a member of a Slot_list2 if possible.
-
- % This first rule applies when Slot_list2 contains a slot with Tag.
- % Result is the unification if it exists.
- % Fail_Flag is set to fail if unification fails, to signal
- % frame_merge to fail.
- slot_unify([Tag : Slot_val1, Slot_list2, Result, Fail_Flag ]):-
- % get value for Tag
- slot_list_val(Tag, Slot_list2, Slot_val2),
- % If slot list 2 contains a slot with Tag,
- % stay in this rule
- !,
- % if these slot values unify
- ( value_unify(Slot_val1, Slot_val2, Result),
- % then stay in this alternative
- !,
- % and tell frame_merge not to fail
- Fail_Flag = true
- % if the slot values do not unify
- % tell frame_merge to fail
- ; Fail_Flag = fail ).
-
- % When the slot in arg. 1 does not appear in the
- % arg. 2 slot list, the result of unify is the slot
- % value in arg. 1
- slot_unify([ _ : Slot_val1, _ , Slot_val1 , _]):- !.
-
-
- /*-------------------- value_unify -----------------------------------------*/
-
- % value_unify unifies slot values
- % Arg 3 is the unification
- % this rule unifies those things that are not frames
- value_unify(Slot_val1, Slot_val2, Slot_val1):-
- Slot_val1 = Slot_val2, !.
-
- % this rule unifies frames
- value_unify(Slot_val1, Slot_val2, Result ):-
- frame_merge(Slot_val1, Slot_val2, Result, slot_unify),
- !.
-
- % set unify slot values that are sets
- value_unify(Slot_val1, Slot_val2, Slot_val1) :-
- set_unify( Slot_val1, Slot_val2 ) ,!.
-
- /*-------------------- add_slot --------------------------------------------*/
-
- /*
- add_slot( Old_frame, Slot, Value, New_frame)
-
- adds [ Slot : Value ] to Old_frame, provided that the new Value of Slot
- unifies with any existing value in Old_frame
- */
-
- add_slot( Old_frame, Slot, Value, New_frame) :-
- frame_unify(Old_frame, [ Slot : Value], New_frame ).
-
- /*-------------------- frame_intersect -------------------------------------*/
-
- /* frame_intersect creates a new frame from 2 existing frames by
- * keeping in slots that appear in both frames with values that unify,
- and letting the value of such slots be the unification of the input
- slot values
- * deleting all other slots, including those where the same tag has
- values in the two frames that don't unify.
- */
-
- frame_intersect(Frame1, Frame2, Intersection ):-
- % do this with frame_merge
- frame_merge(Frame1, Frame2, Intersection, slot_intersect).
-
- slot_intersect([Tag : Slot_val1, Slot_list2, New_slot_val, true ]):-
- slot_list_val(Tag, Slot_list2, Slot_val2), !,
- % merge slot values
- slot_merge0(Slot_val1, Slot_val2, New_slot_val, _ ).
-
- % note that when a slot with Tag is not in Slot_list2,
- % slot_intersect fails. This causes frame_merge to
- % leave the Tag slot out of the computed Intersection
-
- % unify slots if possible
- slot_merge0(Slot_val1, Slot_val2, Slot_val1, _):-
- Slot_val1 = Slot_val2, !.
-
- % intersect slot values that are frames
- slot_merge0(Slot_val1, Slot_val2, New_slot_val, _):-
- frame_merge(Slot_val1, Slot_val2, New_slot_val, slot_intersect),
- !.
-
- % set unify slot values that are sets
- slot_merge0(Slot_val1, Slot_val2, Slot_val1 , _):-
- set_unify( Slot_val1, Slot_val2 ) ,!.
-
-
- /*-------------------- frame_intersect_with_unify --------------------------*/
-
- /* This is similar to frame_intersect, except that if a tag appears in
- both frames, the values must unify. Note that the predicate differs
- only in the use of the fail flag in frame_merge. In frame_intersect
- we let slot unification fail without telling frame_intersect. Here
- we use the fail flag to tell frame_intersect_with_unify to fail.
- */
-
-
- frame_intersect_with_unify(Frame1, Frame2, Intersection ):-
- frame_merge(Frame1, Frame2, Intersection, slot_intersect_with_unify).
-
- % This rule is for when the slot with Tag is in Slot_list2
- % It sets FailFlag according to whether unification succeeds
- slot_intersect_with_unify([Tag : Slot_val1,
- Slot_list2,
- New_slot_val,
- FailFlag ]):-
- slot_list_val(Tag, Slot_list2, Slot_val2), !,
- slot_merge2(Slot_val1, Slot_val2, New_slot_val, FailFlag ).
-
- /*
- % This rule is for when the slot with Tag is not in Slot_list2.
- % It sets FailFlag to true, to tell frame_merge not to fail.
- slot_intersect_with_unify( _, _, _, true) :-!.
- */
-
- % unify slot values if possible
- slot_merge2(Slot_val1, Slot_val2, Slot_val1, true):-
- Slot_val1 = Slot_val2, !.
-
- % or frame intersect_with_unify them
- slot_merge2(Slot_val1, Slot_val2, New_slot_val, true ):-
- frame_merge(Slot_val1,
- Slot_val2,
- New_slot_val,
- slot_intersect_with_unify),
- !.
-
- % set unify slot values that are sets
- slot_merge2(Slot_val1, Slot_val2, Slot_val1 , true):-
- set_unify( Slot_val1, Slot_val2 ) ,!.
-
-
-
- % but tell frame_merge to fail when you can't
- slot_merge2( _, _ , _, fail):- !.
-
-
-
- /*--------------------------------------------------------------------------*/
- /*- UTILITY PREDICATES -*/
- /*--------------------------------------------------------------------------*/
-
- make_call_term(Predicate, First_arg, Call_term):-
- /* Make term by adding First_arg */
- /* as first argument of Predicate */
- /* (other arguments appended) */
- Predicate =.. [Pred_name | Args],
- Call_term =.. [Pred_name, First_arg | Args].
-
- /* Remove E from list: */
- member_remove(E, [E | T], T):-
- !.
- member_remove(E, [H | T], [H | L]):-
- member_remove(E, T, L).
- /* Remove E from list, always */
- /* succeed: */
- remove_if_member(E, L, NewL):-
- member_remove(E, L, NewL),
- !.
- remove_if_member(_, L, L).
-
-
- /* Set handling predicates: */
- set_unify(set([H | T]), set(L2)):-
- member_remove(H, L2, NewL2),
- set_unify(set(T), set(NewL2)).
- set_unify(set([]), set([])).
-
-
-
- /*--------------------------------------------------------------------------*/
- /*- TEST PREDICATES -*/
- /*--------------------------------------------------------------------------*/
- /*
- trace_message(X) :- var(X), !, write(X), nl.
- trace_message([H|T]) :- !, writeq(H), trace_message(T).
- trace_message([]) :- nl,!.
- trace_message(X) :- trace_message([X]),!.
- */
-
- % f(part(X)):- part(X). /* Include part frames in test */
-
-
- % test_display:- /* test frame_display */
- % f(Frame),
- % frame_display(Frame),
- % fail.
- % test_display.
-
-
-
-
- % test_unify:-
- % New_pin_frame = part([part_number : lm309,
- % class : ic,
- % /* Append info. to 'type' slot */
- % /* for pins 3 and 4: */
- % pin(3): pin([type : set([high_gain])]),
- % pin(4): pin([type : set([high_gain])]),
- % /* Add new pin descr. for pin 8: */
- % pin(8): pin([device_number : 2,
- % type : set([output]),
- % milliamps : [0, 100],
- % volts : [-7, 7]
- % ])
- % ]),
- % !,
- % f(Frame),
- % frame_unify(Frame,
- % New_pin_frame,
- % New_frame),
- % frame_display(New_frame).
-
-
- % % test of frame predicates
- % testpred :-
- % Frame = part([part_number : r0505x,
- % class : resistor,
- % value : ohms(1000),
- % rating : watts(0.5),
- % tolerance : percent(5)]),
- % trace_message([$Frame = $, Frame]),
- % trace_message([$calling frame_info$]),
- % frame_info(Frame, Class_name, Slot_list),
- % trace_message([$Class_name = $, Class_name]),
- % trace_message([$Slot_list = $, Slot_list ]),
- % trace_message([$calling frame_map$]),
- % frame_map(Frame, field_display( 10)),
- % trace_message([$calling frame_display:$]),
- % frame_display(Frame),
- % trace_message([$calling slot_remove:$]),
- % slot_remove(value,
- % Slot_list,
- % New_slot_list),
- % trace_message([$Slot_val = $, Slot_val]),
- % trace_message([$New_slot_list = $, New_slot_list ]),
- % trace_message([$calling remove_if_slot, Tag = foo:$]),
- % remove_if_slot(foo,
- % Slot_list,
- % New_slot_list2),
- % trace_message([$New_slot_list2 = $, New_slot_list2 ]),
- % Frame1 = part([part_number : X,
- % class : resistor,
- % value : ohms(1000),
- % rating : watts(Y),
- % tolerance : percent(5)]),
- % Frame2 = part([part_number : 222,
- % class : Z,
- % value : ohms(W),
- % rating : watts(5),
- % tolerance2 : percent(5)]),
- % trace_message([$calling frame_unify Frame1 = $]),
- % frame_display( Frame1 ),
- % trace_message([$calling frame_unify Frame2 = $]),
- % frame_display( Frame2 ),
- % frame_unify(Frame1, Frame2, Unify ),
- % trace_message([$Unify = $]),
- % frame_display( Unify ),
- % trace_message([$calling frame_intersect $]),
- % frame_intersect(Frame1, Frame2, Intersect ),
- % trace_message([$Intersect = $, Intersect]),
- % Frame1a = part([part_number : XX,
- % class : resistor,
- % value : ohms(1000),
- % rating : watts(YY),
- % tolerance : percent(5)]),
- % Frame2a = part([part_number : 222,
- % class : Z,
- % value : ohms(W),
- % rating : watts(5),
- % tolerance2 : percent(5)]),
- % trace_message(
- % [$calling frame_intersect_with_unify Frame1a = $]),
- % frame_display( Frame1a ),
- % frame_intersect_with_unify( Frame1a, Frame2a, U_intersect ),
- % trace_message([$U_intersect = $]),
- % frame_display( U_intersect ).
-
-
- % test_merge:-
- % New_pin_frame = part([part_number : lm309,
- % class : ic,
- % /* Append info. to 'type' slot */
- % /* for pins 3 and 4: */
- % pin(3): pin([type : set([high_gain])]),
- % pin(4): pin([type : set([high_gain])]),
- % /* Add new pin descr. for pin 8: */
- % pin(8): pin([device_number : 2,
- % type : set([output]),
- % milliamps : [0, 100],
- % volts : [-7, 7]
- % ])
- % ]),
- % !,
- % f(Frame),
- % frame_unify( Frame,
- % New_pin_frame,
- % New_frame),
- % frame_display(New_frame).
-
-
-
- % disktest :-
- % stdout( testfile, testpred).
- %
- % % used in test
- % field_display( Tag : Slot_val, N ):-
- % tab(N),
- % write(Tag),
- % write($ : $),
- % write( Slot_val),
- % nl.
-
-
- /*--------------------------------------------------------------------------*/
- /*- END OF LISTING -*/
- /*--------------------------------------------------------------------------*/