principles of obj-2

Upload: scorpress

Post on 06-Jul-2018

231 views

Category:

Documents


0 download

TRANSCRIPT

  • 8/17/2019 Principles of OBJ-2

    1/15

    Principles of OBJ21

    Kokirhi Futatsugi’, Joseph A. Goguen, Jean-Pierre Jouannaud3, and Josk Meseguer

    SRI Intctnational, Menlo Park CA 94025

    and

    Center fnt t.hc Study of Language and Information, Stanford University 94305

    1 Introduction

    0~12 is a functional programming language with an

    underlying formal semantics that is based upon equational

    logic, and an oprtationnl semantics that is based upon

    rewrite rules. Four clsssrs of design principles for 01352 ate

    discussed briefly in this inttoduct,ion, and then in mote

    detail brlnw: (1) motlulntizntion and patnmcteriantion; (2)

    subsorts; (3) implcmcntnt.ion IcBchniquc>s; nd (4) inlrtaction

    and flexibility. WC also

    lrace

    C)II.l history, current shtus,

    and future plans, and give n fairly comp1rl.c OnJ

    bibliography. blast rxnmplc codr hns n-ct,unlly bcbcn un on

    out currclnt OI%.JZ ntcrprc,t (‘r.

    1.X Modules and Generics

    I key ORJ? principle is the systclmntic use of pnrnmot.rtizrd

    (gcnctic) modules . Encapsulating trlntrd code mnkrs it

    more rrusablr, and grnetics at? rvon more tcusablP, since

    thry can br ‘tuned’ for a vnrirty of npplicat.ions by

    choosing differcsnt patam rtrr valurs; motrovrt, debugging,

    ruain(c*nancc, tradnbilitp and portability nrr nil rnhnnccd.

    The interface drclarations of OIL12 genetics arc not purely

    syntactic, likr Ada’s4; .mstcnd, they may cnnt.ain srmant.ic

    ‘Supported in part

    by Office of NWR Ikwarch Cnntracl No.

    N00014-82-C-0333, National Science Foundation Grant No.

    MCS8’701380 and a gift from the Syrlcm Development Foundation.

    2

    Elrctrotechnical Laboratory, l-1-4 Umtwmo, Sakura, Niihari,

    lbaraki 305. Japan; work performed white on leave at SRI.

    3

    GRIN, Ca mpus S cientiliq ue. BP 239, 54506 Vandoeuvre-les-N ancy

    Cedex, France; work performed while on lcavr at SRI and CSI.1.

    4Ada is a registered trademark of the U.S. Government (Ada Joint

    Program Office) and is defined by 171.

    Permission to copy without fee all

    or

    part of this material is granted

    provided that the copies are not made or distributed for direct

    commercial advantage, the ACM copyright notice and the title of the

    publication and its date appear, and notice is given that

    copying is by

    permission of the Association for Comput ing Machinery. ho

    copy

    otherwise, or to republish, requires a fee and/or specific permission.

    O1984 ACM 0-89791-l47-4/85/001/0052 $00.75

    tcquirtlmrnt.s that actual modules must satisfy before they

    can be meaningfully substituted. This can prevent many

    subt,lc bugs. An unusual fea ture of ORJ2 is the commands

    that it provides for modifying and combining program

    modules; thus, (a form of) program transformation is

    ptovidcd wit,hin t,he language itself. A key principle here is

    the systemat,ic

    use of module expressions

    for describing

    and cresting

    compIcx combinations of modules; see Section

    2.5. This provides a level above that of conventional

    programming Isngun.ges,

    in which previously written code

    is dc>sctibrd by theories, and also is manipulated by module

    cxprc*ssions to product new code.

    1.2 Subsorts

    OD.IZ s strongly typcd5. As in many other languages, users

    csn introduce t,hcir own sorts and operations, thus

    supporting user

    defined

    ADTs.

    Aowevct,

    OBJ2

    also permits

    USP~S to dcclste that some s0rt.s contain (or are contained

    in) othcts. This supports a implc yet powerful fntm of

    polymorphism,

    as well #as xception (error) definition and

    handling (tccovety), pntt.inlly defined operations, and

    multiple inheritance (in the sense of object-oriented

    programming); see Section 3. In addition, it permit.s us to

    wtitx vcty simple and elegant code for standard ADTs like

    Lists, Stacks and Tables, as shown below.

    1.3 Implementation Techniques

    Thr current implcmrntation is s Maclisp intetptcter

    rmploying sevrral novrl techniqurs for cffirirnt t,rtm

    trwriting, including forms of tnil recursion, hnsh-coded

    structure sharing (see S&inn 4.4), a.nd usrt defined buitt-

    ins (see Section 4.5). The task of implementing OBJ? has

    been greatly eased by our Command lntetprct.er Generator

    (ClG), essentially a powerful application generator for

    interactive mrnu-driven systems; see Section 4.1. The CIG

    5

    Hereafter we gencralty use the word .sort’ instead of .lype’,

    Wing to avoid confusion among Ihe many different ways that ‘type’

    has been used (major exceptions are use or the word ‘typechecking’

    and of the phrase ‘sbst:act data type?. abbreviated ADT).

    52

  • 8/17/2019 Principles of OBJ-2

    2/15

    allows a strict separation of ODJ2’s high level interactive

    syntax from t.he functions that actually do the work, and

    also helps bring up prototypes very rapidly, facilitating

    experiments with ODJ2’ssyntax and semantics without

    having to reimplement a complex interactive system. An

    interesting methodological point is our use of OBJ to design

    the new implementation. We specified the database and

    the rewrite rule engine in both OOJl and OBJ2, and we also

    specified the interface between these two major

    components (but not in OBJ2). It was instructive to debug

    our OBJ2 design on a real example. It seems doubtful that

    we could have implemented such a complex and novel

    system in one year without using such techniques.

    1.4 Interaction and Flexibility

    OBJ2 s highly inaeractive and flexible. Program entry is

    driven by st*ructured menu choice, rather than by keyword

    entry and subsequent pa.rsing. All syntactic a.nd many

    semantic errors are detected at pr0gra.m entry time; the

    user is then given a diagnostic message and a chance to try

    ag3in. The OR.& interpreter provides much more help than

    most compilers even attempt. Impfemcnting this principle

    is greatly aided by the CIG.

    Users can define their own abstractions , wit.h any desired

    syntax, and then use these abst,ractions as if they were built

    in; in fact, users can even give efficient implementations in

    the underlying L isp. OBJ’s ‘mixfix’ (or .distfix.) syntax

    permits prefix, postfix, infix, ‘outfix. (as in < x 3 or

    I A I), and most generally, distributed fix operat,ions with

    keywords and arguments in any desired order

    (if then-elee-f i is non-trivially mixfix). In addition to

    efficient implementation, user definable built-ins can also

    provide sophisticated l/O packages, such as window

    management, if the underlying hardware supports it.

    (Section 4.5 gives more detail on built-ins.)

    2 Modules and Generice

    The only t.op level OBJ2 entities are modules (which are

    either objec ts or theories) and views (which re late theories

    to modules, see Section 2.4); objects contain executable

    code, while theories contain noncxccutabfe assertions.

    Thus, executable code and nonexecutable assertions are

    both modularized, and are c osely integrated with each

    other. Moreover, the mathematical semantics of theories

    and objects is elegantly unified since both a re data

    theories in the sense of [lS]; there is not space for details

    here, but the essential intuition is that the notion of theory

    generalizes to permit regarding certain subtheories as

    objec ts (i.e., they have initial interpretations) while others

    may have any interpretation.

    2.1 Objects: Syntax and Semantics

    olw’s basic c*llhly is the object, which is a module

    (possibly psr:~mrt~+cd) c,ncnpsulating cxccutabfe code;

    ohjrcts gcnrralfy introdtlcc new sorts of data and new

    opc rat.ions upon that (131.3.

    An object. hns three main parts:

    (t ) a

    header,

    conta.ining its name, parameters, interface

    rrquircmcnts, and importctl motl~~lc ist.; (2) a signature,

    declaring its new sorts, subsort rc*lnt.ionships, and

    operations; and (3) a body, containing its code, consisting

    of equations and sort constraints (t.hrsc are descrihcd in

    Section 3.1). The following BITS objec t introduces two

    new sorts Bit and Bite (for Bit lists) with

    scme

    relevant

    opcrat.ions; these fists have a S-expression-like syntax with .

    and nil. Ot3J2keywords and keysymbols are in italics.

    obj

    BITS is

    erhding

    NAT .

    sorts

    Bit Bite

    ops

    0 1 : -> Bit .

    op nil

    : -> Bite .

    OP

    _,_ : Bit Bits -> Bite .

    op

    length- : Bite -> Nat .

    var B : Bit .

    vat S : Bite .

    eq:

    length nil = 0 .

    eq : length B .

    S = inc length S .

    endo

    Each line in this ex:tmple begins with an OBJ2 keyword.

    The first line with keyword obj gives the name BITS of the

    object. T11csecond line indicates that the built-in objec t

    NAT (for natural numbers) is imported by BITS. The

    keyword “ezleuding” indicates that a certain static check

    is performed (see Section 2.2 for more detail). The

    ops

    tine

    declares the two Rit constants, the next

    op

    line declares the

    empty string nil, the next a #cons’ operation (it adds a

    Dit to some nits) with ‘dot’ syntax, and the next a length

    oprration using the sort Nat from NAT. An operation

    de&ration in 01352 onsists ol: a form, indicating the

    dist,rihution of keywords and arguments (underbars indicate

    argument p tacc*x); art arity, which lists argument sorts; and

    CIcoarity, which is tfle output sort. I”inally, variables of

    sorts Bit and Bite arc declared nnd used in equations

    which give semantics for the length function.

    OnJ?‘s b,asir user-level naming conventions are as follows:

    r~~odulesmust have globally unique names; sort names must

    be unique within thrir module,

    and may

    be qualified by a

    module name for disnmbigua1 ion; a.n operation name

    consists of its form, arity and coarity, and (in a future

    implementation) may be qualified by a module name; note

    t,hat sort names used in n&y and coarity can be qualified

    by module.

    OJ JZcode is execut.rd hy intrrprcting equations as

    rewrite

    rules: the fcfthnnd side is rcgardrd as a pattern to be

    matched within 311 xprc>ssion vnriahlfs can match any

    53

  • 8/17/2019 Principles of OBJ-2

    3/15

    subexpression of appropriate sort); when a match occurs,

    the subexpression matching the lefthand is rcwrhtcn to the

    corresponding substit,ution inst.ance of t.he righthand side,

    This process continues unt.il there are no more matches;

    then t.he expression is said to be reduced or in normal

    form. Writing

    eval

    lrngth 329 . 668 . nil

    ende

    at OBJZ’s top level causes calculation of the reduced form 2

    using the rules in BITS.

    The Church-Rosser and termination properties imply that

    expressions will always have unique reduced forms; we have

    found that experienced programmers usually write rules

    that satisfy these properties. Term rewriting may seem a

    specialized computational paradigm, but in fact it is

    completely gcncral: any computable function over any

    computable data types can be so realized [I, 21. This

    generalizes to operations t.hat are associative, commutative,

    idempotent and/or have an identity [35]; then

    implcmrntation is by matching modulo the given operation

    attributes.

    ODJ2’s

    mathematical semantics is socalled initial algebra

    semant.ics (L4S) 128). IAS provides a standard

    interpretation characterized by the properties of: (1) having

    ,no junk”, meaning that all data values are denoted by

    terms in the available operat,ion symbols; and (2) having

    *no confusion.,

    meaning that two terms denote the same

    data value if and only if they can be proved equal (with

    standard equational reasoning) from the given equations 151.

    defined in an imported module do not occur as topmost

    symbols on the leftha.nd side of a new equation; it can only

    bc used for objects; and it supports separate compilation,

    since a given operation is defined once and for all by the

    module that declares it, and can therefore be computed

    from just the information in that module.

    musinga

    does

    not guarantee anything, it just copies the imported module.

    2.3 Parameterleed Objects and Theories

    Modules group together the data and operations used for

    parbicular problems such a.ssorting, matrix manipulation,

    or graphics. Parameterized modules maximize reusability

    by permitting .tuning. to fit a variety o f applications. For

    exa.mple, using (italicized) square brackets to separate the

    module name from parameters, SORTIN# might sort lists

    over any ordered set X, and MATRIX/n,R] might provide the

    usual nxn matrix operations for scalars from R. The

    parameter X of SORTING anges over (partially) ordered

    sets, i.e., sets with an irreflcxive (i.e., X < X is false)

    transitive rclsbion. The pa rameter n of MATRIX ranges over

    natural numbers, while R ranges over rings6 . Thus, OBJ2

    supports

    semnntic

    interface requirements, whereas Ada’s

    purely synt,actic interfaces cannot exclude actuals that

    would produce unexpected or bizarre behavior. An OBJ2

    module interface is described by a requirement theory,

    giving both syntax and axioms for the interface, with an

    object being an admissible actual only if it satisfies the

    axioms. The requirement theory for SORTING s given by

    th POSET is

    2.2 Hierarchy of Modules

    protecting

    BOOL .

    sort Elt .

    OBJZ modules can import othrr modules in three different

    op c :

    Elt Elt -> Baa1 .

    var;EF.' E" : Elt .

    eq :

    E < E = false .

    ceq :

    E < E" = true

    if(EcE’mdE’

  • 8/17/2019 Principles of OBJ-2

    4/15

    theory may be needed. For example, the following TABLE

    object has two TRIV requirement theories, INDEX and VAL,

    with E lt. INDEX and Elt .VAL their corresponding sorts,

    thus illustrat,ing OBJz’s qualified sort name convention:

    obj TABLEPNDEX :: TRIV, VAL :: TRIV] ie

    protecting BOOL .

    eorts Table ErrVol .

    subsorts

    Elt .VAL < ErrVol .

    OP emPt7

    : -, Table .

    op put : Elt .VAL Elt . INDEX Table -> Tablr .

    op [ 1 : Table Elt. INDEX -> ErrVal .

    op Gndyf : Elt.INDEX -> ErrVal .

    uars I 1’ : Elt. INDEX .

    zIar V : Elt.VAL .

    rot T : Table .

    eq: put(V.I,T) [ I’ 1 =

    if I ==

    I’ then V else T C I’ I ii .

    eq : empty [ I ] = undef (I) .

    jbo

    In the first equation, .==,

    is a built-in equality such that

    for two terms t, t’ of the same sort, t == t’ is true if they

    have the same reduced form, and is f also otherwise. ==

    implements the decision procedure for equality that is

    associated with every objec t, and if-thrn_rlro_ii is a

    polymorphic conditional; both these are provided for every

    sort by the built-in BOOLobject. The supersort ErrVal of

    Elt . VAL accomodates error messages or Iookups of an

    index where no value is stored (Section 3 explains sub- and

    super- sorts). The form o f the operation put has no

    underbars, and therefore gets a standard parentheses-with-

    commas syntax, e.g., put(trur.13.Tl) for

    TABLE/‘INT,BOOL].

    2.4 Views

    Instantiating a parameterized objec t means providing

    actual ob jects satisfying each of its requirement theories’.

    In OBJ?, the actual ob jects are provided through viewa,

    which bind required sorts and operations to those actually

    provided (i.e., views map the sort and operation symbols in

    the formal requirement theory to those in the actual

    objec t’) in such a way that all axioms of the requirement

    theory are satisfied. For example,

    view INT-DESC of INT

    as

    POSET e

    SOPS lt to Int .

    vats X Y : Elt .

    op : x < Y to : Y < x .

    endview

    views INT with descending order 89 a poset; in “op : X < Y

    to : Y < X’ the first .

  • 8/17/2019 Principles of OBJ-2

    5/15

    the lexicographic ordering from LEX/IDJ Here is the code

    for SORTING the parameterized LIST module is given in

    Section 3.1):

    obj SORTING BT :: POSET] s

    eziending LISTDT] .

    op sorted : List -> Boo1 .

    op eort : Liet -> List .

    .uurs E E’ : Elt .

    Yar L L’ L” : Liet .

    eg : eorted(ni1) = true .

    eg :

    sorted(E)

    = true .

    c9 : eorted(E E’ L) =

    (E ==

    E’ or E < E’) and eortsd(E’ L) .

    ceq : eort(L E L’ E’ L’ ‘) =

    eort(L E’ L’ E L’ ‘) if E’ < E .

    ceg : eort (L) = L i / eorted(L) .

    jbo

    (At the time of writ.ing, OBJZ’s module instantiation facility

    was not. quite up t,o this and the following example; but we

    expect it will he by the time the pnpcr is presented.)

    If M is a module expression, then M * (.,.) is another, with

    sorts and operations renamed according t,o (...I. For

    example, we rename the oprration sort of SORTING o

    lex-sort in the module expression SORTINGMPD]] * (op

    sort to lex-eort 1. hlndulc exprc&ons also occur in

    ‘definitions’ inside of modules, wit.11 he effect of renaming

    the principal sort of the module cxprcssion, as in

    obj SYMROLTARLEa

    eztending ID .

    ezfending

    INT .

    dfn Env := STACKpmLE/ID, INT] +

    (sort Int to Lot, serf Table to Layer)].

    jbo

    (The principal sort of a module is the first new sort

    introduced in it; or if there is none, the principal sort of its

    first imported module, and so on rrcursivrly.) Replacing

    the ‘d/n’ by ‘ezfending’ and renaming of sort Stack to

    Env would yield the same operational semantics and

    hierarchy of modules.

    3 Subeorta

    One sort of data is often contained in (or contains) another,

    e.g., the natural numbers are contained in the integers,

    which are contained in the rationals; then

    the sort Nat

    is a

    subsort of Int, and Int is a subsort of Rat (or Int is a

    supersort of Nat, etc.), written Nat < Int < Rat.

    hloreover, an operation may restrict to subsorts of its arity

    and coarity and still be *the same. operation. For

    example, each addition operation + : Rat Rat -> Rat,

    +

    . Int Int -> Int, -+- : N&-Nat -> Nat is a

    -- .

    restriction of the preceding one. OBJ2’s very flexible

    subsort mechanism provides the following, all within the

    framework of a.n nitial algebra semantics:

    1.

    Such ovcrloadcd operations provide a simple but

    powerful polymurphism’ (see Sections 3.2 and 4.2).

    2. Multiple inheritance in t,he sense of object-oriented

    programming permits one sort to be a subsorl of two (or

    more) others, cnch having various defined operations;

    thrn all thtasc operations n.re nherited by the subsort.

    For rxampl(a, WPmight have RsgiateredVehiclr <

    Vehicle n.nd RegieteredVehicle < TaxedObject,

    with say a speed operation on Vehicles and a tax-

    amount opcrn.tion on TaxrdObj rcts; both these

    operations a.rc inherited by items of sort,

    RegieteredVehicle.

    3. The familiar difficult.& for AnTs with operations

    that are Wpnrt.in.l’ (such as tail for lists and pueh for

    bounded stacks) disappear by viewing the operations as

    t.otnl on t,hc right subsorts (see Scctzions 3.1 and 3.2).

    4. Errors can be treated in several styles, without need

    for special syntactic or semantic “error handling.

    mcchn.nisms (see Sections 3.3 a.nd 3.1).

    3.1 Partial Operationa and Sort Constraints

    The following spcrification for a parameterized LIST objec

    introduces a subsort, NeLiet of nonempty lists to make the

    (traditionally partial) head and tail operations total. Here

    .assoc’ indicates that an operation is associative, and “id:

    nil' indicates that it has nil as an identity.

    obj LIST/% :: TRIV] ie

    sorts NeLiet List .

    subsorts Elt < Nstist < List .

    op nil : -, List *

    op :

    op--:

    NoList NeList -> NeList

    [assoc]

    Liet Liet -> List [t18soc d: nil]

    op 62 : NeLiet -> Elt .

    op tail :

    NeList -> Lirt .

    zrar L : NeList .

    zInr E : Elt .

    e9 : hradQ L) = E .

    e9: tailCELl =L .

    jbo

    A more subtle kind of part.ial operation is illustrated by

    “push’ in a hounded stack. Unlike LIST, where nonempty

    list,s are genrrnted by concatenation, the stacks for which

    ‘pueh’ is ok have no natural expression as a set generated

    by constructors (e.g., by pueh itself); but they can be

    chn.ractcrizcd by the equational condition of having a

    Iengt,h not exceeding the bound. Such characterizations are

    called

    sort

    constraints in 0852 (the word ‘declarations’

    ww used in 1151 or the unconditional case) and have the

    general form

    as : f (Xl,. . . ,Xn) if .

    9

    Parameterized objects provide yet another polymophism, since a

    generic object’s operations are available

    to

    all its instances.

    56

  • 8/17/2019 Principles of OBJ-2

    6/15

    An initial algebra semantics for sort constraints k giVVn

    in 1221and an operat.ional semantics is given in [26].

    BOUNDED-STACKses the foliowing requirement theory

    th NAT* is

    proteclirq NAT .

    op bound : -> Nat .

    endfh

    NAT.+s a somewhat subMe t.heory especially constructed so

    that giving an interpretation of it corresponds exactly to

    giving a nat,urnl number as interpretation of the constant

    bound. Now the example:

    obj BOUNDED-STACK/%: TRIV. Y :: NAT*] i8

    8Ott8 N&tack Stack ErrStack .

    subsorts

    N&tack

    < Stack < ErrStrck .

    op

    empty : ->

    Stack .

    op pueh : Elt ErrStack -> ErrStwk .

    op

    top- :

    N&tack -> Elt .

    OP POP- *

    NeStack -> Stack .

    op length :

    Stack -> Nat .

    vat E : Elt ,

    VW S : Stack .

    us NeStack :

    pu8hCE.S) i/ length(S) < bound .

    eq : lsngth(empty) = 0 .

    eq : length(push(E,S)) = inc length(S) .

    cq : top purh(E, S> = E .

    eq : pop pueh(E, S) = S .

    jbo

    (This example has not been run since sort constraints

    require subtleties in the parser that are not yet

    implemented.) Overflow of such a stack during

    computation produces

    a

    runtime parse error (see Section

    3.3).

    3.2 Logic of Subsorte

    Although subsorts are very expressive, their logic is very

    simple, and indeed can be reduced to standard equational

    logic (22, 261. This is both theoretirzdly and practically

    important, since both standard algorithms for term

    rewrit,ing and theorem-proving (e.g., the Knuth-Bendix

    algorithm) and the large literature on algebraic data types

    ran be applied without modification. In the OR52 system,

    subsort notation is available at the user Icvcf, but is

    translated into (lengthier) internal standard equational

    forms. The key idea is to view a subsort pa ir s

  • 8/17/2019 Principles of OBJ-2

    7/15

    2. Partial Operations - here operations are defined on

    only part of what is normally considered their domain;

    for example, toil is only defined for non-empty lists:

    a. Partial Algebras -- here one attempts to generalize the

    theory of abstract data types to algebras involving

    partially defined operations; it has been found that the

    mathematical theory is far more

    complex

    than one

    would like, and we will not discuss this approach

    further here.

    b.Domain

    Subsorts - here one restricts operations to

    the

    domain on which they

    are meaningful by defining a

    subsort for this domain; for example, in OAJ? we could

    define NsLiet < List to be the sort of non-empty

    lists and then have tail : NeList -> List; 01352

    also has sort constraints.

    c. Sort Constraints -- th

    ese give the effect of partial

    operations with domain defined by a condition, 89 in

    the BOUNDED-STACKxample.

    3. Recovery Operations

    -- these are operations from a

    sort that, may contain errors to one that doesn’t:

    a. Retrac ts -- these are left inverses to coercions,

    permitting contingent parsing of expressions which

    would otherwise be ill-formed, IIS described below.

    b. Error Handlers -

    more general recovery operations

    than retracts are possible in

    OBJ2,

    but are not

    discussed here.

    The choice among the options supported by OBJ2 is largely

    a matter of style and taste; moreover, certain of these

    choices are very closely related to one another. For

    example, OBJ2 automatically provides both a coercion and

    a retract for every subsort pair; thus, both error supersorts

    and domain subsorts have associated retracts. One

    consideration in making a choice is what kind of explicit

    error messagesare desired.

    Let us now discuss retracts in more detail. Ill-formed terms

    of the order-sorted algebra are translated to well-formed

    terms of an extended standard algebra having new

    operation symbols rs’ B called retracts that are associated

    with each subsort pair s Boo1 . . 8s its bod

    both it(s subcommidpart and its close key are empty.

    The top level of OBJ2 can be seen as a single command

    whose subcommand set contains object, theory, and view

    commands”; without using italics for keywords, this migh

    look as follows:

    ;;;OBJ2 top levrl command specification

    (0

    ;open key’s

    0

    *cl080 keys

    0 ;body part

    (th-obj -vierkc>

    ;rubcommand procraring fa

    0) ;exit function

    ;;;dubconunand specification for top lrvrl

    (th-obj -view&

    ;fn name for subcommand

    0

    ;init in for rubcommand

    (“prompt’)

    ;prompt aprc

    (* ((th theory)

    ;opm

    key8

    for th coamand

    (endt sndth ht) ;closr key8 for th command

    “The real OB2 syntax is more complex, since communication wit

    the reduction engine, file system, editor

    (Emacs), nd Mac&p

    evaluator also occur at the top level.

    58

  • 8/17/2019 Principles of OBJ-2

    8/15

    (th-name%c)

    ;theorJ name procseeing in

    (th-perte%c IO

    ;eubcommand procrssing in

    ;for thsory co-d

    (throry%er) 1

    issit in for th conunand

    ((obj ob object)

    ;opra

    keye

    for obj command

    (ado jbo bo mdobj)

    ;close key for obj command

    (obj-name-pm%)

    ;obj XIUfie/parUh

    procersng fB

    (obj-part& *) ;rubcommmd procerring in

    ;for

    obj

    command

    (obj rct%ex) 1

    ;rxit in

    for

    obj command

    ((virr ~1)

    ;opon kayo for view command

    (rndv rndvier WV eodwv)

    ;cloee

    keys

    for virr command

    (view-name-part&)

    ;visr nome part procrseng in

    (View-part& *);subcommand ptocesring fn

    ;for view command

    (vielw%rx) 1)

    ; OIit in

    for View

    Command

    0) ;fioal in for rubcommand

    ;;;subcormnand eprc for obj commando

    (ob

    j -part&z

    ;fn name for thir rubcommand

    0

    (‘prompt9 ;prompt rprc

    (* I..

    ((sort

    rorttr 60) ;opm key for sort co-d

    0

    * * .

    1

    . . .

    (fop operator operetion)

    ;open kryr for op command

    0

    . . 1

    1

    ( (VW vare)

    0

    ;open

    keys for var

    command

    . . ,

    )

    ((09 equation)

    ;oprn

    krye for

    rq command

    0

    . . .

    1

    0)”

    .I

    The first S-expression specifies the top level command,

    while subsequent S-expressions specify its subcommand

    parts. The GIG generates one Lisp function for each S-

    expression in this sequence. The generated functions

    combine with the basic functions that process body parts to

    give a highly interactive interpreter. The system generates

    an informative prompt” and the user should then supply a

    body or keyword. At each point in the interaction, the

    menu of possible commands is automatically available.

    The GIG also supports inputing bodies through

    .prompt/rep ly. interaction. (Unfortunately, there is not

    room here for a detailed explanation of CIG syntax.)

    12

    oBJ2 prompt8 with the scqucncc of previous open keys.

    The prcsctnt OILI command structure only requires

    choosing an arbit.rary sequence of subcommands from the

    fixed subcommand srt of each command. However, a GIG

    can in principle hnndle many other kinds of command-

    subcommand control; in particular, t,he present CIG also

    supports choosing just one subcommand from the

    subcommand sot of a command. h’ote that there are

    natural t,ranslnt.ions between the GIG’s syntactic formalism

    and more familiar BNF. The Appendix gives BNF synt.ax

    for WJ? . Our GIG runs in Ma&p, but Thierry Billoir has

    also implrmcnted it on the Symbolics 3600, providing

    mousr-srnsitivc pop-up mrnus for command choice.

    4.2

    Parser

    The 01152parser translates order-sorted expressions (the

    Icft- and right-hand sides and conditions of equations, sort

    expressions in sort const.raint.s, intcrmediat,e terms from the

    rcduct.ion engine, and user queries) int,o sorted expressions

    in standard We form, more specifically into S-expressions

    of int,ernnl oprrnt.ion symhnls. For example, consider the

    following

    8orla Int Rat .

    stlbaorls Int < Rat .

    OP -‘_ :

    Int Int -> Int [assoc comm/

    oP *

    . Int Int -> Int [assoc comm 11

    --.

    op - :

    Xnt

    Int -> Int a

    op ;;cdOf_ond- : Int Xnt -> Int .

    oP +

    - Rat Rat -> Rat [aesoc comm]

    --*

    oP *

    * Rat Rat -> Rat [asaoc comm l]

    --I

    oP -/_ :

    Int Int -> Rat .

    uurs A B C D :

    IBt

    .

    var.3 X Y 2 : Rat .

    where comm in italic brackets indicates that the operation

    is commutative, and a number in italic brackets gives the

    parsing precedence (operations without numbers have

    prcccdrnce 0). The parser distinguishes + on Int from + on

    Rat by decorating the operation with the sort, and we will

    write +i and +r respectively (internal names for operations

    are a bit more coinplex in the real implementation). The

    coercion from Int to Rot and the retract from Rat to Int

    are reprrscnted by c\i\r and r\r\i respectively; this

    retract permits parsing a term with an Int operation

    applied t,o a Rat expression. Then we have the foilowing

    sample lowest parses:

    1.

    A

    + B + C => (+i A (+i B C));

    2.X+Y+Z=> (+rX

    (+rYZ));

    3. A - B -

    C=> (-A (-BC))or(- (-hB) 0,

    a parse error since it is ambiguous;

    4. A +

    B * C => (+i

    A

    (*i B C));

    5.

    A

    + B + X => (+r (c\i\r (+i A 8)) X); and

    6.

    gcdOf A + B

    snd C /

    D

    => (gcdOf (+i A B) (r\r\i U C D))).

  • 8/17/2019 Principles of OBJ-2

    9/15

    A binary associat.ivc opcrntion is pnrscd as right

    associative, where,as a similar nonassociative operation

    would have an a.mbiguous parse, c.g., (l), (2), (3);

    commutative declarations have no cffpct on parsing;

    see [SS] for more detail. Operations of lowest precedence

    are tried first at the top level of an expression (see (4)), and

    t.he parser gives expressions t.hc lowest possible sort; thus, A

    + B is (+i A B) rather t.han (+r (c\i\r A) (c\i\r B)).

    Possible retracts must he considrrcd in parsing exprrssions

    to be reduced, e .g. (6) (see Section 3.2).

    The parser uses recursive descent backtracking, since it

    may be necessary to try all possibilities in checking that

    there is exactly one meaningful lowest parse; thus, parsing

    can be expensive for complex expressions. The parse r

    stores partial results in tables to avoid redoing work. For

    example, in parsing A + B l A + B * A + B, the parse of

    B * A is stored and later looked up. This has a large effect

    for expressions like

    A

    -

    A - A - A. The parser also stores

    ambiguous expressions (those with several parses) and all

    their parses in a table; it can then return a single result

    indicating ambiguity, such as (*error* A - A - A - A);

    thus, we get

    (1) (*error* A - A - A - A1 with parses

    (- A (*error* A - A - A>)

    (- (-AA)

    (-AA))

    (- (*error* A -

    A

    - A)

    A)

    (2) (*error* A - A - A) with parses

    (- A (- A A))

    (- (-

    A A) A)

    4.3

    Database and Module

    Expression

    Evaluator

    The OB.JZ at.abase has four kinds of identifiers: module

    (theory or objec t) and view idcnt.ifirrs, sort identifiers,

    operation identifiers, and equation identifiers. Modules and

    views are basic units manipulated by the OBJZ anguage;

    but sorts, operat,ions and equat.ions cannot be manipulated

    without affecting modulrs since cvcry sort, operation and

    equation belongs to some module. Since module and view

    names are unique (Section 2.1), t,hcy can be used as

    identifiers in the database. A module’s parameter names

    arc local, and are idcntifictl by internally created global

    names. Since the sort names given by users are also local,

    database sort idcnt,ificrs annotate the user sort name with

    the module name. An operation identifier is annotated by

    its form, its rank (t,he list of arity and coarity sorts), and

    its module. Equation identifiers arc created from the top

    operation of the lefthand side and

    a

    key to distinguish

    equations having the same such operation. All information

    that ma.y be needed later is retained in properties of these

    identifiers. For example, all opcrat.ions belonging to a

    module are retained as a property of t,he module identifier

    under .m ops’ , and the rxtend-hirrarchy structure of

    modules is retained in a list of module identifiers on

    ‘m extends. and ‘m extcnded. properties.

    The OBJ2 database supports reusability of modules, Thus,

    a parameterized module is reused by instantiating its

    parameter theories with appropriate views, without

    affecting the original module. A new module can also be

    created by renaming, thus giving different names to sorts

    and operations, and reusing most other parts of the old

    module. Evaluating a module expression often requires

    creating new modules with different sort names, operation

    forms or parameter values. This is implemented by

    representing modules as lambda expressions with their so rt

    names, operation forms, and parameter modules as

    nrguments. By applying such lambda expressions, new

    modules are efficiently created in the database. This

    method is a.lso used to store already constructed modules

    into files so that whole systems can later be reused.

    4.4 Rewrite Rule Engine

    ODJ2 uses equations as rewrite rules, assuming that they

    terminate and are Church-Rosser. Since rewriting can use

    any combinat,ion of associative, commutative, identity and

    idempotent pattern matching, the rewrite engine is

    parameterized by the kind of rewriting used, by attaching

    properties to both sides of each equation; then (for

    example) commutative matching is used when a lefthand

    side has a commutative operation. When a righthand side

    is (for example) associative, its instances are put in normal

    form, i.e., flattened. Each property has such a .normal-

    izabion; systematic use of which greatly speeds up the

    01351matching process implement,ed by Plaisted. OBJ2

    rewriting is also parameterized by the Estrategy of each

    operation, a list of natural numbers telling the order to try

    reductions. For example, if_thsn-alar-f i has strategy

    (1 0); the inil.ia.l 1 means first reduce the first subterm;

    the following 0 means reduce at the top as long aa possible

    aftcr that.

    The rewrite engine’s top level function, Objval, determines

    if a given term is already reduced by checking its

    representation. If it is not, Objval checks if another

    occurrence of the same term has already been computed

    and stored in a hash table (used for results of computations

    with top symbol having the l ~avcrun~’ attribute, which

    can be set by users). Of course, there may be collisions in

    the hash table, in which case only the most recent

    computation is retained. Finally, if the term must be

    computed from scratch, Reduce is called by Objval with

    the Estrategy of the top operation, and the starting term

    is overwritten by the reduced one, to avoid recomputing

    shared subterms. Depending on the Estraiegy, Reduce

    splits into the following cases:

    1. If the strategy is empty, then Reduce is called again

    with the remaining occurrences where reductions must b

    performed, as indicated in 3.d. If there are no such

    occurrences, then Reduce returns that result.

    60

  • 8/17/2019 Principles of OBJ-2

    10/15

    2. For bon-empty Estrategies, the first ocurrence of the

    strategy is processed and if it is not 0, then Objval is

    called wit.h the corresponding subterm 8s argument

    before reducing the whole term with the remaining part

    of the strategy.

    3. Finally, if the first occurrence is 0, then reduction

    st,arts at the top, and the following are tried successively:

    a. Coercion and coercion-retract rules, to keep terms in

    normal form; e.g., terms to be reduced must be lowest

    parses of some OBJ2 expression for the Church-Rosser

    property to hold. These rules are not in the database,

    but the rewrite engine knows their form and uses

    them. The rewritten term will be in normal form

    because coercions and retracts first reduce their

    argument,s; hence, no recursive call is needed here.

    b. Morphism rules, as discussed in Section 3.2, are also

    used to keep terms in normal form, and are built into

    the rewrite engine. If one applies, then Objval must

    be called recursively, since a new operation is on top.

    c. Built-in operations, defined by equations whose

    righthand side is Maclisp code; see Section 4.5. The

    result of a built-in operation is either a built-in

    constant or else an OBJ2 expression that must be

    parsed snd then evaluated recursively by Objval.

    d. Finally, standard rules are attempted according to

    their topmost lefthand side operation. Actually, these

    rules are stored into two different data structures:

    those that don’t change the top operation are tried

    first until none can be applied, using a ring that is

    searched for new rules to apply aa soon as the current

    rule fails. This efficiently implements ‘tail recursive

    calls’; for example, the second rule of

    eq : x+0=x.

    eq : x + 6 Y = (I X) + Y .

    has + on top of both sides; so an expression with + on

    top is repeatedly matched with the second rule until it

    fails. When the ring has been searched without

    finding a rule that applies, the remaining rules are

    applied until one is found (or fails). If there is a

    match, then a new operation is on top, and Objval is

    called again; otherwise, the term cannot be reduced

    any more on top. However, reduction may now be

    possible on some immediate subterms because of

    reductions by rules in the ring: these are the new

    reductions that must be tried once the current strategy

    has been exhausted.

    Let us emphasize some points:

    1. Estrat.pgies may lead to a complex search of the tree,

    very much like what happens with evaluation of parse

    trees by attribute grammars.

    2. JGstratcgirs need not he given by the user, but instead

    can be automatically gcbncratcd at parse time using

    simple heuristics t.hat try to avoid useless computations:

    for example, + in the nhove cxnrnplc has strategy (2 o

    11, using tho heuristic that a binary operation with no

    rules t,hat look inside its first argument should begin by

    cvalunting its second argument, and then reduce at the

    top; the final 1 causes comp1ct.e eduction of non-ground

    terms with + remaining on top; note that left reducing a

    ground t,c?rmwith + on fop is usrlcss, since + is

    completely defined with respect to a set of constructors.

    On the other hand, retracts, coercions and most built-in

    operations (the exception being cont.rol structure built-ins

    like if-then-elee-fi) have a call-by-value strategy that

    reduces their subterms before trying to reduce at the top.

    3. Estrategies do not implement an optimal strategy, if

    one exists, but they are very efficient in practice: the

    ratio between attempted matches and sucessful matches

    is usually around 2/3, which is really impress ive. In

    particular, use of Estrategies and the tail recursion rinrr

    makes a much larger difference in the efficiency of term

    rewriting than dors the choice among data structures as

    discussed in [32].

    4. As an

    apphati(Jn

    of theory in 1261,we can reduce

    expressions that are not well-formed at parse time but

    may have a well-formed normal form. This occurs, for

    example, if WC ry to 11s~ 8 e 8 0 / a 0 0 as an

    integcbr (0 is z(‘ro and o is the successor function)

    somcwhcre in a term. It is apparent.ly a rational, but

    since integers are a subsort of rationals, it may really be

    an intcgcr after reduction. This problem is handled by

    the retract operations mentioned in Section 3.3 as

    follows: a retract from rat,ionals to integers is put on top

    of the above subtcrm to indicnt.e t,he hoped-for sort.

    Then, at reduction time the subt,erm reduces to a B 0

    with a coercion to the rationals since the result is

    supposed to be rational. Thrn a retract-coercion rule is

    applied to delet,e these two extra operations , permitting

    the rest of t,lrc computation to proceed. (261prr~~es

    soundness and completeness of this techniqllr: if the

    starting term cannot be parsed correctly but it.s

    equivalence class contnins CI correct term, then the

    normal form will be computed, assuming that the initial

    rules are Church-Rosspr.

    5. Last, but not le.?s t, all this w.zs easy to implement and

    provides well- ;trurturcd code, since choice of the next

    subterm t,o reduce is not part of f hc rewrite engine itself.

    4..6 User Defined Built-Ins

    A difficult problem for logic programming is to maintain

    purity and yet provide cfficicncy and input/output; most

    61

  • 8/17/2019 Principles of OBJ-2

    11/15

    languages simply compromise purity. OB.12 adopts an

    approach in which logica l purity can be maintained (at

    some cost in specification and theorem proving) or can be

    compromised (if needed to satisfy the practical

    requirements of a programming project). This approach

    permits users to create new ‘built-in” functions or objec ts,

    by implementing them in the underlying Lisp; they are also

    documented with OBJ2 syntax and (optionally, but

    encouraged) with equations. This approach provides OBJ2’s

    built-in objec ts for Booleans, integers, natural numbers,

    identifiers, lists, arrays, etc. Thus, we get the efficiency of

    compiled Lisp along with a precise mathematical

    desrript.ion of what these data types do. Although the

    algebraic specification is not executed, it can be useful for

    documentation and theorem proving. Built-ins are also

    useful for implementing I/O, including graphics. Built-ins

    will later permit ‘compiling9 operations defined by

    equations into Lisp functions (as in Rope and ML) without

    changing the rewrite engine, since these operations can be

    seen as .built-in’ once their Lisp code is generated. Note

    that a built-in operation may produce a built-in constant or

    an OBJ2 expression. Thus, built-in definitions must

    combine

    0852

    and Lisp syntax.

    In order to verify t,bat a given Lisp implementation of a

    built-in does in fact satisfy its specification (a standard

    OBJ2

    object), we need a precise not.ion of ‘implement-

    ation’. The literature includes a number of these 128, 81,

    and the following seems adequat.c for the present purpose

    (it

    dqes

    not take account of states, for which see 139, 20);

    bowmer, the current OBJ2 does not have objects with

    states). Let A and B be objects with signatures C and C’,

    reachable over t,heir respective signatures. Then an

    implementation

    of

    A by

    B is a view v from the theory

    with signature C and no equat,ions to the theory with

    signature C’ and no equations (in the general sense

    mentioned previously, that mnps C-opera.t.ions to C’-

    expressions) such that there is a (necessarily unique and

    surjective) C-homomorphism t,o A from the C-reachable

    part of B viewed by v as

    a

    C-algebra; in symbols,

    reacbC(BV)dA. It can be proved that implementations in

    this sense compose.

    5 Pa&, Present and Future

    OBJ2 is a fruition of fifteen years research in algebraic

    semantics”. In 1972, the basic principle o f .initial algebra

    semantics” (IAS) was developed, and in 1973 appIied to the

    denotation4 (or .attribute’) semantics of context-free

    languages [13]; this was later [29] related to abstract

    syntax, the Scott-Strachey approach, and structural

    induction. By 1973 we realized that concrete data types

    could usefully be viewed as many-sorted algebras [12]. In

    1974, IAS was applied to ADTs by ADJ [28]. Two

    awkward limitations of this first approach were addresed

    by subsequent work: parameterization and errors

    (including partial operations). In 1977, the Clear

    specificntion language [3] was introduced as a way of

    structuring complex specifications into simpler parts;

    a

    majo r principle here is the use of so-called ‘colimits. of

    specifications, following earlier work on structuring genera1

    systems [ll, 191. Clear’s powerful and precise mechanism

    for parameterized specifications inspired OBJ2’s generic

    module mechanism. 1977 a.lsosaw the first draft of OBJ, in

    connection wit,h a proposed algebraic semantics for

    errors [14]. This language was subsequently implemented

    by Joseph Tardo, first as OBJO and later as OBJT [25]. The

    original motivation for this work was the observation that

    algebraic specifications published in the literature were

    very often wrong, so that some way of testing them was

    needed. The theorem that links rewrite rules with

    equat,ional ADT specifications using IAS is that the normal

    forms of a set of terminat.ing Church-Rosser rewrite rules

    give the initial algebra of the rules viewed as a set of

    ejua.tions; this result is the theoretical basis for OBJ and

    appears for example in [16]. David Plaisted’s OBJl [27] is a

    significant improvement of OBJT, including his clever

    efficient implemcnt,ation of associative-commutative

    rewriting, and many powerful and convenient interactive

    features, such as a spelling checker. The current OBJ2

    implementation has profited from all of this.

    Two improvements of OBJ2 to be implemented soon are: a

    .univcrsal. sort U --

    this will give a tremendous flexibility

    in programming style, since it supports arbitrary mixtures

    of typed and untyped code; and

    a

    new value * for E

    strategies, indicating lazy evaluation -- this will support

    infinite data structures and processes. A more distant

    improvement will permit states in objects, following the

    theory in [ZO].

    13This

    paragraph

    is not intended to survey all work related to

    OBJ

    or even all work contributing directly to OBJ;nstead, it only sketches

    the direct line of development. Any survey of closely related work

    would have to include the important work OCZilles 1421and

    Guttag 1301 n ADTs, the work on Hope by Burstall, MacQueen,

    Sanella and others IS], the work of Hoffman and O’Donnell 1311on

    rewrite rule languages, and the survey of Huet and Oppeo 1 341 n

    rewrite rule theory. (391 surveys a good deal of relevant work in

    algebraic semantics.

    62

  • 8/17/2019 Principles of OBJ-2

    12/15

    Although we originally thought of

    OUJ = a

    vehicle for

    testing algebraic ADT specifications, we soon came to think

    of it as a general purpose executable specification language,

    suitable for rapid prototyping [Zl] and for programming

    language semantics [24]. However, our recent more

    efficient implementations and the expected arrival of

    parallel machines Iead us to regsrd OBJ as an ultra high

    level programming language that can be executed

    extremely rapidly on suitable a.rch itectures, and that is

    especially suitable for ‘fifth generation. applications (such

    as expert systems).

    OBJ

    is a ‘logic programming’

    language

    in the sense that its basic statements are equations, and the

    interpretation of those equations (in a,lgebras representing

    the underlying data types) agrees with the logic of

    equations plus the initiality principle. Moreover, a basic

    assumption of the rewrite rule implementation (rmmely, the

    Church-Rosser property) implies that multiple processors

    can be set to work concurrently, without the user having to

    explicitly schedule them or their interactions, with the final

    result guaranteed independent of the order of execution;

    also any available nonoverlapping rewrites can bc carried

    out simultaneously. Recent work 1231 n Eqlog explores

    combining the equational logic (and other powerful

    features) of OBJ with the Horn clause logic (and other

    powerful features) of Prolog. Two other research directions

    that we hope to pursue for rewrite rule languages are

    graphical programm ing methods and parallel architectures.

    Future work will also explore integration with the theorem

    proving capabilities of the REVE system [37], and

    compilation techniques for rewrite rule based languages.

    Integration with

    REVE

    will permit

    OBJ2

    to perform many

    validation checks on objects, including completeness checks

    using Thiel’s algorithm 1411 nd consistency checks using

    the socalled inductive completion algorithm [33]. On the

    other hand,

    0852

    will provide

    REVE

    with a powerful

    language for specifying complex hierarchical theories,

    supporting the ‘hierarchical inductive completion

    algorithm. of [36]. In turn, this algorithm will permit

    checking OBJZ’S protecting property. These techniques can

    be used to prove that

    actuals

    satisfy the requirement

    theories of parameterized modules. Thus, OBJ and REVE

    together constitute a very powerful environment that

    integrates programming, specification and verification”.

    There is little doubt that this will ra ise interesting new

    issues in each of these fields.

    6 References

    1. Bergs tra, J. A., and Tucker, J. V. A Characterization

    of Computable Data Types by Means of a finite equational

    specification method. In Automata, Languages and

    Programming, Seventh Colloquium,

    J. W. de Bakker and

    J. van Leeuwen, Eds., Springer-Verlag, 1980, pp. 76-90.

    2. Bprgstra, J. A., and Tuckrr, .I. V. Algebraic

    Specifications of Computable and Semicomputahle Dat.a

    Structurcls.

    To

    appear in

    Theoreticnl Computer Science;

    24~~.

    3. Burstall, R. M. and Gogucn, J. A. ‘Putting Theories

    togc>t.hcr o Make Specificat,ions.” f’roceedinga, Fi/lh

    International Join.t Conference on Artificial Intelligence

    5 (1877), 1045-1058.

    4. Burstall, R. M., and Goguen, J. A. The Semantics of

    Clear, a Specification Language. In Proceedinga of the

    1979 Copenhagen 1Vinter School on Abetract Software

    Specification,

    Springer-Verlag, 1980, pp. 282-332.

    6. Burstall, R.

    M.

    and Goguen, J. A. Algebras, Theories

    and Freeness: An Introduction for Computer Scientists. In

    fioceedings, 1981 Marktoberdorj NATO Summer School,

    Reidel, 1982.

    6. Burstall, R. M., MacQueen, D. and Sanelia, D. HOPE:

    an Experimental Applicative Language. In Conference

    Record of the 1980 LISP Conference, Stanford University,

    1080, pp. 138143.

    7. United States Department of Defense. Reference

    Manual for the Ada Programming Language. ANSI/MIL-

    STD-1815 A.

    8. Ehrich, H.-D. ‘On the Theory of Specification,

    Implementation and Parameterization of Abstract Data

    Types.’ Journal of the Association for Computing

    Machinery 29 (1982), 206227.

    9. Futatsugi, K. and Okada, K. Specification Writing as

    Construction of llierarchically Structured Clusters of

    Operators. In Proceedings, IFIP Congress 80, IFIP Press,

    1980, pp. 287-282.

    10. Futatsugi, K. and Okada,

    K.

    A Hierarchical

    Structuring Method for Functional Software Systems. In

    Proceeding8, 6th International Conference on Software

    Engineering, IEEE Press, 1982, pp. 393402.

    11. Goguen, J. Mathematical Foundations of

    Hierarchically Organized Systems. In

    Gfobal System8

    Dynamics,

    E. Att,ingcr, Ed., % Karger, 1971, pp. 112-128.

    12. Goguen, J. A. Some Remarks on Data Structures.

    Abstract of 1973 Lectures at Eidgenoschiche Technische

    Ilochschule, Zurich.

    13. Goguen, J. A. Semantics of Computation. In

    Proceedinga, First International Symposium on Category

    Theory Applied to Computalion and Control, University of

    Massachusetts at Amherst, 1974, pp. 234249.

    14. Goguen, J. A. Abstract Errors for Abstract Data

    Types. In IFIP Working Con ference on Formal

    Description of Programming Concepts, MIT, 1877.

    15. Goguen, J. A. Order Sorted Algebra. UCLA

    Computer Science Department,1978.Semantics and Theory

    of Computation Report No. 14.

    %tt alsotbe IotaSystcm 1401.

    63

  • 8/17/2019 Principles of OBJ-2

    13/15

    16. Goguen, J. A. How to Prove Algebraic Inductive

    Hypotheses without Induction: with applications to the

    correctness of data type representations. In

    Rrxeeding~,

    5th Conference on Automated Deduction,

    W. Bibel and

    R. Kowalski, Eds., Springer-Verlag, Lecture Notes in

    Computer Science, Volume 87, 1980, pp. 356373.

    17.

    Goguen, J. A. ‘Parameterized Programming:

    Transactions on Software Engineering SE-IO, 5

    (Sept.ember

    1984),

    5 28-543.0riginally appeared,

    Proceedings, Workshop on Reusability in Programming,

    edited by Biggers taff, T. a.nd Cheatham, T., ITT, pages

    138-150, 1983; also, revised version as Technical Report

    CSLI-84-9, Center for the Study of Language and

    Information, Stanford University, September 1984.

    18. Goguen, J. A. and Burstall, R. M. Introducing

    Institutions. In Proceedings, Logics of Programming

    Workshop,

    E. Clarke and D. Kozen, Ed.,Springer-Verlag,

    1984, pp. 221-256.

    19. Goguen, J. A. and Ginali, S. A Categorical Approach

    to Genrral Syst.ems Theory. In Applied General Systems

    Research, G. Klir, Ed.,Plrnum, 1978, pp. 257-270.

    20.

    Gogucn, 1 . A. and Mcsrgurr, .J. (Jniversal

    Realization, Persis trnt Interconnection and Implcmcntation

    of Abstrac t Modules. In Proceedings, 0fh International

    Colloquium on Automata, Languages and Programming,

    Springer-Verlag, 1982.

    21. Goguen, J. and Mesrguer, J. l R,npid Prototyping in

    the OBJ Exccut.able Specification Lnngu:lge: Software

    Engineering Notes 7, 5 (1982), 75-84Procccdings of Rapid

    Prot.otyping Workshop.

    22. Goguen, J. and Mescgorr, J. Order-Sorted Algebra:

    Partial and Overloaded Operations, Er rors and Inheritance.

    SRI International, Computer Scicncc Lab,l984.Given as

    lecture ‘Logic of Subsorts and Polymorphism at Seminar

    on Types, Carnegie-Mellon Univcrsit.y, June 1983.

    23.

    Gogucn, J. a.nd Mescguer, .J. ‘Equality, Types,

    Modules and (Why Not?) Generics for Logic

    Programming.. The Jovrnal of Logic Programming I, 2

    (1984), 179-21O.Also appears in f’roceeriings, 1984 Logic

    Programming Symposium, Upsala, Sweden, pp. 115-125;

    and Report CSLI-845, Center for the Study of Language

    and Information, Stanford University, March 1984.

    24. Goguen, J. A. and Parsaye-Ghomi, K. Algebraic

    Denotational Semantics using Parameterized Abstract

    Modules. In

    Formalizing Programming Concepts,

    J. Diaz

    and I. Ramos, Eds., Springer-Verlag, Peniscota, Spain,

    1981, pp. 292-309.

    25.

    Goguen, J. A. and Tardo, J. An Introduction to OBJ:

    A Language for Writing and Testing Software

    Spcncifications. In SpeciJiration

    of Reliable Software,

    IEEE Press, 1979, pp. 179-189.

    26. Goguen, J., Jouannaud, J.-P. and Meseguer, J.

    Operational Semantics of Order-Sorted Algebra. Summary

    presented at JFIP WG2.2, Boston, June 1984. Submitted

    for publication.

    27. Gogurn, J. A., Meseguer, J., and Plaisted, D.

    Progra.mming with Parameterized Ab tract Objects in OBJ.

    In Theory and fiactice of Soffware Technology, D. Ferrari,

    M. Bolognani and J. Goguen, Eds., North-Holland, 1983,

    pp. 163-193.

    28. Goguen, J. A., Thatcher, J. W. and Wagner, E. .Au

    Initial Algahra Approach to the Specificat,ion, Correctness

    and Implemrnte.tion of Abstract Data Types.’

    Current

    Trends

    in Progrnmming

    Methodology N (1978),

    80-149.Orig ind version, IBM T. J. Watson Research

    Center Technics1 Report RC 6487, October 1976.

    29. Gogucn, J. A. , Thatcher, J. W., Wagner, I’;. and

    Wright, J. B. “Initial Algebra Semantics and Continuous

    Algebras.’

    Journal

    of

    the

    Association

    for Computing

    Machinery 24, 1 (January 1977).

    30. Gutta.g, J. V.

    The

    Specification

    and Application to

    Programming of Abstract Data Types. Ph.D. Th.,

    University of Toronto,1975.Computer Science Department,

    Report CSR.G-59.

    31. Iloffman, C. M. and O’Donnell, M. J. .Programming

    wit.b Equations.’ ACM Transactions on Programming

    Languages and Systems 1, 4

    (1982), 83-112.

    32. Hnffmnn, C. and O’Donnell, M. .Pattern Matching

    in Trees..

    Journal of the Association

    for

    Computing

    Machinery 20,

    1 (1984), 68-95.

    33. IIuet, G., Hullot, J.M. .Proofs by Induction in

    Equational Theories with Constructors..

    Journal of

    the

    Association for

    Computing Machinery 25, 2 (1982),

    239-266.

    34.

    Huet, G. and Oppen, D. Equations and Rewrite

    Rules: A Survey. In

    Formal Language Theory:

    Perspectives and Open Problems, R. Book., Ed.,Academic

    Press, 1980.

    35. Jouannaud, J.P. and Kirchner, H. Completion of a

    Set of Rules Modulo a Set of Equations, In Roceedings,

    f Ith Symposium on

    Rinciples of Bogramming

    Languages,

    ACM, 1984, pp. 83-92.

    36.

    Kirchner, H. A Genera1 Inductive Completion

    Algorit,hm and Application to Abstrac t Data Types. In

    Proceedings, 7th Conference on Au tomated Deduction,

    Springer-Verlng, 1984, pp. 282-302.

    37. I,c~scn.nnr,P. Computer Experiments with the REVE

    Term Rewriting Systems Generator. In Proceedings,

    Symposium

    on Principles of Rogramming Languages,

    ACM, 1983.

    38.

    Mac Lanp,

    S.. Categories

    for

    the Working

    Mathematician. Springer-Verlag, 1971.

    64

  • 8/17/2019 Principles of OBJ-2

    14/15

    40. Nakajimn, R. and Yuasa, T.. The IOTA

    Progrumming Syslem.

    Springer-Vcrlag, 1083. Lecture

    Notes in Computer Science, Volume 160.

    41. Thicl, J.J. St.op Losing Slwp over 1ncornplct.c Dat,n

    Type Spccificalioo. In Proceedinga, 1 (th Symposium on

    Principles of f’rogramming Lungangerc,

    ACM, lf184.

    42. Zillcs, S. Absbact Specification of D&a Typrs.

    Report 1 Q, Computation Structurw Croup, MIT,lQ74.

    7 Appendix: OBJ2 BNF

    This appendix does not use italics for keywords, nor tloc~st

    give syot,ax for cvnluation, file m;~nipul:r.t.ion, etc.

    Syntactic Conventions

    nonterminal symbole

    I

    alternative separator

    exp.. .

    one

    or

    more exp’ll

    :&;

    one or more exp’s separated by .;

    zero or one exp. except that {{.)3

    indicates either pe riod or

    631

    ,...,sn3 choice of exactly one of el,...,en

    {-wt..3

    exp in one line; i.e., no

    (sxp)

    parentheses for syntactic grouping

    of expressions

    .(. .).

    parentheses ae terminal symbols

    --- text comment

    Theory and Object Commands

    : :=

    {th,theorv>

    UhNamO

    is

    :

    -

    ...

    Cendt,endth,ht)

    I GxtendingCmd>

    cUeingCmd> I

    .

    ::= GW.ng,us) .

    ::=

    (df,dfn,define)

    := .

    --- the principal eort of the module

    --- ie renamed to , i.e.

    ---

    df SortKey := ModExp

    --- ie equivalent to

    --a

    extending *

    ---

    .(”

    sort to “).

    GortsCmd? ::= {sort,eorts,so)

    SortKsy>...-3

    ::=

    ---

    is an expression composed

    Only

    ---

    of one operator symbol and variable8 (e.g..

    --- push Elm to Stack, add Elm to Set, etc.)

    ::=

    ::= {eq,equation) {{)) :

    =

    ::= {beq.bq,builtineq) ii))

    : =

    ::= Ccq,ceq,condeq) {{)) :

    cLhs> =

    if .

    cLhs>

    : :=

    : :=

    65

  • 8/17/2019 Principles of OBJ-2

    15/15

    aakecmd> : :=

    bke,mk3 cObjNams> la

    Iendm, endmk, km, okam)

    --- make CObjNameB r l ndm

    --- ir squvolent to

    --- obj CObjNames ir wing . rndo

    View Commands

    ::=

    a8 ie CVierPartCmd>...

    ~endv,endvier,endvr,wv3

    ::= I

    I

    ::=