<div class="notebook open-fullscreen"> <div class="nb-cell markdown" name="md1"> # Rules as Code Demonstration in SWISH and s(CASP) Rules as Code is a movement in the public service to take advantage of the opportunities presented by encoding legislative and regulatory requirements apart from other kinds of knowledge. This SWISH notebook is a demonstration of how to "do" Rules as Code in SWISH, with the s(CASP) module for SWI-Prolog. It uses the example of an encoding of [Rule 34 of Singapore's Legal Profession (Professional Conduct) Rules](https://sso.agc.gov.sg/SL/LPA1966-S706-2015?ProvIds=P13-#pr34-), which describes when a lawyer can and cannot accept an executive appointment inside an organization other than their own firm. That encoding is work that I did at Singapore Management University's Centre for Computational Law as part of its research program. The original version of the encoding, which was used to demonstrate the capability of these tools to detect legislative drafting errors, is [available on GitHub](https://github.com/smucclaw/r34_scasp). A modified version has also been used to power the demonstration of L4-Docassemble, which is also [available on GitHub](https://github.com/smucclaw/l4-docassemble). A video demonstrating L4-Docassemble is [available on YouTube](https://www.youtube.com/watch?v=NEjrV4Wwyh8). </div> <div class="nb-cell markdown" name="md2"> In order to use s(CASP) inside of SWI-Prolog, we need to load the scasp library, which is done with the following command. s(CASP) code also currently generates a lot of error messages, so we use the style_check and set_prolog_flag commands to remove warnings about singleton variables and discontiguous predicate definitions, and missing s(CASP) predicates. </div> <div class="nb-cell program" data-background="true" name="p1"> :- use_module(library(scasp)). :- style_check(-discontiguous). :- style_check(-singleton). :- set_prolog_flag(scasp_unknown, fail). </div> <div class="nb-cell markdown" name="md3"> ## Enabling Defeasibility In order to be able to make statements about which rules override which other rules, and in order to be able to include the defeating relationships in the explanations generated for the user, we need to create an argumentation theory. The argumentation theory implemented below is based on the default argumentation theory implemented in [Flora-2](http://flora.sourceforge.net/)'s defeasibility method, which is described in a paper entitled ["Logic Programming with Defaults and Argumentation Theories"](https://link.springer.com/chapter/10.1007%2F978-3-642-02846-5_35). The user interface for this theory is very simple. The user uses the `according_to/2` predicate to set out what rule has made what conclusion. The user then indicates what conclusions from what rules contradict one another using the `opposes/4` predicate, and indicates which conclusions from which rules override which other conclusions from which other rules using the `overrides/4` predicate. The user can then query the `legally_holds/2` predicate to determine whether a conclusion holds, or is defeated, and why. </div> <div class="nb-cell program" data-background="true" name="p3"> % An implementation of Logic Programming with Defaults and Argumentation Theories % These are the three predicates that the user should use in their code. % they can also be customized to be displayed in a more friendly way, as can the % other predicates. For example, to improve the display you can encode % #pred according_to(R,flies(X)) :: 'according to rule @(R), @(X) flies'. #pred rule(R) :: '@(R) is a rule'. #pred conclusion(C) :: '@(C) is a conclusion'. %#pred according_to(R,C) :: 'according to rule @(R), the conclusion @(C) holds'. #pred overrides(R1,C1,R2,C2) :: 'the conclusion @(C1) from rule @(R1) overrides the conclusion @(C2) from rule @(R2)'. #pred opposes(R1,C1,R2,C2) :: 'the conclusion @(C1) from rule @(R1) conflicts with the conclusion @(C2) from rule @(R2)'. % Oppositions must be stated explicitly, and must be ground at evaluation time. opposes(R1,C1,R2,C2) :- opposes(R2,C2,R1,C1). % A rule is rebutted if it conflicts with another rule, neither is refuted, the rebutting rule is not compromised, and there is no priority between them. #pred rebutted_by(R1,C1,R2,C2) :: 'the conclusion @(C1) from rule @(R1) is rebutted by the conclusion @(C2) from rule @(R2)'. rebutted_by(Rule,Conclusion,Other_Rule,Other_Conclusion) :- according_to(Rule,Conclusion), according_to(Other_Rule,Other_Conclusion), opposes(Rule,Conclusion,Other_Rule,Other_Conclusion), not refuted(Rule,Conclusion), not refuted(Other_Rule,Other_Conclusion), not compromised(Other_Rule,Other_Conclusion), not overrides(Rule,Conclusion,Other_Rule,Other_Conclusion), not overrides(Other_Rule,Other_Conclusion,Rule,Conclusion). % A rule is refuted if there is another rule that conflicts with it and overrides it. #pred refuted_by(R1,C1,R2,C2) :: 'the conclusion @(C1) from rule @(R1) is refuted by the conclusion @(C2) from rule @(R2)'. refuted_by(Rule,Conclusion,Other_Rule,Other_Conclusion) :- opposes(Rule,Conclusion,Other_Rule,Other_Conclusion), overrides(Other_Rule,Other_Conclusion,Rule,Conclusion), according_to(Rule,Conclusion), Rule \= Other_Rule, Conclusion \= Other_Conclusion, according_to(Other_Rule,Other_Conclusion). % A rule is compromised if it is either refuted or defeated. #pred compromised(Rule,Conclusion) :: 'the conclusion @(Conclusion) from rule @(Rule) is compromised'. compromised(Rule,Conclusion) :- refuted_by(Rule,Conclusion,_,_). %% Inserting this rule causes OLON problems. compromised(Rule,Conclusion) :- defeated_by(Rule,Conclusion). % A rule is disqualified if it defeats itself through a cycle of rebuttals or refutations (not disqualifications) #pred defeated_by_closure(R1,C1,R2,C2) :: 'the conclusion @(C1) from rule @(R1) is defeated by closure by the conclusion @(C2) from rule @(R2)'. #pred defeated_by_closure(R,C,R,C) :: 'the conclusion @(C1) from rule @(R1) is self-defeating'. defeated_by_closure(Rule,Conclusion,Other_Rule,Other_Conclusion) :- unsafe_rebutted_by(Rule,Conclusion,Other_Rule,Other_Conclusion). defeated_by_closure(Rule,Conclusion,Other_Rule,Other_Conclusion) :- refuted_by(Rule,Conclusion,Other_Rule,Other_Conclusion). defeated_by_closure(Rule,Conclusion,Other_Rule,Other_Conclusion) :- unsafe_rebutted_by(Rule,Conclusion,Third_Rule,Third_Conclusion), defeated_by_closure(Third_Rule,Third_Conclusion,Other_Rule,Other_Conclusion). defeated_by_closure(Rule,Conclusion,Other_Rule,Other_Conclusion) :- refuted_by(Rule,Conclusion,Third_Rule,Third_Conclusion), defeated_by_closure(Third_Rule,Third_Conclusion,Other_Rule,Other_Conclusion). % Defeat by closure checks for chains of rebuttals and refutations, regardless of whether % the defeating or rebutting rule is defeated or compromised. unsafe_rebutted_by(Rule,Conclusion,Other_Rule,Other_Conclusion) :- according_to(Rule,Conclusion), according_to(Other_Rule,Other_Conclusion), opposes(Rule,Conclusion,Other_Rule,Other_Conclusion), not overrides(Rule,Conclusion,Other_Rule,Other_Conclusion), not overrides(Other_Rule,Other_Conclusion,Rule,Conclusion). #pred disqualified(Rule,Conclusion) :: 'the conclusion @(Conclusion) from rule @(Rule) is disqualified'. disqualified(Rule,Conclusion) :- defeated_by_closure(Rule,Conclusion,Rule,Conclusion). % A rule is defeated if it is refuted or rebutted by a rule that is not compromised, or if it is disqualified. % (A rebutting rule is already not compromsied, the requirement of non-compromise does not apply to refutation) %#pred defeated(Rule,Conclusion) :: 'the conclusion @(Conclusion) from rule @(Rule) is defeated'. #pred defeated_by_disqualification(R1,C1,R2,C2) :: 'the conclusion @(C1) from rule @(R1) is defeated by disqualification by the conclusion @(C2) from rule @(R2)'. #pred defeated_by_rebuttal(R,C,OR,OC) :: 'the conclusion @(C) from rule @(R) is defeated by rebuttal by the conclusion @(OC) from rule @(R)'. #pred defeated_by_refutation(R,C,OR,OC) :: 'the conclusion @(C) from rule @(R) is defeated by refutation by the conclusion @(OC) from rule @(R)'. defeated_by_disqualification(Rule,Conclusion,Rule,Conclusion) :- disqualified(Rule,Conclusion). defeated_by_rebuttal(Rule,Conclusion,Other_Rule,Other_Conclusion) :- Rule \= Other_Rule, Conclusion \= Other_Conclusion, rebutted_by(Rule,Conclusion,Other_Rule,Other_Conclusion). % The ordering of the clauses in the body seems important for whether or not an OLON situation is created. defeated_by_refutation(Rule,Conclusion,Other_Rule,Other_Conclusion) :- refuted_by(Rule,Conclusion,Other_Rule,Other_Conclusion). % A conclusion can be defeated three ways. defeated(R,C) :- R \= OR, C \= OC, opposes(R,C,OR,OC), defeated_by_disqualification(R,C,OR,OC). defeated(R,C) :- R \= OR, C \= OC, opposes(R,C,OR,OC), defeated_by_rebuttal(R,C,OR,OC). defeated(R,C) :- R \= OR, C \= OC, opposes(R,C,OR,OC), defeated_by_refutation(R,C,OR,OC). % a conclusion holds if it is found and not defeated. %#pred legally_holds(R,C) :: 'the conclusion @(C) from rule @(R) ultimately holds'. legally_holds(R,C) :- not defeated(R,C), according_to(R,C). #pred legally_holds(Rule,may(Y,accept,Z)) :: 'it holds in accordance with @(Rule) that @(Y) is permitted to accept @(Z)'. #pred legally_holds(Rule,must_not(Y,accept,Z)) :: 'it holds in accordance with @(Rule) that @(Y) is prohibited from accepting @(Z)'. #pred defeated(Rule,may(Y,accept,Z)) :: 'the conclusion that @(Y) may accept @(Z) from rule @(Rule) is defeated'. #pred defeated(Rule,must_not(Y,accept,Z)) :: 'the conclusion that @(Y) must not accept @(Z) from rule @(Rule) is defeated'. </div> <div class="nb-cell markdown" name="md4"> ## Natural Language Generation The next thing to do is describe the natural langauge version of each of the predicates in use in the encoding. I find that it is useful to keep these together, and in alphabetical order, to avoid accidentally creating duplicates as you go through the encoding. So these would realistically have been drafted as you went through the law, but are now all collected at the top. </div> <div class="nb-cell program" data-background="true" name="p4"> % PREDICATE DEFINITIONS #pred accepts_position_as_representative(A,B,C) :: '@(A) accepts the position @(B) as a representative of @(C)'. #pred according_to(X,described_in_s1(Y)) :: 'according to @(X), @(Y) is described in section 1'. #pred according_to(X,may(Y,accept,Z)) :: 'in accordance with @(X), @(Y) is permitted to accept @(Z)'. #pred according_to(X,must_not(Y,accept,Z)) :: 'in accordance with @(X), @(Y) is prohibited from accepting @(Z)'. #pred as_compensation_for(A,B) :: '@(A) is provided as compensation in respect of @(B)'. #pred associated_with(A,B) :: '@(A) is associated with @(B)'. #pred beneficial_owner_of(X,Y) :: '@(X) is a beneficial owner of @(Y)'. #pred business_entity(X) :: 'in accordance with the r34(9) definition of business entity, @(X) is a business entity'. #pred business_trust(X) :: '@(X) is a business trust'. #pred business(X) :: 'in accordance with the r34(9) definition of business, @(X) is a business'. #pred calling(X) :: '@(X) is a calling'. #pred carries_on(X,Y) :: '@(X) carries on @(Y)'. #pred company(X) :: '@(X) is a company'. #pred conditions_of_second_schedule_satisfied :: 'the conditions of the second schedule are satisfied'. #pred corporation(X) :: '@(X) is a corporation'. %#pred defeated(X,Y) :: 'the conclusion from @(X) of @(Y) is defeated'. #pred derogates_from_dignity_of_legal_profession(X) :: '@(X) derogates from the dignity of the legal profession'. #pred described_in_first_schedule(X) :: '@(X) is set out in the first schedule'. #pred described_in_s1(B) :: '@(B) is a business described in 34(1)'. #pred detracts_from_dignity_of_legal_profession(X) :: '@(X) detracts from the dignity of the legal profession'. #pred director_of(X,Y) :: '@(X) is a director of @(Y)'. #pred entitles_holder(X) :: '@(X) entitles the holder to perform executive functions'. #pred -executive_appointment(X) :: '@(X) is not an executive appointment for the purposes of section 34'. #pred executive_appointment(X) :: 'in accordance with the r34(9) definition of executive appointment, @(X) is an executive appointment'. #pred executive_appointment_associated_with_a_business(X,Y) :: '@(X) is an executive appointment associated with the business @(Y)'. #pred executive_appointment_in_a_business_entity(X,Y) :: '@(X) is an executive appointment in the business entity @(Y)'. #pred executive_appointment_in_a_law_practice(X,Y) :: '@(X) is an executive appointment in the law practice @(Y)'. #pred -for_profit(X) :: '@(X) is not for profit'. #pred for_profit(X) :: '@(X) is for profit'. #pred foreign_law_practice(X) :: '@(X) is a foreign law practice'. #pred formal_law_alliance(X) :: '@(X) is a formal law alliance'. #pred in_fourth_schedule(X) :: '@(X) is listed in the fourth schedule'. #pred in_third_schedule(X) :: '@(X) is listed in the third schedule'. #pred in(X,Y) :: '@(X) is in @(Y)'. #pred incompatible_dignity_of_legal_profession(X) :: '@(X) is incompatible with the dignity of the legal profession'. #pred independent_director(X) :: '@(X) is an independent directorship'. #pred institution(X) :: '@(X) is an institution'. #pred involves_paying_commission(X,Y,Z) :: '@(X) involves paying @(Y) to @(Z)'. #pred involves_sharing_fees(X,Y,Z) :: '@(X) involves sharing @(Y) with @(Z)'. #pred joint_law_venture(X) :: '@(X) is a joint law venture'. #pred jurisdiction(X,Y) :: '@(X) is located in @(Y)'. #pred law_practice_in_singapore(X) :: '@(X) is a singapore law practice'. #pred law_practice(X) :: '@(X) is a law practice'. #pred law_related_service(X) :: '@(X) is a law-related service'. #pred legal_owner_of(X,Y) :: '@(X) is a legal owner of @(Y)'. #pred legal_practitioner(X) :: '@(X) is a legal practitioner'. #pred legal_service(X) :: '@(X) is a legal service'. #pred legal_work(X) :: '@(X) is legal work'. #pred llp(X) :: '@(X) is a limited liability partnership'. #pred locum_solicitor(X) :: '@(X) is a locum solicitor'. #pred materially_interferes_with(X,Y,Z) :: '@(X) materially interferes with @(Y) with regard to @(Z)'. #pred may(A,accept,B) :: '@(A) may accept an appoinment to @(B)'. #pred member_of(A,B) :: '@(A) is a member of @(B)'. #pred must_not(A,accept,B) :: '@(A) must not accept @(B)'. #pred must_not(A,participate,B) :: '@(A) is prohibited from participating in @(B)'. #pred non_executive_director(X) :: '@(X) is a non-executive directorship'. #pred owner_and_not_partner_of(Y,Z) :: 'someone who is a legal or beneficial owner of @(Y) is not a sole proprietor, partner, or director of @(Z)'. #pred owner_of(X,Y) :: '@(X) is the legal or beneficial owner of @(Y)'. #pred participation_prohibited(X,Y) :: '@(X) is prohibited from participating in @(Y)'. #pred partner_of(X,Y) :: '@(X) is a partner of @(Y)'. #pred partner_sp_or_director_of(X,Y) :: '@(X) is a partner, sole proprietor, or director of @(Y)'. #pred partnership(X) :: '@(X) is a partnership'. #pred performed_by(A,B) :: '@(A) was performed by @(B)'. #pred position(X) :: '@(X) is a position'. #pred primary_occupation_of(X,Y) :: '@(Y) is the primary occupation of @(X)'. #pred prohibited_business(X) :: '@(X) is a prohibited business'. #pred provides_legal_or_law_related_services(X) :: '@(X) provides legal or law-related services'. #pred provides(A,B) :: '@(A) provides @(B)'. #pred service(X) :: '@(X) is a service'. #pred sole_proprietor_of(X,Y) :: '@(X) is the sole proprietor of @(Y)'. #pred soleprop(X) :: '@(X) is a sole proprietorship'. #pred third_schedule_institution(X) :: '@(X) is an institution listed in the third schedule'. #pred trade(X) :: '@(X) is a trade'. #pred unauthorized(X) :: '@(X) is unauthorised to peform legal work'. #pred unfair(X) :: '@(X) is likely to unfairly attract business in the practice of law'. </div> <div class="nb-cell markdown" name="md6"> ## Encoding of Rule 34 Now we get into the nitty-gritty, and actually encode the legislation. The original text of the legislation is [available here for references](https://sso.agc.gov.sg/SL/LPA1966-S706-2015?ProvIds=P13-#pr34-). We are encoding a slightly amended version. ### 34(1) #### Source ``` Rule 34 34. Executive appointments RULE 34(1) 34.—(1) A legal practitioner must not accept any executive appointment associated with any of the following businesses: ``` #### Encoding Notes Rather than re-encoding this statememt multiple times for the sub-paragraphs, it is included here once, with a predicate defined for when a business is defined in section 1. </div> <div class="nb-cell program" data-background="true" name="p5"> according_to(r34_1,must_not(Actor, accept, Appointment)) :- legal_practitioner(Actor), associated_with(Appointment,Business), business(Business), according_to(Rule,described_in_s1(Business)), executive_appointment(Appointment). % moving executive appointment to the bottom of the list of clauses made the code run. </div> <div class="nb-cell markdown" name="md5"> ### 34(1)(a) #### Source ``` (a) any business which detracts from, is incompatible with, or derogates from the dignity of, the legal profession; ``` #### Encoding Notes Because s(CASP) does not have an "or" structure, the disjunction in this statement becomes three different wasy to conclude that something is described in section 1 (a). Because there is no guidance in the law as to the circumstances under which any of the three requirements would be true, they are encoded as unary predicates over a business, and are expected to be provided by the user. It was possible to encode the dignity of the legal profession as an entity in and of itself, or as a unary predicate `dignity_of/1` over an occupation, and to encode using predicates like `detract/2`, as "the practice of law" is used as an occupation elsewhere in the Rule. But the words "detract", "derogate" and "incompatible with" are not used elsewhere in the Rule. As such the three concepts are implemented as unary predicates over businesses. </div> <div class="nb-cell program" data-background="true" name="p6"> according_to(r34_1_a,described_in_s1(Business)) :- detracts_from_dignity_of_legal_profession(Business), business(Business). according_to(r34_1_a,described_in_s1(Business)) :- incompatible_dignity_of_legal_profession(Business), business(Business). according_to(r34_1_a,described_in_s1(Business)) :- derogates_from_dignity_of_legal_profession(Business), business(Business). </div> <div class="nb-cell markdown" name="md7"> ### 34(1)(b) #### Source ``` (b) Repealed in amendment. ``` #### Encoding Notes In this version of the rules, we have amended them to remove section 1(b) and replace it with a section 1A below. There is therefore no encoding of section 1(b). </div> <div class="nb-cell program" data-background="true" name="p12"> % Repealed in amendment. </div> <div class="nb-cell markdown" name="md8"> ### 34(1)(c) #### Source ``` (c) any business which is likely to unfairly attract business in the practice of law; ``` #### Encoding Notes There is no guidance in the rule as to how to determine whether a business is likely to unfairly attract business in the practice of law. As such that is encoded as a unary predicate over a business, and left as an input. </div> <div class="nb-cell program" data-background="true" name="p7"> according_to(r34_1_c,described_in_s1(X)) :- unfair(X). </div> <div class="nb-cell markdown" name="md9"> ### 34(1)(d) #### Source ``` (d) any business which involves the sharing of the legal practitioner’s fees with, or the payment of a commission to, any unauthorised person for legal work performed by the legal practitioner; ``` #### Encoding Notes Because s(CASP) does not have an "or" operator, this becomes two rules which differ only on the criteria of whether they "involve sharing fees" or "involve paying commission". All of the conditions are left as inputs. </div> <div class="nb-cell program" data-background="true" name="p8"> according_to(r34_1_d,described_in_s1(X)) :- involves_sharing_fees(X,Fees,Recipient), as_compensation_for(Fees,Work), performed_by(Work,Lawyer), legal_work(Work), unauthorized(Recipient). according_to(r34_1_d,described_in_s1(X)) :- involves_paying_commission(X,Fees,Recipient), as_compensation_for(Fees,Work), performed_by(Work,Lawyer), legal_work(Work), unauthorized(Recipient). </div> <div class="nb-cell markdown" name="md10"> ### 34(1)(e) #### Source ``` (e) any business set out in the First Schedule; ``` #### Encoding Notes The first schedule is outside the scope of the encoding, and so this is left as a unary predicate over businesses. </div> <div class="nb-cell program" data-background="true" name="p9"> according_to(r34_1_e,described_in_s1(X)) :- described_in_first_schedule(X). </div> <div class="nb-cell markdown" name="md11"> ### 34(1)(f) #### Source ``` (f) any business which is prohibited by — (i) the Act; (ii) these Rules or any other subsidiary legislation made under the Act; (iii) any practice directions, guidance notes and rulings issued under section 71(6) of the Act; or (iv) any practice directions, guidance notes and rulings (relating to professional practice, etiquette, conduct and discipline) issued by the Council or the Society. ``` #### Encoding Notes The Act, the Rules outside of Rule 34, subsidiary legislation, practice directions, guidance notes, and rulings are all outside the scope of the encoding, and so this entire section is encoded as a unary predicate over businesses and left as an input from the user. </div> <div class="nb-cell program" data-background="true" name="p10"> according_to(r34_1_f,described_in_s1(X)) :- prohibited_business(X). </div> <div class="nb-cell markdown" name="md12"> ### 34(1A) AS AMENDED In this encoding, 34(1A) replaces 34(1)(b) in the original Rule. #### Source ``` 1A: A legal practitioner must not accept any executive appointment that: materially interferes with — (i) the legal practitioner’s primary occupation of practising as a lawyer; (ii) the legal practitioner’s availability to those who may seek the legal practitioner’s services as a lawyer; or (iii) the representation of the legal practitioner’s clients. ``` #### Encoding Notes Note that while the numbering would change in the case of an actual amendment, we retain the use of `r34_1_b` as the name for this rule so as to avoid the need to make additional changes elsewhere in the code, and in associated tests. Because s(CASP) does not have an "or" operator, the three subsections are implemented as three rules with the same conclusion. </div> <div class="nb-cell program" data-background="true" name="p11"> according_to(r34_1_b,must_not(Actor, accept, Appointment)) :- legal_practitioner(Actor), executive_appointment(Appointment), materially_interferes_with(Appointment,practicing_as_a_lawyer,Actor), primary_occupation_of(Actor,practicing_as_a_lawyer). according_to(r34_1_b,must_not(Actor, accept, Appointment)) :- legal_practitioner(Actor), executive_appointment(Appointment), materially_interferes_with(Appointment,availability,Actor). according_to(r34_1_b,must_not(Actor, accept, Appointment)) :- legal_practitioner(Actor), executive_appointment(Appointment), materially_interferes_with(Appointment,representation,Actor). </div> <div class="nb-cell markdown" name="md15"> ### 34(2)(a) #### Source ``` RULE 34(2)(a) (2) Subject to paragraph (1), a legal practitioner in a Singapore law practice (called in this paragraph the main practice) may accept an executive appointment in another Singapore law practice (called in this paragraph the related practice), if the related practice is connected to the main practice in either of the following ways: (a) every legal or beneficial owner of the related practice is the sole proprietor, or a partner or director, of the main practice; ``` #### Encoding Notes "Subject to paragraph (1)" is implemented by stating that this section's conclusion opposes and is overridden by both r34_1 and r34_1_b, which is the new amended section 34(1A) that independently concludes must_not. The requirement that every legal or beneficial owner of the related practice is the sole proprietor or partner or director of the main practice is a universal quantification. All things of type X must also be of type Y. That can be converted to a negation, which is that there are no things of type X that are not type Y. So it is implemented as a predicate called "owner_and_not_partner_of", which accepts the two practices. That in turns is based on two disjunctive clauses that each has multiple rules. The section refers to an executive appointment in a law practice, so that convenience predicate from the definition of executive appointment is used here. </div> <div class="nb-cell program" data-background="true" name="p14"> according_to(r34_2_a,may(LP,accept,EA)) :- legal_practitioner(LP), member_of(LP,Main_Practice), law_practice_in_singapore(Main_Practice), executive_appointment_in_a_law_practice(EA,Other_Practice), law_practice_in_singapore(Other_Practice), Main_Practice \= Other_Practice, not owner_and_not_partner_of(Other_Practice,Main_Practice). opposes(r34_1_b,must_not(LP,accept,EA),r34_2_a,may(LP,accept,EA)). opposes(r34_1,must_not(LP,accept,EA),r34_2_a,may(LP,accept,EA)). overrides(r34_1_b,must_not(LP,accept,EA),r34_2_a,may(LP,accept,EA)). overrides(r34_1,must_not(LP,accept,EA),r34_2_a,may(LP,accept,EA)). owner_of(X,Y) :- legal_owner_of(X,Y). owner_of(X,Y) :- beneficial_owner_of(X,Y). partner_sp_or_director_of(X,Y) :- partner_of(X,Y). partner_sp_or_director_of(X,Y) :- sole_proprietor_of(X,Y). partner_sp_or_director_of(X,Y) :- director_of(X,Y). owner_and_not_partner_of(Y,Z) :- owner_of(X,Y), not partner_sp_or_director_of(X,Z). </div> <div class="nb-cell markdown" name="md16"> ### 34(2)(b) #### Source ``` RULE 34(2)(b) (b) the legal practitioner accepts the executive appointment as a representative of the main practice in the related practice, and the involvement of the main practice in the related practice is not prohibited by any of the following: (i) the Act; (ii) these Rules or any other subsidiary legislation made under the Act; (iii) any practice directions, guidance notes and rulings issued under section 71(6) of the Act; (iv) any practice directions, guidance notes and rulings (relating to professional practice, etiquette, conduct and discipline) issued by the Council or the Society. ``` #### Encoding Notes The pre-amble to section 34(2) is included here and encoded in the same way. The defeating relationship is also specified the same way. All of the elements listed in (i) through (iv) are beyond the scope of this encoding, and so "participation is prohibited" is encoded as a binary input predicate over the two practices. </div> <div class="nb-cell program" data-background="true" name="p15"> according_to(r34_2_b,may(LP,accept,EA)) :- legal_practitioner(LP), member_of(LP,Main_Practice), law_practice_in_singapore(Main_Practice), executive_appointment_in_a_law_practice(EA,Other_Practice), law_practice_in_singapore(Other_Practice), Main_Practice \= Other_Practice, accepts_position_as_representative(LP,EA,Main_Practice), not participation_prohibited(Main_Practice,Other_Practice). % this is a low-fidelity representation of the prohibition. opposes(r34_1,must_not(LP,accept,EA),r34_2_b,may(LP,accept,EA)). opposes(r34_1_b,must_not(LP,accept,EA),r34_2_b,may(LP,accept,EA)). overrides(r34_1,must_not(LP,accept,EA),r34_2_b,may(LP,accept,EA)). overrides(r34_1_b,must_not(LP,accept,EA),r34_2_b,may(LP,accept,EA)). </div> <div class="nb-cell markdown" name="md17"> ### 34(3) #### Source ``` RULE 34(3) (3) Subject to paragraph (1), a legal practitioner may accept an executive appointment in a business entity which provides law-related services. ``` #### Encoding Notes This rule refers specifically to executive appointments in business entities, so that predicate from the definition of executive appointment is used. Law-related service is not defined in the rule, so it is left as as input predicate, as is "provides" and "legal practitioner". The phrase "subject to parapraph (1)" is implemented by noting that the conclusions of paragraph (1) and (1)(b) both conflict with and override the conclusion of this section. It is necessary to include both r34_1 and r_34_1_b due to the fact that we have amended section r_34_1_b to become 34(1A), which now concludes a prohibition on its own. </div> <div class="nb-cell program" data-background="true" name="p16"> according_to(r34_3,may(LP,accept,EA)) :- legal_practitioner(LP), executive_appointment_in_a_business_entity(EA,BE), provides(BE,LRS), law_related_service(LRS). opposes(r34_1,must_not(LP,accept,EA),r34_3,may(LP,accept,EA)). opposes(r34_1_b,must_not(LP,accept,EA),r34_3,may(LP,accept,EA)). overrides(r34_1,must_not(LP,accept,EA),r34_3,may(LP,accept,EA)). overrides(r34_1_b,must_not(LP,accept,EA),r34_3,may(LP,accept,EA)). </div> <div class="nb-cell markdown" name="md18"> ### 34(4) #### Source ``` RULE 34(4) (4) Subject to paragraph (1), a legal practitioner (not being a locum solicitor) may accept an executive appointment in a business entity which does not provide any legal services or law-related services, if all of the conditions set out in the Second Schedule are satisfied. ``` #### Encoding Notes As in 34(3), the phrase "subect to paragraph (1)" is implemented by noting that this rule conflicts with and is overriden by the results of r34_1 and r_34_1_b. The latter needs to be included because we are re-using the number to refer to an amended section 34(1A) that now reaches the conclusion of prohibition on its own. This section also refers to executive appointment in a business entity, so the convenience predicate from the defintion of executive appointment is used. Schedule 2 is out of the scope of the encoding, and from context it is not clear whether it is something that is satisfied per business entity, or globally. As such it has been implemented as a nullary predicate, with the assumption that schedule 2 is, in any given fact scenario, either always or never satisfied. </div> <div class="nb-cell program" data-background="true" name="p17"> according_to(r34_4,may(LP,accept,EA)) :- legal_practitioner(LP), not locum_solicitor(LP), executive_appointment_in_a_business_entity(EA,BE), not provides_legal_or_law_related_services(BE), conditions_of_second_schedule_satisfied. opposes(r34_1,must_not(LP,accept,EA),r34_4,may(LP,accept,EA)). opposes(r34_1_b,must_not(LP,accept,EA),r34_4,may(LP,accept,EA)). overrides(r34_1,must_not(LP,accept,EA),r34_4,may(LP,accept,EA)). overrides(r34_1_b,must_not(LP,accept,EA),r34_4,may(LP,accept,EA)). </div> <div class="nb-cell markdown" name="md19"> ### 34(5) #### Source ``` RULE 34(5) (5) Despite paragraph (1)(b), but subject to paragraph (1)(a) and (c) to (f), a locum solicitor may accept an executive appointment in a business entity which does not provide any legal services or law-related services, if all of the conditions set out in the Second Schedule are satisfied. ``` #### Encoding Notes "Provides legal services or law-related service" is implemented as its own predicate with two rules to represent the disjunction. Provides/2 and legal_service/1 are left as inputs. Because it refers specifically to executive appointments in a business entity, the convenience function from the defintion of business entity is used. Again, conditions of the second schedule are treated as a nullary predicate. It is not clear whether something can be a locum solicitor without being a legal practitioner. For greater certainty, we have added the requirement that the locum solicitor be a legal practitioner, but that may be redundant. The rather complicated defeasibility relationship "despite paragraph (1)(b), but subject to paragraph (1)(a) and (c) to (f)" benefits from the fact that we have refactored 1(b) out of the list into its own section 34(1A). As such, we only need to indicate that this section opposes and overrides 1(b), and opposes and is overridden by 34(1). Note that this is an example of the benefits to isomorphism that arise from using the defeasibility method used here. The text of this section makes the section both superior and subordinate to different other sections. Despite that, it is possible to contain all of that information in a small block of text that implements only 34(5), and no changes need to be made elsewhere in the code. </div> <div class="nb-cell program" data-background="true" name="p18"> according_to(r34_5,may(LP,accept,EA)) :- legal_practitioner(LP), locum_solicitor(LP), executive_appointment_in_a_business_entity(EA,BE), not provides_legal_or_law_related_services(BE), conditions_of_second_schedule_satisfied. opposes(r34_1,must_not(LP,accept,EA),r34_5,may(LP,accept,EA)). opposes(r34_5,may(LP,accept,EA),r34_1_b,must_not(LP,accept,EA)). overrides(r34_1,must_not(LP,accept,EA),r34_5,may(LP,accept,EA)). overrides(r34_5,may(LP,accept,EA),r34_1_b,must_not(LP,accept,EA)). provides_legal_or_law_related_services(BE) :- provides(BE,Serv), legal_service(Serv). provides_legal_or_law_related_services(BE) :- provides(BE,Serv), law_related_service(Serv). </div> <div class="nb-cell markdown" name="md20"> ### 34(6)(a) #### Source ``` RULE 34(6) (6) Except as provided in paragraphs (2) to (5) — (a) a legal practitioner in a Singapore law practice must not accept any executive appointment in another Singapore law practice; and ``` #### Encoding Notes Because the in/2 predicate is used to refer to the relationship between positions and business entities, the relationship between legal practitioners and law firms is modeled instead using member_of/2. The encoding of the rule is straightforward, but the defeasibility statements are complex. This is because paragraphs 2-5 are implemented as 5 different rules in our encoding, and there is currently no simple way to refer to them by a range. So the opposes and overrides statement are repeated 5 times. We again use the convenience predicate set out in the definition of executive appointment. </div> <div class="nb-cell program" data-background="true" name="p19"> according_to(r34_6_a,must_not(LP,accept,EA)) :- legal_practitioner(LP), executive_appointment_in_a_law_practice(EA,Other_Practice), member_of(LP,Own_Practice), law_practice_in_singapore(Own_Practice), law_practice_in_singapore(Other_Practice), Own_Practice \= Other_Practice. opposes(r34_2_a,may(LP,accept,EA),r34_6_a,must_not(LP,accept,EA)). opposes(r34_2_b,may(LP,accept,EA),r34_6_a,must_not(LP,accept,EA)). opposes(r34_3,may(LP,accept,EA),r34_6_a,must_not(LP,accept,EA)). opposes(r34_4,may(LP,accept,EA),r34_6_a,must_not(LP,accept,EA)). opposes(r34_5,may(LP,accept,EA),r34_6_a,must_not(LP,accept,EA)). overrides(r34_2_a,may(LP,accept,EA),r34_6_a,must_not(LP,accept,EA)). overrides(r34_2_b,may(LP,accept,EA),r34_6_a,must_not(LP,accept,EA)). overrides(r34_3,may(LP,accept,EA),r34_6_a,must_not(LP,accept,EA)). overrides(r34_4,may(LP,accept,EA),r34_6_a,must_not(LP,accept,EA)). overrides(r34_5,may(LP,accept,EA),r34_6_a,must_not(LP,accept,EA)). </div> <div class="nb-cell markdown" name="md21"> ### 34(6)(b) #### Source ``` (b) a legal practitioner must not accept any executive appointment in a business entity. ``` #### Encoding Notes This encoding is simple, with the same complication to the defeasibiilty statements as above. The convenience predicate from the definition of executive appointment is used. </div> <div class="nb-cell program" data-background="true" name="p20"> according_to(r34_6_b,must_not(LP,accept,EA)) :- legal_practitioner(LP), executive_appointment_in_a_business_entity(EA,BE). opposes(r34_2_a,may(LP,accept,EA),r34_6_b,must_not(LP,accept,EA)). opposes(r34_2_b,may(LP,accept,EA),r34_6_b,must_not(LP,accept,EA)). opposes(r34_3,may(LP,accept,EA),r34_6_b,must_not(LP,accept,EA)). opposes(r34_4,may(LP,accept,EA),r34_6_b,must_not(LP,accept,EA)). opposes(r34_5,may(LP,accept,EA),r34_6_b,must_not(LP,accept,EA)). overrides(r34_2_a,may(LP,accept,EA),r34_6_b,must_not(LP,accept,EA)). overrides(r34_2_b,may(LP,accept,EA),r34_6_b,must_not(LP,accept,EA)). overrides(r34_3,may(LP,accept,EA),r34_6_b,must_not(LP,accept,EA)). overrides(r34_4,may(LP,accept,EA),r34_6_b,must_not(LP,accept,EA)). overrides(r34_5,may(LP,accept,EA),r34_6_b,must_not(LP,accept,EA)). </div> <div class="nb-cell markdown" name="md22"> ### 34(7) #### Source ``` RULE 34(7) (7) To avoid doubt, nothing in this rule prohibits a legal practitioner from accepting any appointment in any institution set out in the Third Schedule. ``` #### Encoding Notes The phrase "to avoid doubt" is generally used to indicate that it is an interpretive guide, and doesn't change the meaning of the rule. However, the phrase "nothing in this rule prohibits" can reasonably be translated to "this rule permits, and no other part of it overrides that permission". As such, this rule is implemented as a conclusion that a legal practitioner can accept a position in an institution listed in the third schedule. The third schedule itself if outside the scope of the encoding, so whether or not the institution is in the third schedule is left as a unary input predicate over the institution. To represent the strictness of the conclusion, we might also have encoded a negation of any override statement with regard to this conclusion, for instance `:- overrides(_,_,r34_7,may(LP,accept,P)).` But that constraint is ommitted for reasons of efficiency. </div> <div class="nb-cell program" data-background="true" name="p21"> according_to(r34_7,may(LP,accept,P)) :- legal_practitioner(LP), position(P), institution(I), in(P,I), in_third_schedule(I). </div> <div class="nb-cell markdown" name="md23"> ### 34(8) #### Source ``` (8) To avoid doubt, this rule does not authorise the formation of, or regulate — (a) any related practice referred to in paragraph (2); or (b) any business entity referred to in paragraph (3), (4) or (5). ``` #### Encoding Notes This provision is an interpretive guide, but does not actually change the semantic meaning of any of the provisions in the Rule. If this section did not exist, nothing about paragraphs 2, 3, 4, or 5 would have the proscripted effect. The phrase "to avoid doubt" seems to suggest that some doubt in that regard is possible, but if so I don't know why. No effort is made to encode 34(8), here. </div> <div class="nb-cell program" data-background="true" name="p22"> % Not encoded. </div> <div class="nb-cell markdown" name="md24"> ### 34(9) "Definitions" #### Source ``` DEFINITIONS (9) In this rule and the First to Fourth Schedules — ``` #### Encoding Notes The restriction of the definitions to the scope of "this rule" is implied by the scope of the encoding. While it might be relevant if this encoding was combined with others, that is not the inteded use case, and so we don't accommodate for it, here. It is also not clear how the semantic meaning could be implemented except to encode the definitions below using predicates in the nature of `business_as_defined_in_rule_34/1`, and then use that predicate in the place of `business/1` above. The schedules are outside of the scope of the encoding. Therefore there is no meaning here to encode. </div> <div class="nb-cell program" data-background="true" name="p23"> % Not encoded </div> <div class="nb-cell markdown" name="md25"> ### 34(9) definition of "business" #### Source ``` “business” includes any business, trade or calling in Singapore or elsewhere, whether or not for the purpose of profit, but excludes the practice of law; ``` #### Encoding Notes Defining businesses as businesses is circular, but it is possible to reflect that interpretation in s(CASP) without breaking things, so we do so. Both "in Singapore or elsewhere" and "whether or not for the purpose of profit" create binary criteria, both of which satisfy the rule. As such they are effectively meaningless. Because s(CASP) does not have an "or" operator, "business, trade, or calling" becomes three different rules, each of which includes the exclusion of the practice of law from its operation. Trades and callings are input predicates, and arguably so is business/1, though it can be derived. </div> <div class="nb-cell program" data-background="true" name="p24"> business(X) :- trade(X), X \= practice_of_law. business(X) :- calling(X), X \= practice_of_law. business(X) :- business(X), X \= practice_of_law. % circular much? </div> <div class="nb-cell markdown" name="md26"> ### 34(9) definition of "business entity" #### Source ``` “business entity” — (a) includes any company, corporation, partnership, limited liability partnership, sole proprietorship, business trust or other entity that carries on any business; but (b) excludes any Singapore law practice, any Joint Law Venture, any Formal Law Alliance, any foreign law practice and any institution set out in the Third Schedule; ``` #### Encoding Notes For convenience, a predicate law_practice_in_singapore/1 is defined based on the law_practice/1 and jurisdiction/2 predicates. Because s(CASP) does not provide a disjunction operator, the list "company, corporation, partnership, llp, sole proprietorship, business trust, or other entity" disjunctive list is converted into 7 different rules. Each of those 7 includes the requiements of subections (b). It is not terribly clear from the drafting whether it was intended that the requirement of carrying on a business applies to all the elements of the list, or only the final element of the list. I have decided to encode it as though it applies to all of the elements of the list. There is no guidance in the rule for what does or does not qualify as an "entity." It is also probably reasonable to assume that anything that is capable of carrying on a business is an "entity". For that reason the "other entity" version of this rule does not actually test for that requirement. </div> <div class="nb-cell program" data-background="true" name="p25"> business_entity(X) :- carries_on(X,Y), business(Y), company(X), not law_practice_in_singapore(X), not joint_law_venture(X), not formal_law_alliance(X), not foreign_law_practice(X), not third_schedule_institution(X). business_entity(X) :- carries_on(X,Y), business(Y), corporation(X), not law_practice_in_singapore(X), not joint_law_venture(X), not formal_law_alliance(X), not foreign_law_practice(X), not third_schedule_institution(X). business_entity(X) :- carries_on(X,Y), business(Y), partnership(X), not law_practice_in_singapore(X), not joint_law_venture(X), not formal_law_alliance(X), not foreign_law_practice(X), not third_schedule_institution(X). business_entity(X) :- carries_on(X,Y), business(Y), llp(X), not law_practice_in_singapore(X), not joint_law_venture(X), not formal_law_alliance(X), not foreign_law_practice(X), not third_schedule_institution(X). business_entity(X) :- carries_on(X,Y), business(Y), soleprop(X), not law_practice_in_singapore(X), not joint_law_venture(X), not formal_law_alliance(X), not foreign_law_practice(X), not third_schedule_institution(X). business_entity(X) :- carries_on(X,Y), business(Y), business_trust(X), not law_practice_in_singapore(X), not joint_law_venture(X), not formal_law_alliance(X), not foreign_law_practice(X), not third_schedule_institution(X). business_entity(X) :- carries_on(X,Y), business(Y), not law_practice_in_singapore(X), not joint_law_venture(X), not formal_law_alliance(X), not foreign_law_practice(X), not third_schedule_institution(X). law_practice_in_singapore(X) :- law_practice(X), jurisdiction(X,singapore). </div> <div class="nb-cell markdown" name="md27"> ### 34(9) definition of "executive appointment" #### Source ``` “executive appointment” means a position associated with a business, or in a business entity or Singapore law practice, which entitles the holder of the position to perform executive functions in relation to the business, business entity or Singapore law practice (as the case may be), but excludes any non‑executive director or independent director associated with the business or in the business entity; ``` #### Encoding Notes For convenience, three predicates are defined for the three disjunctive options, and three rules are created each requiring only one of the three. Rather than model the relationship between the position and the associated organization repeatedly, we have defined whether it entitles the holder to perform executive functions as a unary predicate. This will be inadequate if, for example, we are trying to encode a situation in which the same position is "in" or "associated with" more than one business, business entity, or Singapore law practice, and whether it is an executive position varies among them. Likewise, whether the position is a non-executive director or independent director is treated as a unary predicate, with out reference to the entity that the position is "in" or "associated with." </div> <div class="nb-cell program" data-background="true" name="p2"> executive_appointment(X) :- executive_appointment_associated_with_a_business(X,Y). executive_appointment(X) :- executive_appointment_in_a_business_entity(X,Y). executive_appointment(X) :- executive_appointment_in_a_law_practice(X,Y). executive_appointment_associated_with_a_business(X,Y) :- position(X), entitles_holder(X), associated_with(X,Y), business(Y), not non_executive_director(X), not independent_director(X). executive_appointment_in_a_business_entity(X,Y) :- position(X), entitles_holder(X), in(X,Y), business_entity(Y), not non_executive_director(X), not independent_director(X). executive_appointment_in_a_law_practice(X,Y) :- position(X), entitles_holder(X), in(X,Y), law_practice(Y), jurisdiction(Y,singapore), not non_executive_director(X), not independent_director(X). </div> <div class="nb-cell markdown" name="md13"> ### Summary of Encoding Now we have encoded Rule 34 in s(CASP), let's take a step back and think about what we did and did not need to do. Unlike in most imperative programming langauges, we did not have to think about how the rules interact with one another, and come up with an algorithm for answering any particular question. Instead, we have just encoded what we know about what the law says. That is easier to do, faster to write, and easier for other people to check our work. Also, we were able to go section-by-section through the rule and convert each section of law into a section of code. That 1:1 correspondence between small sections of law and small sections of code, which I call structural isomorphism, is very important. It means that if a section of the law changes later, we know exactly where in our code we need to go to reflect that change. That massively simplifies maintaining encodings in environments where the rules are changing frequently. It also means that we can divvy-up the work of writing the encodings and reviewing them between different people and expect it to be possible to scale effectively. Long term, those small translations from law to code might enable us to use Rules as Code encodings like this as a rosetta stone to traing machine learning tools to do the translation. The smaller the pieces of the translation, the more effective that is likely to be. What we have done here is not "programming", so much as it is "knowledge representation". We have described the law to the computer, without telling the computer what it is we want to "do" with it. But if you can't do anything with it, what would be the point? So now let's look at what you can do with it. ## Using the Encoding Now that we have our encoding, let's show off what we can do with it! </div> <div class="nb-cell markdown" name="md14"> ### Specific Fact Scenario The simplest thing we can do with the encoding is to describe a specific fact scenario, and ask a specific question. This is the functionality that an application might use if it interviewed a user in order to answer a specific question. Here we encode the scenario that there is a person who works at a firm, and there is a corporation, and a position in that corporation that entitles the holder to exercise executive authority in that corporation. </div> <div class="nb-cell program" name="p26"> % Jill is a legal practitioner whose primary occupation is practicing as a lawyer. legal_practitioner(jill). primary_occupation_of(jill,practicing_as_a_lawyer). % MegaCorp is a corporation with an associated position CEO, which entitles the holder to % exercise executive authority. MegaCorp carries on the trade of widget sales. position(ceo). entitles_holder(ceo). in(ceo,megacorp). corporation(megacorp). business(widget_sales). carries_on(megacorp,widget_sales). trade(widget_sales). % Being CEO of MegaCorp would interfere with anyone's availability to practice as a lawyer. materially_interferes_with(ceo,practicing_as_a_lawyer,_). </div> <div class="nb-cell markdown" name="md37"> Now that we have described a fact scenario, which we might have gotten from a user's answers to questions in an interview tool, we can ask whether it legally holds (that is, a rule concludes it and no other overriding rule disagrees), that Jill must not accept the job of CEO at MegaCorp. </div> <div class="nb-cell query" name="q2"> ? legally_holds(Rule,must_not(jill,accept,ceo)). </div> <div class="nb-cell markdown" name="md28"> When you click on the run arrow in the above query, you will get three things: bindings, an s(CASP) Model, and an s(CASP) justification. The bindings represent the values that need to be inserted into the variables in your query, if any, in order to answer the question. In this case, the only variable was `Rule`. So the first model returned by the query reports that the rule which concludes that Jill may not accept the position of CEO is `r_34_1_b`. The s(CASP) model is just a list of all of the relevant things that are known about the scenario that answers the question, with natural langauge versions of each. The s(CASP) justification is a tree-structured natural langauge explanation of how those things combine to explain the answer. If you click on the arrow next to the justification, and choose "Expand all", you can see the entire tree. This is a natural language explanation, with references to the relevant sections of the law, explaining the legal conclusion. So providing specific facts and answering a specific question is pretty straightforward, and gets you a lot of useful information. But what if we have another question? We can also ask if Jill is allowed to accept the job of ceo, as follows. </div> <div class="nb-cell query" name="q1"> ? legally_holds(Rule,may(jill,accept,ceo)). </div> <div class="nb-cell markdown" name="md29"> ### Asking "Why Not" Questions All that this query tells us is "false." So there are no facts in the database that will lead to the conclusion that Jill is allowed to accept the position. But that is not terribly helpful to the user who wonders "why not?" One of s(CASP)'s unique features is that it creates a virtual "opposite" of the rules that you have have specified, called a "dual", that can be used to answer "why not" questions like this. So if we would like to know why jill is not permitted, we can simply pose a more specific query like this: </div> <div class="nb-cell query" name="q3"> ? not according_to(r34,may(jill,accept,ceo)). </div> <div class="nb-cell markdown" name="md30"> ### Making Decisions with Partial Information s(CASP) also has the ability to allow you to answer questions where you don't know certain facts. This is extremely useful in environments where the user may not have access to all the relevant inputs, or where you want to do some of the calculations before the user has answered all the relevant questions, either to start giving feedback early, or because you don't want to pester them with 100 interview screens. Imagine, for example, that we know all the same facts except that we cannot know whether or not being CEO of MegaCorp interferes with people's availability to practice law. We can express this uncertainty in s(CASP) by using the `#abducible` directive, as shown in the snippet below. </div> <div class="nb-cell program" name="p13"> % Jill is a legal practitioner whose primary occupation is practicing as a lawyer. legal_practitioner(jill). primary_occupation_of(jill,practicing_as_a_lawyer). % MegaCorp is a corporation with an associated position CEO, which entitles the holder to % exercise executive authority. MegaCorp carries on the trade of widget sales. position(ceo). entitles_holder(ceo). in(ceo,megacorp). corporation(megacorp). business(widget_sales). carries_on(megacorp,widget_sales). trade(widget_sales). % We do not know whether or not being CEO of megacorp interferes with anyone's availability to practice as a lawyer. #abducible materially_interferes_with(ceo,practicing_as_a_lawyer,_). </div> <div class="nb-cell markdown" name="md31"> Now we can pose the original question, does it legally hold that jill is prohibited from accepting the position of CEO, like this: </div> <div class="nb-cell query" name="q4"> ? legally_holds(Rule,must_not(jill,accept,ceo)). </div> <div class="nb-cell markdown" name="md32"> ### Analysing Different Models You can see in the explanation of the first model that the answer includes the phrase > it is assumed that ceo materially interferes with practicing_as_a_lawyer with regard to jill indicating that it is possible to reach the conclusion that Jill is prohibited from accepting the job of CEO with MegaCorp, but (in that model) only if you make the assumption of interference. However, if you press "Next" repeatedly, you will find that there are 8 models that answer the question, even though there are only two bindings, rule_34_1_b, and rule_34_6_b. Also, the explanations for the conclusions with regard to rule_34_6_b do not include any assumptions, indicating that even if we remove the abducibility statement, it would still be prohibited. So s(CASP) is effectively telling us "If you assume that there is interference, there are four additional ways to justify the conclusion. But you can also justify the conclusion without interference." In an interactive tool, checking to see whether or not there is already a good answer to the question, without the need for collecting additional information from the user, is extremely valuable. You can use that information to decide when to stop asking questions, and start answering them. Let's try our fact scenario again, with no information about interference, to be sure. </div> <div class="nb-cell program" name="p27"> % Jill is a legal practitioner whose primary occupation is practicing as a lawyer. legal_practitioner(jill). primary_occupation_of(jill,practicing_as_a_lawyer). % MegaCorp is a corporation with an associated position CEO, which entitles the holder to % exercise executive authority. MegaCorp carries on the trade of widget sales. position(ceo). entitles_holder(ceo). in(ceo,megacorp). corporation(megacorp). business(widget_sales). carries_on(megacorp,widget_sales). trade(widget_sales). % We say nothing about material interference. </div> <div class="nb-cell query" name="q5"> ? legally_holds(Rule,must_not(jill,accept,ceo)). </div> <div class="nb-cell markdown" name="md33"> ### Analysing your Rules So we can see that in the absence of information about whether or not being CEO of MegaCorp interfere's with Jill's practice of a lawyer, she is still prohibited from accepting the position under the terms of 34(6)(b). But if you click "Next" on the above query repeatedly, you will see that s(CASP) has come to this conclusion four different ways! Why is that? What does that mean about our law? Well, if we examine the explanation trees closely, we can see that there are two differences. #### Two Different Ways of Being a Business Entity First, MegaCorp is a business entity for two reasons. First, it is a business entity because it is a corporation (and the other criteria apply). Second, it is a business entity because only the other criteria apply. Why would that be? Let's look at the definition we have of "business entity" and how we encoded it. </div> <div class="nb-cell markdown" name="md34"> ``` “business entity” — (a) includes any company, corporation, partnership, limited liability partnership, sole proprietorship, business trust or other entity that carries on any business; but (b) excludes any Singapore law practice, any Joint Law Venture, any Formal Law Alliance, any foreign law practice and any institution set out in the Third Schedule; ``` We have encoded this to mean that something is a business entity if a) it carries on any business, and b) if it falls into one of the categories. One of the categories is "other entity". But we did not have any way of explaining, in terms of the rule, what would constitute an "other entity" or not. And the fact that something carries on business implies that it is an entity. So one of the ways that we encoded the rule doesn't require anything more than that we know the thing carries on a business. Maybe that's a problem with our encoding, or maybe that's a problem with the law. Is there such a thing as something that carries on any business, and isn't an "entity?" If not, why require both? And if any "entity" is sufficient, why bother making the list? Perhaps the legislation should read "includes any entity that carries on any business." In any case, whether it is the fault of the law, or the fault of the encoding, there are two ways to explain that MegaCorp is a business entity. One is that it is a corporation that carries on a business. The other is that it is an "other entity" that carries on a business. #### Two Different Ways of Being a Business The other option comes from the defintion of a business. In two of the models, it says that "widget sales is a business because it is a trade." In the other two, it says that "widget sales is a business" without providing more justification. Why is that happening? Here's the definition of "business" ``` “business” includes any business, trade or calling in Singapore or elsewhere, whether or not for the purpose of profit, but excludes the practice of law; ``` So the law says that something is a business if it is a trade, which widget sales is. And if you look in our fact scenario above, we explicitly said that widget_sales was a business. So the fact that widget_sales is a business is also something that is just known to be true. That might seem like we have done something redundant in our fact scenario. But when using code like this, you may actually already know some of the legal conclusions that are relevant to your question. Maybe you know widget_sales is a business, because the courts decided that years ago. s(CASP) is able to accept that information, and use it. But it uses that on top of whatever other options exist for reaching the same conclusions. Two ways to conclude business entity, multiplied by two ways to conclude business, gives you four models for why Jill is prohibited from accepting the CEO job. So you can see how by encoding your legislation as faithfully as possible in s(CASP), even the *number of answers to a query* can tell you something about your legislation or your encoding that you didn't already know. Even if you aren't using s(CASP) to deploy your software, having modeled it in s(CASP) will tell you things about how it is behaving that would be very difficult to detect in other methods. Because you can see deeper into what your code is doing, your code can be that much more reliable. Encoding and testing in s(CASP) and then deploying with other declarative approaches like SWI-Prolog may be a good quality assurance technique. This sort of analysis also turns out to be a very effective strategy for testing your encodings (or your laws) in the complete absence of facts. ### Running Queries Without Facts What if we took all of the input predicates that s(CASP) needs to calculate something, and made them ALL #abducible? What happens if we just tell s(CASP) to make up a fact scenario that satisfies a query. Can it do that? We can do that with the entire encoding above, but it would be computationally expensive. So let's take a smaller example to start. Let's just ask s(CASP) what are all the ways something could possibly be a "business entity". We start by taking all of the input predicates that are relevant to the query, and making them all abducible. </div> <div class="nb-cell program" name="p28"> #abducible position(X). #abducible entitles_holder(X). #abducible associated_with(X,Y). #abducible non_executive_director(X). #abducible independent_director(X). #abducible in(X,Y). #abducible law_practice(Y). #abducible jurisdiction(X,singapore). #abducible carries_on(X,Y). #abducible company(X). #abducible corporation(X). #abducible partnership(X). #abducible llp(X). #abducible soleprop(X). #abducible business_trust(X). #abducible joint_law_venture(X). #abducible formal_law_alliance(X). #abducible foreign_law_practice(X). #abducible third_schedule_institution(X). #abducible trade(X). #abducible calling(X). #abducible business(X). </div> <div class="nb-cell markdown" name="md35"> Now we can pose a query which in this context, where all the input predicates are abduicble, effectively means "describe all of the fact scenarios in which I might conclude that something is a business entity." </div> <div class="nb-cell query" name="q6"> ? business_entity(X). </div> <div class="nb-cell markdown" name="md36"> If you click the "100" button after the first response (and then wait about 10 seconds), you will see the s(CASP) is able to calculate 42 different factual scenarios in which something would legally qualify as a "business entity" under Rule 34. You can analyse how it got to 42 models, in order to better understand what your law says, or what your encoding says. Or, you can use those 42 models to create an exhaustive set of tests for another piece of software that is supposed to be able to correctly answer the same question. ### Constraints If you look at the explanation for the first answer, you will see phrases like: > X carries on A other than the practice_of_law This is an example of how s(CASP) can use constraints in reaching conclusions. Instead of just referring to the business carried on, it refers always to "A other than the practice of law", maintaining the restriction (constraint) on what value the variable A can hold that will satisfy the query. So the first model is effectively "X is a business entity if it carries on something other than the practice of law, and that something other than the practice of law is a business, and X is a company." </div> <div class="nb-cell markdown" name="md38"> ## Deploying s(CASP) Code SWISH is a convenient environment for writing code and explaining it, and documenting it, and testing it. Once we have an encoding that accurately represents our knowledge of the law, and is capable of answering all the questions we anticipate needing to ask it, what do we do? Well, as an example, SWI-Prolog has exposed a web API at [https://dev.swi-prolog.org/scasp](https://dev.swi-prolog.org/scasp), which accepts an encoding, a query, and some configuration options, and returns the answer from the s(CASP) reasoner either as JSON or in HTML format. The SWI-Prolog dev server is not to be relied on in any real-world application, of course, but the code for creating it is part of the open source s(CASP) implementation in SWI-Prolog, [available on GitHub](https://github.com/JanWielemaker/sCASP), and can be deployed and changed however you would like. Any application that is able to put its data into predicate statements that follow the design of your encoding can then format a query to be posed to that web API, and process the JSON or HTML that it receives in response to display to the user, allowing your encoding to become legal reasoning as a service. ## Conclusion So what does this file demonstrate about Rules as Code? It demonstrates that you can use SWISH notebooks as a way to encode legislation alongside an explanation for the source material being encoded, and the decisions that were made in doing the encoding. It demonstrates that anyone with a web browser has access to a very sophisticated Rules as Code development environment. It demonstrates that you can also use the SWISH notebooks as a way of describing and then writing and running tests against your encoding, either to test the encoding or to test the law itself. It demonstrates that s(CASP) enables you to get natural langauge explanations for the legal conclusions that your code provides. It demonstrates that s(CASP) enables you to ask and usefully answer questions when only some of the input factors are known. It demonstrates that s(CASP) allows you to reverse the logic of your code and answer "why not" queries with no additional work. It demonstrates that s(CASP) can deal intelligently with superior and subordinate clauses in legislation, and can explain which rules were overridden by which other rules. It demonstrates that s(CASP) allows you to go from providing fact scenarios and getting answers to providing answers and getting fact scenarios. That level of flexibility is extremely important for analysis, and for planning tasks. Again, this happens with no additional coding work. And it demonstrates that encoding legislation in s(CASP) is a very intuitive translation, that can proceed section-by-section, without requiring the knowledge engineer to know in advance what question is going to be asked, or to generate any algorithms for calculating the right answers. </div> </div>