Multi-Paradigm Logic Programming
Some Applications of Functional-Logic Programming Christian Prehofer Abstract
We show examples for higher-order functional logic programming in which both programming concepts nicely complement each other. These include modeling distributed systems, parsing and hardware synthesis.
1 Introduction The aim of this paper is to show some examples for functional logic programming and to sketch application areas. We show in several examples that the advanced concepts of functional and (higher-order) logic programming can nicely complement each other, leading to new applications. In particular, we focus on the newly developed concepts for a truly higher-order integration of functional and logic programming [14, 16, 17, 15]. Roughly speaking, we extend a higher-order functional core language by logic variables as in Prolog. These logic variables may be higher-order. Thus we need in general higher-order unication, as e.g. in Prolog [10]. The language is based on higher-order rewrite rules, which model functional programming (and actually more). To support logic programming, we allow conditions with extra variables. In the following, we rst give an informal introduction into higher-order term rewriting in Section 2, followed by an introduction to higher-order narrowing in Section 3. This will be the basis for the examples. Some important renements, such as a call-by-need strategy [15], will be briey discussed, as well as conditional rules. The new aspects of the applications in Section 5 are discussed in Section 6. The technical background is summarized in Appendix A.
2 Higher-Order Term Rewriting Higher-order term rewriting is the natural extension of rst-order rewriting to reasoning with higher-order equations. In this work, we follow the approach in [11]: we consider simply-typed -terms in -normal form and view the reductions of -calculus as implicit operations. For instance, immediate substitution of arguments via -reduction, e.g. (x:f (x))a = f (a), is generally assumed. Furthermore, we compute modulo -conversion, i.e. renaming of bound variables. For instance x:f (x) = y:f (y). Higher-order term rewriting easily deals with scoping, here pushing quantiers inside:
8x:P ^ Q(x) ! P ^ 8x:Q(x) In this example the quantier 8 is a constant of type (term ! bool) ! bool, where 8(x:P ) is written as 8x:P for brevity. Notice that the variable conventions of -calculus allow for a concise statement of the rst rule: the variable P in x:P ^ Q(x) represents a term not containing the
bound variable x. As another example for the utility of higher-order programming, consider symbolic dierentiation. The function diff (F; X ), as dened below, computes the dierential of a function F at a
Fakultät für Informatik, Technische Universität München, 80290 München, Germany, E-mail:
[email protected]
35
Applications of Functional-Logic Programming, Christian Prehofer
point X. diff (y:F; X ) diff (y:y; X ) diff (y:sin(F (y)); X ) diff (y:F (y) + G(y); X ) diff (y:F (y) G(y); X )
! 0 ! 1 ! cos(F (X )) diff (y:F (y); X ) ! diff (y:F (y); X ) + diff (y:G(y); X ) ! diff (y:F (y); X ) G(X ) + diff (y:G(y); X ) F (X )
With these rules, we can for instance compute: diff (y:sin(sin(y)); X ) ?! cos(sin(X )) diff (y:sin(y); X ) ?! cos(sin(X )) cos(X ) diff (y:y; X ) ?! cos(sin(X )) cos(X ) 1 In contrast, rst-order term rewriting only permits a limited, rst-order version of diff, as e.g. in [1, 19]. This example is developed further in [17, 15]. Apart from such high-level computations, an important application of higher-order rewriting is to model the basic mechanisms of current, higher-order functional programming languages such as SML or Haskell. Clearly, higher-order rewriting is more expressive, since it permits explicit -abstractions in the left-hand sides (as in the above example), which is not possible in functional programming. When proceeding from evaluation by rewriting to solving equations, we will use higher-order unication in the following. Higher-order unication is a powerful method for solving equations between higher-order -terms modulo the conversions of -calculus. Particularly, bound variables must be treated correctly: the unication problem x:sin(F (x)) =? x:sin(cos(x)) has solution fF 7! y:cos(y)g, whereas x:F =? x:sin(cos(x)) is unsolvable.
3 Lazy Narrowing In this section, we introduce the central narrowing calculus [14] which is used for functional-logic programming. Our setting for goal-directed lazy narrowing is as follows. We start with a goal R s !? t, where a substitution is a solution if s ?! t. This goal may be simplied to smaller goals by the narrowing rules. Let s $? t stand for one of s !? t and t !? s. For goals of the form s $? t, the rules are intended to preserve the orientation. We extend the transformation rules on goals to sets of goals in the canonical way: fs !? tg [ S ) fsn !? tn g [ S if s !? t ) fsn !? tng. For a sequence )1 )n of LN steps, we write ) , where = n : : :1 . System LN for lazy higher-order narrowing, shown in Figure 1, essentially consists of the rules for higher-order unication [18] plus the Lazy Narrowing rules. For a rst impression of lazy narrowing, we start with a few examples. Assuming the rules map(F; [X jY ]) ! [F (X )jmap(F; Y )] map(F; []) ! [] father(mary) ! john father(john) ! art
36
Multi-Paradigm Logic Programming
we solve the goal R(mary) !? art by R(mary) !? art
)LN Narrowing at Variable; R 7! x:f (R1 (x)) R1(mary) !? john; art !? art )LN Deletion or Decomposition R1(mary) !? john )LN Narrowing at Variable; R1 7! x:f (R2 (x)) R2(mary) !? mary; john !? john )LN Projection mary !? mary; john !? john ) LN Solved by Deletion Thus we get the solution R 7! x:father(father(x)). Notice that the trivial solution R 7! x:art
is also possible here, but it is easy to avoid by further constraints as e.g. in the following example. Another, slightly more involved example is the following. We use functional evaluation in this example for brevity. map(F; [mary; john]) !? [john; art]
) LN Evaluation,
F (mary) !? john; F (john) !? art
) LN Lazy Narrowing; F 7! x:father(H (x))
Decomposition
H (mary) !? mary; john !? john; father(H (john)) !? art )LN Projection; H 7! x:x mary !? mary; john !? john; father(john) !? art The last goals are easily solved by evaluation and Deletion. Composing the partial bindings yields the solution F 7! x:father(x). Observe how in the last examples Lazy Narrowing at Variable is used to compute solutions for functional variables. Although this rule is very powerful, it also has a high degree of non-determinism as it is quite unrestricted. There are however complete strategies which restrict this rule [17, 5]. The calculus employs two sources of non-determinism for such systems of transformations: which rules to apply and how to select the equations. Completeness fortunately does not depend on the goal selection, as each subgoal is independently solvable.
4 Functional-Logic Programming Functional-logic programming can be viewed as a special case of narrowing with left-linear rewrite rules. Left-linearity means that free variables do not occur repeatedly on the left side of a rule. This small and common restriction has a signicant impact on the expressiveness, i.e. full higherorder equality is avoided and decidable unication is gained in the second-order case [13]. In addition, it is an important source of optimizations for narrowing and, most importantly, leads to the Call-by-Need strategy. The important observation is that in this setting a particular class of goals, called Simple Systems, suces and has several nice properties. For instance, a variable cannot occur on both sides of a goal, e.g. X !? f (X ) is impossible and thus the occurs check is immaterial. Furthermore, solved forms are easy to detect. For instance, a Simple System of the form t1 !? X1 ; : : :; tn !? Xn ; is guaranteed to have a solution. It follows from the invariants of Simple Systems that all X1 ; : : :; Xn are distinct. In Simple Systems a solution to the variable elimination problem leads to a new strategy, coined Call-by-Need Narrowing [15]. The idea is quite simple: goals of the form t !? X, which are usually created when passing a parameter to a function, are simply delayed. Consider for instance the narrowing step with the rule f (X; Y ) ! g(X; X )
ff (t1 ; t2) !? g(a; Z )g )CLN ft1 !? X; t2 !? Y; g(X; X ) !? g(a; Z )g 37
Applications of Functional-Logic Programming, Christian Prehofer
Deletion
t !? t [ S ) fg
Decomposition xk :v(tn ) ! xk :v(t0n ) ) fxk :tn ! xk :t0ng Elimination F $ t ) fg if F 2= FV (t) and = fF 7! tg Imitation xk :F (tn) $ xk :f (t0m ) ) fxk :Hm (tn ) $ xk :t0m g where = fF 7! xn :f (Hm (xn ))g ?
?
?
?
?
with fresh variables Hm
Projection xk :F (tn) $ xk :v(t0m ) ) fxk :ti (Hp (tn )) $ xk :v(t0m )g where = fF 7! xn :xi(Hp (xn))g; Hp : p , and xi : p ! with fresh variables Hp Lazy Narrowing with Decomposition xk :f (tn ) ! xk :t ) fxk :tn ! xk :ln ; xk :r ! xk :tg where f (ln ) ! r is an xk -lifted rule Lazy Narrowing at Variable xk :H (tn) ! xk :t ) fxk :Hm (tn ) ! xk :lm ; xk :r ! xk :tg where f (lm ) ! r is an xk -lifted rule and = fH 7! xn :f (Hm (xn ))g ?
?
?
?
?
?
?
?
with fresh variables Hm
Figure 1: System LN for Lazy Narrowing The rst two goals are delayed, and only when solving the last one, the rst one has to be handled again. In contrast to evaluation as in functional languages, solving the goals t1 !? X; t2 !? Y may have many solutions. This simple idea leads to Call-by-Need Narrowing, which computes values only if needed and also avoids copying. It generalizes call-by-need or lazy evaluation with sharing of identical subterms from the functional world to functional-logic programming. Another important aspect of functional-logic programming are conditional rules. We consider normal conditional rules of the form l ! r ( l1 ! r1; : : :; ln ! rn, where ln ! rn denote conditions for the application of the rule and rn are ground terms (i.e. without free variables) in R-normal form. For such rules, it suces to add the conditions as additional goals for a lazy narrowing step, which is not shown here. Notice that we permit new variables in the left sides of the conditions, which are used as existential variables, to be computed by unication. This suces for logic programming, as predicates are just rewrite rules to the constant true.
5 Examples for Functional-Logic Programming We show several examples for functional-logic programming with left-linear, normal conditional HRSs. A summary of the new aspects of higher-order functional-logic programming can be found in Section 6. As we do not allow extra variables on the right-hand side of the conditions, local variables as in functional programming are created via let-constructs. For example, we show how a let-construct for pairs can be formulated by higher-order rewrite rules. This common notation for let can be 38
Multi-Paradigm Logic Programming
dened by pair(xs; ys) = X in F (xs; ys) =def let X in xs; ys:F (xs; ys) Several of the following examples assume an equality predicate on some data type. There are two ways to formalize such a predicate: either by a rule X = X ! true, which goes beyond functional-logic programming, or by encoding strict equality =s on some data type. For instance, the rules s(X ) =s s(Y ) ! X =s Y 0 =s 0 ! true can be used for the constructors s and 0 for natural numbers. As we will see, strict equality suces for most applications. We sometimes write p for a rule p ! true or a goal p !? true. Note further that we prefer the notation 8x:p instead of the logically equivalent x:p to clarify the examples (see also Section 6). let
5.1 Hardware Synthesis
This section shows how simple hardware gates can be represented and computed within functionallogic programming. Representing circuits by -terms is a very natural choice, allowing for instance simple composition and computation. Similarly, equality of circuits should be irrespective of the names of input parameters. The goal of this example is to compute functions composed of nand-functions (or gates). Thus we rst specify the nand-function and some auxiliary functions. nand(0; X ) nand(X; 0) nand(1; 1) map2(F; []) map2(F; [pair(X; Y )jR]) size nand(x; y:x) size nand(x; y:y) size nand(x; y:nand(F (x; y); G(x; y)))
! 1 ! 1 ! 0 ! [] ! [F (X; Y )jmap2(F; R)] ! 0 ! 0 ! size nand(x; y:F (x; y))+
size nand(x; y:G(x; y)) In this set of rules, the function size nand servers two purposes. First, it counts the number of nand functions, but also assures that some term contains no other functions. Now we are ready to compute a few simple gates. We rst synthesize an or-function consisting of at most three nand-gates with the following goals size(F ) 3; 8x; y:map2(F; [pair(0; 0); pair(x; 1);pair(1; y)]) !? [0; 1; 1]; where the second goal species the or-function. The rst solution F 7! x; y:nand(nand(x; x); nand(y; y)) is found by exhaustive search. The only other solution is a simple permutation: F 7! x; y:nand(nand(y; y); nand(x; x)) It is also possible to compute functions with one argument by ignoring the other. For instance, a not-function consisting of at most two nand-gates can be specied with size(x; y:F (x)) 2; map(F; [0; 1]) !? [1; 0] The solution is simply F 7! x:nand(x; x). 39
Applications of Functional-Logic Programming, Christian Prehofer
5.2 A Functional-Logic Parser
Top-down parsers belong to the classical examples for logic programming. The support for nondeterminism in logic programming is the main ingredient for this application. On the other hand, functional parsers (see e.g. [12]) have other benets, such as abstraction over parsing functions. We will integrate the best of both approaches in this example. We model the following tiny grammar, which is similar to the one in [12]. In addition to terminal symbols, e.g. a; b; c, we have the constructs and(T; T 0), or(T; T 0 ), and rep(T ). Their meaning is shown in the following table. For example and(t(a); or(t(b); t(c)) recognizes [a; b] and [a; c]. Construct recognizes t(a) a, where a is a terminal symbol and(T; T 0) wv if T recognizes w and T 0 recognizes v. or(T; T 0 ) v if T or T 0 recognizes v, rep(T ) v1 : : :vn if T recognizes each vi . In our setting, each of these constructs is represented as a parsing function (of the same name). The main issue of this example is to show how to model non-deterministic constructs such as the parsing function for or with conuent rewrite rules. The solution is to add an extra argument, called prophecy, to or, which determines the choice. When invoking or with a free variable as prophecy, the desired eect is achieved and in addition, the prophecies tell us which choice was made at each or construct. In the following rules, T; T 0 represent parsing expressions and L is the input list of terminals. To stratify matters, we use prophecies for all parsing constructs, and not only for or. The constant symbols pand; p1; p2; pt are used as prophecies. The function t(x) is used to parse the terminal x. t(X; pt; [Y jL]) ! L ( X =s Y and(T; T 0; pand(P 1; P 2);L) ! let T (P 1; L) in l:T 0(P 2; l) or(T; T 0 ; por1(P ); L) ! T (P; L) or(T; T 0 ; por2(P ); L) ! T 0 (P; L) rep(T; pemp; L) ! L rep(T; prep(P; P 1); L) ! let T (P; L) in l:T 0 (P 2; l) The following example illustrates how parsing is performed: and(t(a); or(t(b); t(c)); P; [a; b]) !? [] succeeds with P 7! pand(pt; por1(pt)). This solution for the prophecy can be seen as a parsing script showing how the word was parsed. Here, the rst choice in the or construct was chosen. As another example consider the goal rep(or(t(b); t(c)); P; [b; c; b]) !? [] whose parsing function accepts words of b's and c's. The goal succeeds with the solution P 7! prep(por1(t); prep(por2(t); prep(por1(t); pemp))): In purely functional versions of this parser, the needed mechanism for non-determinism and search has to be coded by some means. Compared to rst-order logic programming, we achieve a higher level of abstraction and exibility. For instance, the rep construct can be used with any parsing function (of the right type). In a rst-order version, the constructs and, or etc would be represented as a data structure, and a function/predicate has to be written to interpret such constructs. Thus, when passing such a data structure, representing a parser, to some other function, this function has to know how to interpret the structure.
5.3 The Alternating Bit Protocol
This example shows how to model distributed systems with inherent non-determinismby functionallogic programming. For algebraic specications, this has been shown in [7]. The alternating bit 40
Multi-Paradigm Logic Programming
protocol [3] is used for reliable communication on unreliable asynchronous channels. Assume sender s and receiver r are connected as in shown below via the transmitters ch1 and ch2. These model unreliable communication, as they may lose messages. The goal is to hide this from the environment and to deliver exactly the messages on Rmsg which have been received via Smsg . ch1
} }} }}
AA AARpkt AA AA
AA AA AA Sack AA
} }} }} } }} Rack
Spkt }}} >
Smsg /
s
`
ch2
r Rmsg /
~
For safe communication, s sends packages marked with a bit b. If r receives a message, only the bit is sent back via ch2 . S repeats sending a message until the same bit is received at Sack . Then s starts sending the next message marked with :b. Similarly, r only sends a message on Rmsg , if the bit changes. We will model the communication histories via streams, one for each channel. Note that this model implicitly provides for asynchronous communications via buering messages for each channel. Each component is modeled as a function from input to output streams. There is however a further complication with this model, as discussed in [4]: we need to model time progress explicitly. Roughly speaking, the sender must wait for answers but also repeat sending messages. However, this is not possible with functions which are monotonic wrt the prex order on streams [4]. Hence we introduce an extra message p which models the advance of time, also called time tick. The transmitters ch1 and ch2 are modeled as functions, which take an additional parameter, the prophecy. This stream determines the loss of data and may also send time ticks. For the following function denitions, the relation between argument positions and the channel names in the gure above can be seen in the goals below. Only for ch1 and ch2, the second arguments are prophecies, which are not shown above. s(u; v) s0 (b; []; v) s0 (b; [aju]; [pjv]) s0 (b; [aju]; [b0jv]) s0 (b; [aju]; [b0jv]) r(u) s0 ([]; v) r0(b; [pju]) r0(b; [(a; b)ju]) r0(b; [(a; :b)ju]) ch1(s; p) ch2(s; p) ch([]; p) ch(u; [pjp]) ch([aju]; [truejp]) ch([aju]; [falsejp])
! ! ! ! ! ! ! ! ! ! ! ! ! ! ! !
s0 (true; u; v)
[]
a; b)js0(b; [aju]; v)] a; b)js0(b; [aju]; v)] s0 (:b; u; v) r0(false; u)
[( [(
( b =s :b0 ( b =s b0
let (u0; v0 ) = r0(b; u) in ([pju0]; [pjv0]) let (u0; v0 ) = r0(:b; u) in ([aju0]; [bjv0]) let (u0; v0 ) = r0(b; u) in (u0 ; [:bjv0]) ch(s; p) ch(s; p) []
pjch(u; p)] [ajch(u; p)] p [ jch(u; p)] [] [
With this specication, we can model runs of the system via the following goal list: s(Smsg ; Sack ) !? Spkt; ch1(Spkt ; P1) !? Rpkt; r(Rpkt) !? (Rmsg ; Rack); ch2(Rack ; P2) !? Sack 41
Applications of Functional-Logic Programming, Christian Prehofer
For simulation, we need to instantiate some of the variables. For instance, with
Smsg = [d1; d2]; P2 = [true; true]; P2 = [p; true; true] we obtain the following solution behavior: fSpkt 7! p[(d1; true); (d2; false)]; Rpkt 7! Spkt ; Rmsg 7! [d1; d2]; Sack 7! [ ; true; false]; Rack 7! [true; false]g To model some loss of data, we can try
p
Smsg = [d1jd2]; P1 = [falsejtruejtrue]; P2 = [ jtruejtruejtrue] which yields p fSpkt 7! [(d1; true); (d1; true ); (d2; false)]; Rpkt 7! [ ; (d1; true); (d2 ; false)]; p p Rmsg 7! [d1; d2]; Sack 7! [ ; ; true; false]; Tack 7! [p; true; false]g Clearly, many more interesting simulations are possible. In general, only correct outputs on Rmsg should be computed for all solutions for P1 and P2. In general, narrowing is not powerful enough for formal verication, but complete wrt nding counter examples, which can very useful during development. Full verication of the algorithm (see [4]) is of course more involved and is usually attempted after simulation.
6 Discussion We have presented examples for the integration of functional and logic programming. Our higherorder setting allows for several new aspects in functional-logic programming, which are summarized in the following: Higher-order functional programming with non-determinism and search is a new combination. This is for instance shown in the parsing example, which integrates ideas of functional and logic programming. 8-quantied goals can be modeled directly via binders. That is, a goal 8x:t !? s logically corresponds to x:t !? x:s. In general, we observe that 9y:8x:p(x; y) is modeled as x:p(x; Y ) and 8x:9y:p(x; y) is modeled as x:p(x; Y (x)). -terms are often useful as data structures, similar to higher-order logic programming. This provides for built-in anonymous local constants via -conversion and a notion of substitution via -reduction. These aspects of -terms are often essential, as e.g. in the diff-example. In several other domains, such as dealing with programs, e.g. modeling semantics of programs and hardware synthesis, the constructs and conversions of -calculus are natural. In contrast to the rst-order case, it is possible to compute or synthesize functions via unication. This is needed if the original goal does not contain higher-order free variables, since such variables may be introduced during computation. Functional objects can be treated as data objects. This means that functions have a term structure which can be accessed. For instance, for a functional term x:and(x; or(a; x)), we can write a program to count the number of operations and; or. This allows to restrict functional objects computed to consist only of certain function symbols or to be of a certain maximal size. A further interesting renement for higher-order narrowing has been presented in [5]. To achieve optimality results, some further restrictions on rewrite rules are needed. Most of the example we show however t into this framework. 42
Multi-Paradigm Logic Programming
References [1] Leo Bachmair. Canonical Equational Proofs. Progress in Theoretical Computer Science. Birkhäuser, 1991. [2] Hendrik Pieter Barendregt. The Lambda Calculus, its Syntax and Semantics. North Holland, 2nd edition, 1984. [3] K.A. Bartlett, R.A. Scantlebury, and P.T. Wilkinson. A note on reliable full-duplex transmission over half-duplex lines. Communications of the ACM, 12(5):260261, 1969. [4] M. Broy. Functional specication of time sensitive communicating systems. ACM Transactions on Software Engineering and Methodology, 2(1):146, January 1993. [5] M. Hanus and C. Prehofer. Higher-order narrowing with denitional trees. In Proc. Seventh International Conference on Rewriting Techniques and Applications (RTA'96). To appear in Springer LNCS, 1996. [6] J.R. Hindley and J. P. Seldin. Introduction to Combinators and -Calculus. Cambridge University Press, 1986. [7] H. Huÿmann. Nondeterminism in Algebraic Specications and Algebraic Programs. Birkhäuser, 1993. [8] Richard Mayr and Tobias Nipkow. Higher-order rewrite systems and their conuence. Technical report, Institut für Informatik, TU München, 1994. [9] Dale Miller. A logic programming language with lambda-abstraction, function variables, and simple unication. J. Logic and Computation, 1:497536, 1991. [10] Gopalan Nadathur and Dale Miller. Higher-order logic programming. In C. Hogger D. Gabbay and A. Robinson, editors, Handbook of Logic in Articial Intelligence and Logic Programming, volume 5. Oxford University Press. To appear. [11] Tobias Nipkow. Higher-order critical pairs. In Proc. 6th IEEE Symp. Logic in Computer Science, 1991. [12] Lawrence C. Paulson. ML for the Working Programmer. Cambridge University Press, 1991. [13] Christian Prehofer. Decidable higher-order unication problems. In Automated Deduction CADE-12. Springer LNAI 814, 1994. [14] Christian Prehofer. Higher-order narrowing. In Proc. Ninth Annual IEEE Symposium on Logic in Computer Science. IEEE Computer Society Press, July 1994. [15] Christian Prehofer. A Call-by-Need Strategy for Higher-Order Functional-Logic Programming. In J. Lloyd, editor, Logic Programming. Proc. of the 1995 International Symposium, pages 147161. MIT Press, 1995. [16] Christian Prehofer. Higher-order narrowing with convergent systems. In 4th Int. Conf. Algebraic Methodology and Software Technology, AMAST '95. Springer LNCS 936, July 1995. [17] Christian Prehofer. Solving Higher-order Equations: From Logic to Programming. PhD thesis, TU München, 1995. Also appeared as Technical Report I9508. [18] Wayne Snyder and Jean Gallier. Higher-order unication revisited: Complete sets of transformations. J. Symbolic Computation, 8:101140, 1989. [19] Leon Sterling and Ehud Shapiro. The Art of Prolog: Advanced Programming Techniques. MIT Press, 1986. 43
Applications of Functional-Logic Programming, Christian Prehofer
1 Technical Background
We briey introduce simply typed -calculus (see e.g. [6]). We assume the following variable conventions: F; G; H; X; Y denote free variables, a; b; c; f; g (function) constants, and x; y; z bound variables. Type judgments are written as t : . Further, we often use s and t for terms and u; v; w for constants or bound variables. The set of types for the simply typed -terms is generated by a set of base types (e.g. int, bool) and the function type constructor !. The syntax for -terms is given by t = F j x j c j x:t j (t1 t2) A list of syntactic objects s1 ; : : :; sn where n 0 is abbreviated by sn . For instance, n-fold abstraction and application are written as xn :s = x1 : : :xn:s and a(sn ) = (( (a s1 ) ) sn ), respectively. Free and bound variables of a term t will be denoted as FV (t) and BV (t), respectively. Let fx 7! sgt denote the result of replacing every free occurrence of x in t by s. Besides conversion, i.e. the consistent renaming of bound variables, the conversions in -calculus are dened as: -conversion: (x:s)t = fx 7! tgs, and -conversion: if x 2= FV (t), then x:(tx) = t. The long -normal form of a term t, denoted by tl , is the -expanded form of the -normal form of t. It is well known [6] that s = t i sl = tl . As long -normal forms exist for typed -terms, we will in general assume that terms are in long -normal form. For brevity, we may write variables in -normal form, e.g. X instead of xn:X (xn ). We assume that the transformation into long -normal form is an implicit operation, e.g. when applying a substitution to a term. A substitution is in long -normal form if all terms in the image of are in long normal form. The convention that -equivalent terms are identied and that free and bound variables are kept disjoint (see also [2]) is used in the following. Furthermore, we assume that bound variablesSwith dierent binders have dierent names. Dene Dom() = fX j X 6= X g and Rng() = X 2Dom() FV (X ). Two substitutions are equal on a set of variables W , written as =W 0 , if = 0 for all 2 W. A substitution is idempotent i = . We will in general assume that substitutions are idempotent. A substitution 0 is more general than , written as 0 , if = 0 for some substitution . We describe positions in -terms by sequences over natural numbers. The subterm at a position p in a -term t is denoted by tjp . A term t with the subterm at position p replaced by s is written as t[s]p . A term t in -normal form is called a (higher-order) pattern if every free occurrence of a variable F is in a subterm F (un) of t such that the un are -equivalent to a list of distinct bound variables. Unication of patterns is decidable and a most general unier exists if they are uniable [9]. Also, the unication of a linear pattern with a second-order term is decidable and nitary, if they are variable-disjoint [13]. Examples of higher-order patterns are x; y:F (x; y) and x:f (G(z:x(z ))), where the latter is at least third-order. Non-patterns are for instance x; y:F (a; y) and x:G(H (x)). A rewrite rule [11, 8] is a pair l ! r such that l is a pattern but not a free variable, l and r are long -normal forms of the same base type, and FV (l) FV (r). Assuming a rule l ! r and a position p in a term s in long -normal form, a rewrite step from s to t is dened as !r s ?!lp; t , sjp = l ^ t = s[r]p : For a rewrite step we often omit some of the parameters l ! r; p and . We assume that constant symbols are divided into free constructor symbols and dened symbols. A symbol f is called 44
Multi-Paradigm Logic Programming
a dened symbol, if a rule f (: : : ) ?! t exists. Constructor symbols are denoted by c and d. A term is in R-normal form for a set or rewrite rules R if no rule from R applies and a substitution is R-normalized if if all terms in the image of are in R-normal form. An xk -lifter of a term t away from W is a substitution = fF 7! (F )(xk ) j F 2 FV (t)g where is a renaming such that Dom() = FV (t), Rng() \ W = fg and F : 1 ! ! k ! if x1 : 1 , : : : , xk : k and F : . A term t (rewrite rule l ! r) is xk -lifted if an xk -lifter has been applied to t (l and r). For example, fX 7! X 0 (x)g is an x-lifter of g(X ) away from any W not containing X 0
45
Applications of Functional-Logic Programming, Christian Prehofer
46