The Design of Vector Programs

Size: px
Start display at page:

Download "The Design of Vector Programs"

Transcription

1 Algorithmi Languages, de Bakker/van Vliet (eds.) FP, North-Holland Publishing ompany, 1981, The Design of Vetor Programs Alain Bossavit and Bertrand Meyer Diretion des Etudes et Reherhes, Eletriite de Frane, lamar!, Frane urrent vetor omputers suh as the ray-, yber 205 S 1, DAP or BSP pose a speial hallenge to the software designer as the available software tools and tehniques are far behind the hardware developments, and the goals of effiient vetor programming seem to onflit with some of the basi priniples of good software engineering. After studying some properties of these omputers, with partiular emphasis on the ray-l, we purport to show that a systemati approah to vetor programming is possible and fruitful; the proposed methods are applied to the systemati, proof-oriented derivation of several vetor algorithms. Language aspets are also onsidered. 1. ntrodution The advent of 'seond-generation' vetor proessors [8] suh as the ray-l, D yber 205, Lawrene Livermore Laboratory S, L DAP and Burroughs BSP, is one more piee of evidene for the fat that software lags far behind hardware as far as pratial industrial usage is onerned. These omputers, built with the latest LS or VLS tehnology in highly optimized arhitetures, are apable of ahieving speeds whih were unheard of before: for example, a ray-l omputer will in good onditions arry out more than 100 million 'atual' operations, exluding ontrol, per seond. On the other hand, a look at the software provided with these 'super-omputers' will show them to be what may be alled Fortran mahines: even though proessors for other languages may exist, these omputers are obviously tailored to a philosophy of programming whih has the stati array as its only data struture and the DO-loop as its main ontrol struture. Reipes given for writing effiient programs in that 99

2 100 A. Bossavit and B. Meyer framework [6], seem at first glane to be very far from modern ideas about programming, if not inompatible with them. Vetor programming thus appears as a hallenge for the software speialist. Areas where advanes are needed inlude the following interrelated topis: (1) algorithmis (algorithms for vetor proessing, and methods for finding suh algorithms); (2) program design (how to find program and data strutures whih will lead to effiient use of superomputers while ensuring other program qualities suh as reliability, larity, portability, modularity, et.); (3) program transformation (methods for adapting existing programs to effiient exeution on vetor omputers); (4) languages for vetor programming; (5) proof methods. The aim of this paper is to lay some foundations for a systemati treatment of vetor programming. t is mostly onerned with (1) and (2), with a brief disussion of (4). The partiular mahine whih motivated this study is the ray-l omputer, whih seems to be the most widely available among the 'seond generation' vetor mahines, and is quoted as the fastest urrently available omputer, even in salar mode [4,8]. Most of the disussion is, however, also valid for the other mahines. n Setion 2, we give a software interpretation of the rules whih must be obeyed by a omputation in order to be able to use the vetorization apabilities of the hardware. n Setion 3, we give a more abstrat interpretation of these rules in terms of the data types involved. Setion 4 disusses language problems. Setion 5 is devoted to a study of systemati program onstrution tehniques applied to vetor programming; several algorithms, in partiular a 'vetor holesky', are derived. 2. Rules for Vetorization Vetor mahines require that a program satisfy ertain onditions in order to be vetorizable, i.e. amenable to proessing in vetor, as opposed to salar, mode. The study of these onditions is partiularly interesting in the ase of vetor omputers suh as the ray-l or BSP whih aept standard FORTRAN, so that vetorization rests with the ompiler rather

3 The design of vetor programs 101 than the programmer. Abstrating from mahine peuliarities, five basi onditions appear as neessary and suffiient: - repetitive series of operations; - primitive operations only; - regularity; - no bakward dependeny; - no ross dependeny. These onditions are studied in [12] for the ray ase. We shall outline them here in general terms Repetitive series oj operations The only sequenes amenable to vetorization are loops, and, more preisely, for loops, i.e. ounter loops with a number of exeutions known at the outset. The/or loop ontrol struture, assoiated with the array data struture, is the software representative of the so-alled SMD (Single nstrution stream, Multiple Data stream) mode of restrited parallelism Primitive operations only With some slight extensions, only assignments and numerial or boolean operations are allowed in a vetor loop. This preludes in partiular jumps, thene onditional statements other than onditional assignments. The ray-1 Fortran ompiler (FT) will also inhibit vetorization of a loop ontaining a subprogram all (exept the subprogram is known to FT as having a vetor version) or another loop (thus restriting vetorization to the innermost loops) Regularity For a loop to be vetorizable, it must involve only 'regular' array elements, i.e. elements whose indies follow a stritly defined pattern, so that they an be fethed in advane for vetor operations. On the yber 205, the only regular elements are those whih are stored ontiguously; on the ray-l, a sequene is regular iff the distane between suessive elements is onstant (but not neessarily 1). Thus only ertain types of subarrays may be proessed in vetor mode.

4 102 A. Bossavit and B. Meyer 2.4. No bakward dependeny Let a loop with i as a ounter ontain the following array element assignment: where ALGOL-like brakets are used for array elements, op is some numerial or logial operation, the fk's are linear funtions (from the regularity rule), and all arrays are onsidered as one-dimensional (whih is always possible on a mahine with a linear store). This assignment has a bakward dependeny, whih will inhibit vetorization, iff for some k (1 < k ~ m) b k is a, and for some pair of values p, q in the range of i, the following holds: p<q and fk(p)=fo(q). n other words, the omputation of a[fo(q)] will use the value of another element of a, whih was fethed for updating in some previous iteration. For example, the assignment a[i]:= a[i - 1] + 1 introdues a bakward dependeny. The reason for this rule is that the vetor interpretation of suh a omputation would use the old value of the array element, not the new one as in the standard (sequential) interpretation of the loop. Note that the vetor interpretation makes perfet sense; it is only different from the sequential one. On the ray-l the ondition is less stringent; a bakward dependeny will atually arise only if the above ondition holds together with q-64<p where 64 is the length of the vetor registers, whih on the ray must be used for the operands and results of vetor operations (in ontrast, the yber 205 and BSP work diretly on vetors stored in memory). Vetor proessing on the ray-l may be onsidered, for all pratial purposes, as suessive proessing of 64-element vetor slies, all elements in a slie being proessed in parallel. An important ase of bakward dependeny ours when the dependeny affets a simple variable (whih may be onsidered as a one-element array, whose index is onstant through the loop), i.e. when the loop ontains an assignment of the form X:= op(x, b [Jl (i)], b2[j2(i)],... ).

5 A The design oj vetor programs 103 Suh an operation is alled a redution; it is partiularly unfortunate that it should not vetorize, sine it orresponds to the very ommon ase of aumulating a result into a variable, as in the omputation of the sum of the elements of a vetor, or of the salar (inner) produt of two vetors. n pratie, tehniques exist for reduing the loss of effiieny of redutions as ompared to truly vetorizable operations; redutions may thus be thought of as 'pseudo-vetorizable' operations who exeute more slowly than vetorizable operations but faster than salar ones No ross dependeny Let a loop ontain the following assignments: a[!o(i)] := op(... ); [go(i)] := op'(..., a[g,(i)],... ). They indue a ross dependeny, whih will inhibit vetorization, iff for some pair of values p, q in the range of i, the following holds: g,(p) =!o(q) with q - pi < 64 (on the ray-l). For example, the following statements in a loop on i will ause a ross dependeny: a[i] := 1; [i] := a[i + 1]. The rule stems from the fat that, due to the limited size of the instrution buffers, long loops may have to be split into several shorter ones in order to be vetorized (by slies of 64 on the ray); thus the two assignments might end up in two different loops, giving a different semantis for the program. n our example, assuming a was initially all 0, then would reeive the previous null values in the sequential ase and the new unity values in the vetor ase. 3. Basi Thoughts for a Vetor Programming Methodology onsidering the preeding rules, even though they do not inlude many details whih may be found in manufaturers' doumentation, it is quite tempting to dismiss them as too low-level and mahine-dependent, and

6 A. Bossavit and B. Meyer assert that vetor programming is just programming with objets of data type 'vetor'. Although we will use this definition as the basis for our approah to vetor program onstrution, it should be pointed out that it is not quite suffiient and that the previous rules, espeially the last ones on dependeny, must also be taken into aount for pratial purposes. Let us illustrate this point with an important vetor algorithm: matrix multipliation. Assume e is initialized to zero; a, b~ e have dimensions (m,n), (n,p) and (m,p) respetively. The ordinary algorithm will not vetorize (notations are mostly taken from [11]): for i in 1.. m do jor j in 1.. P do jor k in 1.. n do eli,)] := eli,)] + a[i, k] * b[k,)] (3.1) n terms of the preeding rules, we may say that [i,)] has a bakward dependeny on itself (the last line is a redution). Now if we reverse the loops on) and k, the program beomes vetorizable. This in fat means that instead of the 'element' formula whih forms the basis for algorithm (3.1) : n eli,)] = L au, k] * b[k,)] k=! one relies on the 'vetor' formula n e[i~ *] = L a[i,k] *b[k, *] k= 1 (where x[i, *] and x[ *,)] respetively denote the ith line and )th olumn of matrix x). However, if we applied a purely funtional view of vetor programming, i.e. obtained a program diretly from an 'abstrat data type' speifiation of matrix multipliation, the initial version of our program, as dedued from the last formula, would require, for eah line i, n vetor variables: J [i, *] : = a [i, 1] * b [1, *]; 2[i, *] :=a[i,2] *b[2, *] + [i, *]; em[i, *] :=a[i,m] *b[m, *] + m -l[i, *]; [i, *] :=m[i, *].

7 The design o/vetor programs 105 For pratial reasons (storage) this is exluded; the same variable [i, *] has to be used all along. This programming simplifiation is orret beause it does not onflit with the no bakward dependeny rule, as every operation of the form [i, *] := op([i, *]) will be implemented as a ounter loop whose body is [i,}] := op([i,}]) without any referene to [i, /] for' =f.= j (note that the loop ounter here is}). This ondition guarantees that the vetorized form of the new version (Le. the standard program where loops on j and k have been interhanged) is indeed semantially equivalent to the standard program. Suh a ondition, whih is more restritive but oneptually simpler than the no bakward dependeny rule, may be used as a replaement for it in a systemati approah. t an be formalized in the following way, inspired from the presentation of sequenes in the speifiation language Z [1]. Let VE X[(n)], for n ErN (the set of n-vetors of elements of X) be defined as the set of all total funtions from 1,..., n to X. Let & be the funtional binary operator suh that, if f and g are two funtions with the same domain Y, then f &g is the funtion h suh that, for any y E Y, hey) is the pair (f(y), g(y». Then for any binary operation p on X (p: XxX-+ Z for some Z) we may define a vetor extension of p, ext(p): VE[X](n) x VE[X](n)-+ VE[Z](n), whose value for any two vetors v and w in ve[x](n) is ext(p)(v, w) = po (v& w) where 0 is funtional omposition; in other words, for any i E 1,..., n, ext(p)(v, w)(i) = p(v(i), wei)~. t is possible to define in the same way (at least if p is assoiative) a vetor redution of funtionality red(p): VE[X]~X where red( +) = E, et. We shall interpret the rules of Setion 2 as implying that, in designing programs for vetor omputers, one should work on objets of data type vetor, restriting oneself to extension operations as muh as possible. When an extension operation annot be applied, a redution will still be preferable to operations whih would perform arbitrary shifting of indies

8 rr;;m == 106 A. Bossavitand B. Meyer (e.g. po«vo pred)&w), where pred is the predeessor funtion on integers, whih would give p(vi - 1), w(i)) for any i); suh operations would introdue hopeless bakward dependenies. The situation may be depited using a hierarhy of abstrat mahines (Fig. 1). At the matrix level, mahine MAT offers the operations of matrix algebra: multipliation, inversion, et. At the vetor level, several mahines are available to implement these operations: the extension mahine EXT, the redution mahine RED, and others. hoosing one of them will lead to a definite algorithm, the salar mahine SAL, whih orresponds to onventional programming languages. t is lear that the standard matrix multipliation algorithm given above (3.1) stems from the RED' mahine, while its vetorizable ounterpart will ome out naturally if one uses the EXT mahine. Data Type Abstrat mahi nes Matrix MAT Vetor EXT Salar seal r/ ,.,. r ,, RED --- :::.::?-- Fig. 1. Hierarhy of types and virtual mahines. Using the above approah, we will derive vetor algorithms by working on vetor objets from the beginning. This should lead to programs whih are both properly strutured and effiient on a vetor proessor. This should be ontrasted with the results obtained through more 'ad ho' methods. For example Higbie [6], in a paper on how to write ode whih will vetorize on the ray, warns that 'overly modular or strutured programs' will not be vetorizable (beause of the rule whih we alled 'primitive operations only', preluding subprogram alls inside a vetorizable loop). f this were true, the situation might be onsidered quite sad for the programmer, fored to hoose between struture and vetorization. On

9 The design of vetor programs 107 the other hand, if one agrees that a program is 'strutured' at least as muh from its proper adequation of ontrol struture to data struture as from its observane of rules regarding ontrol struture only (e.g. many subprograms, et.), then the answer is lear: rather than in-line expansion of subprogram alls in loop bodies, one should strive to write subprograms working on entire arrays (to use expressions found in ray publiations, "put the loop in the subroutine rather than the subroutine in the loop"). This will, in effet, implement the 'vetor' data type abstration. f the program is indeed vetorizable, i.e. if it does have vetors as its prinipal objets, there is a good hane that the version thus 'vetorized' will be learer and better 'strutured' independently of any mahine onsideration. 4. Language onsiderations Before we turn to the derivation of a few vetor algorithms, we must pay some attention to language issues. The ray approah uses a standard language, FORTRAN, and plaes the task of deteting vetorizable portions of ode upon the ompiler. The BSP also has a 'vetorizer' for standard FORTRAN ode (an introdution to the tehniques used for suh program transformations may be found in [10]). Other methods have been used or suggested (see [9] or [14] for a survey); for example, the yber 205 superomputer only vetorizes alls to speial array proessing subroutines. Perrott [14,15,16] has argued repeatedly in favor of using a language designed speifially for vetor programming; he desribes suh a language, ATUS, based on PASAL. This approah an be justified on several grounds: - n the ray and BSP approah to optimization, the programmer has to present his ode in a 'favorable' way so that the ompiler will be able to detet vetorizable piees of ode; he thus has to know the ompiler's idiosynraies in this respet. This, however, has to be balaned with the onsiderations on program struturing expressed above. - The searh for vetorizable ode amounts to de-ompilation (reonstruting higher-level vetor onstruts, suh as they might be expressed in ALGOL 68, PL/ or APL, from lower-level FORTRAN salar operations), whih is a rather silly ativity; - t is quite natural to speify the amount of allowable parallelism in

10 108 A. Bossavitand B. Meyer onnetion with the data struture definition rather than with the desription of the operations performed on it. On the other hand, the 'vetor language' approah seems extremely diffiult to implement in the ontext of a large sientifi omputing enter (the typial target for superomputers), where it is not realisti to imagine that programmers will turn to a new language for every new kind of appliation and every new mahine - espeially at a time when onerns for portability are at last making their way into the sientifi programming ommunity. Given the failures experiened by all previous efforts to impose languages other than FORTRAN to this ommunity, it is doubtful that a proposal applying to vetor omputers would sueed. n view of the urrent state of the art, the ray approah seems sensible as far as program oding is onerned. Languages suh as ATUS may, however, be very useful as intermediary notations for vetor program design, and we shall use similar ways of expression in the examples whih follow. 5. Examples of Systemati Vetor Program onstrution We turn now to the appliation of the priniples expounded in Setion 3 to the onstrution of some pratial programs. We shall use a method and set of heuristis for onstruting programs from speifiations whih were exposed in [13]. A similar approah was applied to lassial (salar) numerial algorithms in [2]. The following notation will be used in addition to the ones defined in Setion 3: - VE(n) stands for VE[REAL](n), the set of vetors of n real elements; - MTR(m, n) is the set of (m, n) real matries; - P,v, where VE VE(n) and l~ n, is the projetion of v on VE(l). For a matrixsemtr(m, n), if i~m andj~n, we will onsider line s[i, *] and olumn s[ *,j] as vetors in VE(m) and VE(n) respetively Triangular systems We saw in Setion 3 a vetor algorithm for matrix multipliation. Let us proeed with the inverse operation: solving linear systems. We first examine triangular systems. This will be a simple example of top-down synthesis of a numerial algorithm.

11 The design oj vetor programs The first step in the design of the program (alled trisolv) is to express it as a matrix algorithm (whih ould run on the virtual mahine MAT): (P) in s: MTR(n, n), b: VE(n); out x: VE(n); { <i:::;n=*pi-1s[*, i] =0 and s[i, i] :;O} trisolv Q) {sx= b, i.e. Lk= 1 s[ *, k] *x[k] = b} We must refine trisolv into a prediate transformer (on the vetor mahine EXT) from the preondition (P) to the postondition (Q). Let us try twie the heuristi alled 'unoupling' [13], i.e. add an auxiliary vetor variable y, and an integer one, notiing that (Q) ~ b = L s[ *, k] *x[k] ~ (y + Lk::;n s[ *, k] *x[k] = band y = 0) ~ (y + Lk::;/S[ *, k] *x[k] = band P,y = 0) and =n. SO (Q) ~ (1(1) and 1 = n) if we set 1(1) = the first term of the and above. Here, 1(1) is a 'weakening' of the exit ondition (Q) (whih is l(n». We notie that 1(0) an be trivially obtained. Thus a refinement of trisolv, using 1(1) as an invariant and 1 = n as the goal (exit ondition) will be: var : nteger; 1:=O;y:=b {1(1)} while <n do /:=1+1; reestablish 1(1); { 1 = nand 1(1)} This program is orret (by onstrution): 1(1) being a loop invariant, it is true after the ompletion of the loop, and the exit ondition 1 = n is also true, hene l(n). The statement reestablish is now Gust as trisolv was, one step bakwards) a speifiation for what is to be done. Next step: develop reestablish. One must go from 1(1-1), i.e. to 1(1), i.e. y + Lk<,s[ *, k] *x[k] = band p/-1y = 0

12 110 A. Bossavit and B. Meyer Without modifying b, whih is part of the input, we must use the assignment y:= y - s[ *, ] *x[l] after an x[l] suh that P(Y - s[ *, ] *x[l]) = 0 has been found. But P - 1 S[ *, ] = 0 by hypothesis, and P'-Y = 0 also. The equation thus beomes y[l] - s[ *, ] *x[l] = 0, thene x[/]. The final version of the program is: 1:=0; :=b; J(O) while <n do 1:= 1+ 1; {reestablish J(l) :} x[/] := y[ *, ]/s[/, ] y:= y -sf *, ] *x[l] Starting from a matrix speifiation and aiming at the EXT vetor target mahine, we have just synthesized a program whih must be, by onstrution, vetorizable Vetorized holeski We shall now introdue a more diffiult algorithm, holeski fatorization: given a symmetri positive-definite matrix A, find a lower triangular S suh that sst =A (in view of the resolution in two easy steps, using e.g. the above program, of the linear system Ax= b). What follows is also valid for the LV fatorization. We again apply systemati top-down synthesis. Here are the suessive steps. First the speifiation, expressed in terms of MAT objets: in a: MTR(n, n); out s: MTR(n, n); (R) {symmetri(a) and positive-dejinite(a)} holeski { :s; i < n => Pi -1 [ *, i] = O} (S) {A = sst, i.e. a = Lksn s[ *, k] *s[ *, k]} As before, we unouple (S), after introduing the auxiliary variable of type MTR(n, n): (S) # «+ LksS[*, k] *s[ *, k] = a and P = 0) and 1 = n) (J(/) and =n).

13 The design of vetor programs 111 The next refinement is, quite naturally: 1:= 0; := a; {/(On while <n do : = 1+ 1; { + r k < = a and P, _ 1 = O} reestablish /(1); {+ Lk<l=a-s[*,/] *s[*,/] and P,=O}. To reestablish /(1), one must perform the assignment := - s[ *, ] *s[ *, l] one an s[ *, ] suh that P-S' = 0 and P,( - s[ *, l] *s[ *, ]) = 0 has been found. As P, -1 = 0, row is the only one onerned, and must satisfy -olumn( - s[ *, ] * s[ *, ]) = 0, that is to say [l, *] - s[l, ] * s[ *, l] = 0, whih implies ( omponent) [l, l] = (s[/, 1])2. Thene the two instrutions for reestablish /(1): s[/,/] :=sqrt([l,/])); s[*,l] :=[l, *]ls[l,l]. As is symmetri (this fat is itself a loop invariant), P'-l [ *, ] = implies P'-l [l, *] = 0, therefore P'-lS[ *, ] = O. The final version will thus be: 1:= 0; := a; while <n do 1:=1+1; pivot:= sqrt([l, ]); s[ *, ] : = [/, *]1 pivot; := - s[ *, l] *s[ *, ] A FORTRAN translation appears on Fig. 2 and 3. t exhibits some of the nie properties of programs resulting from top-down design (high-level built-in doumentation, et.) and the safety guaranteed by the systemati synthesis method.

14 m 112 A. Bossavil and B. Meyer SUBROUTNE H 0 V E. (N, A, S, NDP) PURPm;E:, FATORZATON OF A SYMMETR MATRX, VETORZABLE VERSON. NPUT NTEGER N Order of the matri~ A r~eal. A ( 1 ) Array of the entries of A. Aij is at the position «J - 1)(2N - J) + 21)/2. ('olumn-symmetri storage mode') G OUTPUT REAL. s ( 1 ) Array of the entries of A. Aij is at the position «J - 1)(2N - J) + 21)/2 On e~it, if NDP = N, A = S tr(s)rt NTEGER NDP Number of olumns atually taken into aount during the fatori2ation. f NDP ( N, a non-positive radi~ ape peared in the treatment of olumn NDP r LOAL VARABLES: NTEGEH 1..., NNF'lS;:~, ADRL..., ADFUl.., ADF~.JJ, 1.,J, LF'l REAL PVOT, MUL, RADl ARTHMET FUNTON: NTEGEF~ ADDf~ESS, ADF~ESB(. ~J) "" «J _. U*(2*N....J) + 2U)/:':~ Fig. 2. Head of the vetorizable holeski program (FORTRAN). 6. onlusion The field of numerial and sientifi programming, although the oldest and one of the best established among the appliation domains of omputers, has shown strong resistane to the pratial implementation of software researh and advanes in programming methodology. With the

15 The design oj vetor programs NDP :::: 0 :i. (--- 0 ; L. ::: 0' (- - A ; NNP1S2:::: (N*(N + 1»/2 DO 1 :::: 1. NNP1S2 1 S) :::: A() -- The array S ontains both and A. r while i ( n do 2 F (L "GE" N) GOTO 7 i --- i + 1 ; L :::: L + 1 ADRLL ~ ADRESS(L. L) pivot (--- sqrtll) ; RAD "" S (ADRLU F RAD "LE" 0") GOTO 7 r 81 (--- l/pivot ; DO 3 :::: L. N -- Exeption if A is not positive definite PVOT::: SQRTRAD) NDP ::: L. :'3 8(ADRLL t... U.- S(ADRL.L t - U/PVOT * Sl L.P1 ::: L + 1 F LPl " EQ" N) GOTO 6 DO 5 J ~.:: L.P1, N ADRJJ :::: ADRESSJ. J) ADRJL :::: ADRESS(J. L) HUL :::: S (ADF~ Jl.) DO 4 ::: ~J. N S(ADRJJ+-J) :::: S(ADRJJt-J) - HUL.*SADRJL+-J) -- This loop is the only vetori2ab1e one 4 ONTNUE 5 ONTNUE 6 ONTNUE GOTO 2 "7 RETURN END Fig. 3. Body of the holeski program. popularization of new 'number-runhing' mahines, there is again a strong temptation to go bak to low-level, mahine-dependent, programming tehniques, and to dismiss any attempts at better software engineering as inompatible with the effiient use of these very fast omputers. We hope to have shown that suh an attitude has no justifiation, and that systemati methods an be applied for the rational and effiient use of this new tehnology.

16 114 A. Bossavit and B. Meyer Referenes [1] J.R. Abrial, S.A. Shuman and B. Meyer, Speifiation language, in: Proeedings Summer Shool on Program onstrution, Belfast (September 1979). [2] A. Bossavit and B. Meyer, On the onstrutive approah to programming: the ase for partial holeski fatorization (a tool for stati ondensation), in: Vihnevetsky and Stepleman (Eds.), Advanes in omputer Methods for Partial Differential Equations (MAS. 1979). [3] ray-l omputer System, FORTRAN (FT) Referene Manual, ray Doument No , Version E (1981). [4] M. Dungworth, The ray 1 omputer system, in: nfoteh State of the Art Report on Superomputers, Volume 2: nvited papers (Maidenhead, 1979) pp [5J P.M. Flanders, FORTRAN extensions for a highly parallel proessor, in: nfoteh State of the Art Report on Superomputers, Volume 2: nvited Papers (Maidenhead, 1979) pp [6] L. Higbie, Vetorization and onversion of FORTRAN programs for the ray-l (FT) ompiler, ray Doument No (June 1979). [7] nfoteh State of the Art Report on Superomputers, Volume 1: Total Systems ssues; Volume 2: nvited papers (Maidenhead, 1979). [8] E. W. Kozdrowiki and D.J. Theis, Seond-generation of vetor superomputers, omputer (EEE), Speial Setion on Sypersystems for the 80's, 13 (11) (1980) [9] D.J. Kuk, Languages and ompilers for parallel and pipeline mahines, in: REST onferene on Design of Numerial Algorithms for Parallel Proessing, Bergamo, taly (June 1981). [10] D.l. Kuk, Automati program restruturing for high-speed omputation, in: W. Handler (Ed.), ONPAR 81, Niirnberg, June 1981, Leture Notes in omputer Siene 111 (Springer, Berlin, 1981) pp [11] B. Meyer and. Baudoin, Methodes de programmation (Eyrolles, Paris, 1978). [12] B. Meyer, Un alulateur vetoriel: Le ray-l et sa programmation, EDF Report H , Atelier logiiel No. 24 (May 1980). [13] B. Meyer, A basis for the onstrutive approah to programming, in: S.H. Lavington (Ed.), nformation Proessing 80 (North-Holland, Amsterdam, 1980). [14] R.H. Perrott, Parallel languages, in: nfoteh State of the Art Report on Superomputers, Volume 1: Total Systems ssues (Maidenhead, 1979) pp [15] R.H. Perrott, A standard for superomputer languages, in: nfoteh State of the Art Report on Superomputers, Volume 2: nvited Papers (Maidenhead, 1979) pp [16] R.H. Perrott, A language for array and vetor proessors, TOPLAS (Transations on Programming Languages and Systems, AM) 1 (2) (1979)

Programming Basics - FORTRAN 77 http://www.physics.nau.edu/~bowman/phy520/f77tutor/tutorial_77.html

Programming Basics - FORTRAN 77 http://www.physics.nau.edu/~bowman/phy520/f77tutor/tutorial_77.html CWCS Workshop May 2005 Programming Basis - FORTRAN 77 http://www.physis.nau.edu/~bowman/phy520/f77tutor/tutorial_77.html Program Organization A FORTRAN program is just a sequene of lines of plain text.

More information

An Enhanced Critical Path Method for Multiple Resource Constraints

An Enhanced Critical Path Method for Multiple Resource Constraints An Enhaned Critial Path Method for Multiple Resoure Constraints Chang-Pin Lin, Hung-Lin Tai, and Shih-Yan Hu Abstrat Traditional Critial Path Method onsiders only logial dependenies between related ativities

More information

Channel Assignment Strategies for Cellular Phone Systems

Channel Assignment Strategies for Cellular Phone Systems Channel Assignment Strategies for Cellular Phone Systems Wei Liu Yiping Han Hang Yu Zhejiang University Hangzhou, P. R. China Contat: wliu5@ie.uhk.edu.hk 000 Mathematial Contest in Modeling (MCM) Meritorious

More information

i_~f e 1 then e 2 else e 3

i_~f e 1 then e 2 else e 3 A PROCEDURE MECHANISM FOR BACKTRACK PROGRAMMING* David R. HANSON + Department o Computer Siene, The University of Arizona Tuson, Arizona 85721 One of the diffiulties in using nondeterministi algorithms

More information

CIS570 Lecture 4 Introduction to Data-flow Analysis 3

CIS570 Lecture 4 Introduction to Data-flow Analysis 3 Introdution to Data-flow Analysis Last Time Control flow analysis BT disussion Today Introdue iterative data-flow analysis Liveness analysis Introdue other useful onepts CIS570 Leture 4 Introdution to

More information

Sebastián Bravo López

Sebastián Bravo López Transfinite Turing mahines Sebastián Bravo López 1 Introdution With the rise of omputers with high omputational power the idea of developing more powerful models of omputation has appeared. Suppose that

More information

Hierarchical Clustering and Sampling Techniques for Network Monitoring

Hierarchical Clustering and Sampling Techniques for Network Monitoring S. Sindhuja Hierarhial Clustering and Sampling Tehniques for etwork Monitoring S. Sindhuja ME ABSTRACT: etwork monitoring appliations are used to monitor network traffi flows. Clustering tehniques are

More information

A Context-Aware Preference Database System

A Context-Aware Preference Database System J. PERVASIVE COMPUT. & COMM. (), MARCH 005. TROUBADOR PUBLISHING LTD) A Context-Aware Preferene Database System Kostas Stefanidis Department of Computer Siene, University of Ioannina,, kstef@s.uoi.gr Evaggelia

More information

Deadline-based Escalation in Process-Aware Information Systems

Deadline-based Escalation in Process-Aware Information Systems Deadline-based Esalation in Proess-Aware Information Systems Wil M.P. van der Aalst 1,2, Mihael Rosemann 2, Marlon Dumas 2 1 Department of Tehnology Management Eindhoven University of Tehnology, The Netherlands

More information

Classical Electromagnetic Doppler Effect Redefined. Copyright 2014 Joseph A. Rybczyk

Classical Electromagnetic Doppler Effect Redefined. Copyright 2014 Joseph A. Rybczyk Classial Eletromagneti Doppler Effet Redefined Copyright 04 Joseph A. Rybzyk Abstrat The lassial Doppler Effet formula for eletromagneti waves is redefined to agree with the fundamental sientifi priniples

More information

How To Fator

How To Fator CHAPTER hapter 4 > Make the Connetion 4 INTRODUCTION Developing seret odes is big business beause of the widespread use of omputers and the Internet. Corporations all over the world sell enryption systems

More information

Neural network-based Load Balancing and Reactive Power Control by Static VAR Compensator

Neural network-based Load Balancing and Reactive Power Control by Static VAR Compensator nternational Journal of Computer and Eletrial Engineering, Vol. 1, No. 1, April 2009 Neural network-based Load Balaning and Reative Power Control by Stati VAR Compensator smail K. Said and Marouf Pirouti

More information

5.2 The Master Theorem

5.2 The Master Theorem 170 CHAPTER 5. RECURSION AND RECURRENCES 5.2 The Master Theorem Master Theorem In the last setion, we saw three different kinds of behavior for reurrenes of the form at (n/2) + n These behaviors depended

More information

Supply chain coordination; A Game Theory approach

Supply chain coordination; A Game Theory approach aepted for publiation in the journal "Engineering Appliations of Artifiial Intelligene" 2008 upply hain oordination; A Game Theory approah Jean-Claude Hennet x and Yasemin Arda xx x LI CNR-UMR 668 Université

More information

Capacity at Unsignalized Two-Stage Priority Intersections

Capacity at Unsignalized Two-Stage Priority Intersections Capaity at Unsignalized Two-Stage Priority Intersetions by Werner Brilon and Ning Wu Abstrat The subjet of this paper is the apaity of minor-street traffi movements aross major divided four-lane roadways

More information

Henley Business School at Univ of Reading. Pre-Experience Postgraduate Programmes Chartered Institute of Personnel and Development (CIPD)

Henley Business School at Univ of Reading. Pre-Experience Postgraduate Programmes Chartered Institute of Personnel and Development (CIPD) MS in International Human Resoure Management For students entering in 2012/3 Awarding Institution: Teahing Institution: Relevant QAA subjet Benhmarking group(s): Faulty: Programme length: Date of speifiation:

More information

WORKFLOW CONTROL-FLOW PATTERNS A Revised View

WORKFLOW CONTROL-FLOW PATTERNS A Revised View WORKFLOW CONTROL-FLOW PATTERNS A Revised View Nik Russell 1, Arthur H.M. ter Hofstede 1, 1 BPM Group, Queensland University of Tehnology GPO Box 2434, Brisbane QLD 4001, Australia {n.russell,a.terhofstede}@qut.edu.au

More information

Intelligent Measurement Processes in 3D Optical Metrology: Producing More Accurate Point Clouds

Intelligent Measurement Processes in 3D Optical Metrology: Producing More Accurate Point Clouds Intelligent Measurement Proesses in 3D Optial Metrology: Produing More Aurate Point Clouds Charles Mony, Ph.D. 1 President Creaform in. mony@reaform3d.om Daniel Brown, Eng. 1 Produt Manager Creaform in.

More information

Context-Sensitive Adjustments of Cognitive Control: Conflict-Adaptation Effects Are Modulated by Processing Demands of the Ongoing Task

Context-Sensitive Adjustments of Cognitive Control: Conflict-Adaptation Effects Are Modulated by Processing Demands of the Ongoing Task Journal of Experimental Psyhology: Learning, Memory, and Cognition 2008, Vol. 34, No. 3, 712 718 Copyright 2008 by the Amerian Psyhologial Assoiation 0278-7393/08/$12.00 DOI: 10.1037/0278-7393.34.3.712

More information

Granular Problem Solving and Software Engineering

Granular Problem Solving and Software Engineering Granular Problem Solving and Software Engineering Haibin Zhu, Senior Member, IEEE Department of Computer Siene and Mathematis, Nipissing University, 100 College Drive, North Bay, Ontario, P1B 8L7, Canada

More information

Static Fairness Criteria in Telecommunications

Static Fairness Criteria in Telecommunications Teknillinen Korkeakoulu ERIKOISTYÖ Teknillisen fysiikan koulutusohjelma 92002 Mat-208 Sovelletun matematiikan erikoistyöt Stati Fairness Criteria in Teleommuniations Vesa Timonen, e-mail: vesatimonen@hutfi

More information

arxiv:astro-ph/0304006v2 10 Jun 2003 Theory Group, MS 50A-5101 Lawrence Berkeley National Laboratory One Cyclotron Road Berkeley, CA 94720 USA

arxiv:astro-ph/0304006v2 10 Jun 2003 Theory Group, MS 50A-5101 Lawrence Berkeley National Laboratory One Cyclotron Road Berkeley, CA 94720 USA LBNL-52402 Marh 2003 On the Speed of Gravity and the v/ Corretions to the Shapiro Time Delay Stuart Samuel 1 arxiv:astro-ph/0304006v2 10 Jun 2003 Theory Group, MS 50A-5101 Lawrene Berkeley National Laboratory

More information

A Holistic Method for Selecting Web Services in Design of Composite Applications

A Holistic Method for Selecting Web Services in Design of Composite Applications A Holisti Method for Seleting Web Servies in Design of Composite Appliations Mārtiņš Bonders, Jānis Grabis Institute of Information Tehnology, Riga Tehnial University, 1 Kalu Street, Riga, LV 1658, Latvia,

More information

Open and Extensible Business Process Simulator

Open and Extensible Business Process Simulator UNIVERSITY OF TARTU FACULTY OF MATHEMATICS AND COMPUTER SCIENCE Institute of Computer Siene Karl Blum Open and Extensible Business Proess Simulator Master Thesis (30 EAP) Supervisors: Luiano Garía-Bañuelos,

More information

Henley Business School at Univ of Reading. Chartered Institute of Personnel and Development (CIPD)

Henley Business School at Univ of Reading. Chartered Institute of Personnel and Development (CIPD) MS in International Human Resoure Management (full-time) For students entering in 2015/6 Awarding Institution: Teahing Institution: Relevant QAA subjet Benhmarking group(s): Faulty: Programme length: Date

More information

AUDITING COST OVERRUN CLAIMS *

AUDITING COST OVERRUN CLAIMS * AUDITING COST OVERRUN CLAIMS * David Pérez-Castrillo # University of Copenhagen & Universitat Autònoma de Barelona Niolas Riedinger ENSAE, Paris Abstrat: We onsider a ost-reimbursement or a ost-sharing

More information

10.1 The Lorentz force law

10.1 The Lorentz force law Sott Hughes 10 Marh 2005 Massahusetts Institute of Tehnology Department of Physis 8.022 Spring 2004 Leture 10: Magneti fore; Magneti fields; Ampere s law 10.1 The Lorentz fore law Until now, we have been

More information

INCOME TAX WITHHOLDING GUIDE FOR EMPLOYERS

INCOME TAX WITHHOLDING GUIDE FOR EMPLOYERS Virginia Department of Taxation INCOME TAX WITHHOLDING GUIDE FOR EMPLOYERS www.tax.virginia.gov 2614086 Rev. 07/14 * Table of Contents Introdution... 1 Important... 1 Where to Get Assistane... 1 Online

More information

FOOD FOR THOUGHT Topical Insights from our Subject Matter Experts

FOOD FOR THOUGHT Topical Insights from our Subject Matter Experts FOOD FOR THOUGHT Topial Insights from our Sujet Matter Experts DEGREE OF DIFFERENCE TESTING: AN ALTERNATIVE TO TRADITIONAL APPROACHES The NFL White Paper Series Volume 14, June 2014 Overview Differene

More information

Computer Networks Framing

Computer Networks Framing Computer Networks Framing Saad Mneimneh Computer Siene Hunter College of CUNY New York Introdution Who framed Roger rabbit? A detetive, a woman, and a rabbit in a network of trouble We will skip the physial

More information

) ( )( ) ( ) ( )( ) ( ) ( ) (1)

) ( )( ) ( ) ( )( ) ( ) ( ) (1) OPEN CHANNEL FLOW Open hannel flow is haraterized by a surfae in ontat with a gas phase, allowing the fluid to take on shapes and undergo behavior that is impossible in a pipe or other filled onduit. Examples

More information

FIRE DETECTION USING AUTONOMOUS AERIAL VEHICLES WITH INFRARED AND VISUAL CAMERAS. J. Ramiro Martínez-de Dios, Luis Merino and Aníbal Ollero

FIRE DETECTION USING AUTONOMOUS AERIAL VEHICLES WITH INFRARED AND VISUAL CAMERAS. J. Ramiro Martínez-de Dios, Luis Merino and Aníbal Ollero FE DETECTION USING AUTONOMOUS AERIAL VEHICLES WITH INFRARED AND VISUAL CAMERAS. J. Ramiro Martínez-de Dios, Luis Merino and Aníbal Ollero Robotis, Computer Vision and Intelligent Control Group. University

More information

Picture This: Molecular Maya Puts Life in Life Science Animations

Picture This: Molecular Maya Puts Life in Life Science Animations Piture This: Moleular Maya Puts Life in Life Siene Animations [ Data Visualization ] Based on the Autodesk platform, Digizyme plug-in proves aestheti and eduational effetiveness. BY KEVIN DAVIES In 2010,

More information

protection p1ann1ng report

protection p1ann1ng report f1re~~ protetion p1ann1ng report BUILDING CONSTRUCTION INFORMATION FROM THE CONCRETE AND MASONRY INDUSTRIES Signifiane of Fire Ratings for Building Constrution NO. 3 OF A SERIES The use of fire-resistive

More information

Chapter 1 Microeconomics of Consumer Theory

Chapter 1 Microeconomics of Consumer Theory Chapter 1 Miroeonomis of Consumer Theory The two broad ategories of deision-makers in an eonomy are onsumers and firms. Eah individual in eah of these groups makes its deisions in order to ahieve some

More information

A Keyword Filters Method for Spam via Maximum Independent Sets

A Keyword Filters Method for Spam via Maximum Independent Sets Vol. 7, No. 3, May, 213 A Keyword Filters Method for Spam via Maximum Independent Sets HaiLong Wang 1, FanJun Meng 1, HaiPeng Jia 2, JinHong Cheng 3 and Jiong Xie 3 1 Inner Mongolia Normal University 2

More information

Chapter 5 Single Phase Systems

Chapter 5 Single Phase Systems Chapter 5 Single Phase Systems Chemial engineering alulations rely heavily on the availability of physial properties of materials. There are three ommon methods used to find these properties. These inlude

More information

Weighting Methods in Survey Sampling

Weighting Methods in Survey Sampling Setion on Survey Researh Methods JSM 01 Weighting Methods in Survey Sampling Chiao-hih Chang Ferry Butar Butar Abstrat It is said that a well-designed survey an best prevent nonresponse. However, no matter

More information

Price-based versus quantity-based approaches for stimulating the development of renewable electricity: new insights in an old debate

Price-based versus quantity-based approaches for stimulating the development of renewable electricity: new insights in an old debate Prie-based versus -based approahes for stimulating the development of renewable eletriity: new insights in an old debate uthors: Dominique FINON, Philippe MENNTEU, Marie-Laure LMY, Institut d Eonomie et

More information

Improved SOM-Based High-Dimensional Data Visualization Algorithm

Improved SOM-Based High-Dimensional Data Visualization Algorithm Computer and Information Siene; Vol. 5, No. 4; 2012 ISSN 1913-8989 E-ISSN 1913-8997 Published by Canadian Center of Siene and Eduation Improved SOM-Based High-Dimensional Data Visualization Algorithm Wang

More information

A novel active mass damper for vibration control of bridges

A novel active mass damper for vibration control of bridges IABMAS 08, International Conferene on Bridge Maintenane, Safety and Management, 3-7 July 008, Seoul, Korea A novel ative mass damper for vibration ontrol of bridges U. Starossek & J. Sheller Strutural

More information

REDUCTION FACTOR OF FEEDING LINES THAT HAVE A CABLE AND AN OVERHEAD SECTION

REDUCTION FACTOR OF FEEDING LINES THAT HAVE A CABLE AND AN OVERHEAD SECTION C I E 17 th International Conferene on Eletriity istriution Barelona, 1-15 May 003 EUCTION FACTO OF FEEING LINES THAT HAVE A CABLE AN AN OVEHEA SECTION Ljuivoje opovi J.. Elektrodistriuija - Belgrade -

More information

A Design Environment for Migrating Relational to Object Oriented Database Systems

A Design Environment for Migrating Relational to Object Oriented Database Systems To appear in: 1996 International Conferene on Software Maintenane (ICSM 96); IEEE Computer Soiety, 1996 A Design Environment for Migrating Relational to Objet Oriented Database Systems Jens Jahnke, Wilhelm

More information

The Application of Mamdani Fuzzy Model for Auto Zoom Function of a Digital Camera

The Application of Mamdani Fuzzy Model for Auto Zoom Function of a Digital Camera (IJCSIS) International Journal of Computer Siene and Information Seurity, Vol. 6, No. 3, 2009 The Appliation of Mamdani Fuzzy Model for Auto Funtion of a Digital Camera * I. Elamvazuthi, P. Vasant Universiti

More information

Masters Thesis- Criticality Alarm System Design Guide with Accompanying Alarm System Development for the Radioisotope Production L

Masters Thesis- Criticality Alarm System Design Guide with Accompanying Alarm System Development for the Radioisotope Production L PNNL-18348 Prepared for the U.S. Department of Energy under Contrat DE-AC05-76RL01830 Masters Thesis- Critiality Alarm System Design Guide with Aompanying Alarm System Development for the Radioisotope

More information

An integrated optimization model of a Closed- Loop Supply Chain under uncertainty

An integrated optimization model of a Closed- Loop Supply Chain under uncertainty ISSN 1816-6075 (Print), 1818-0523 (Online) Journal of System and Management Sienes Vol. 2 (2012) No. 3, pp. 9-17 An integrated optimization model of a Closed- Loop Supply Chain under unertainty Xiaoxia

More information

RATING SCALES FOR NEUROLOGISTS

RATING SCALES FOR NEUROLOGISTS RATING SCALES FOR NEUROLOGISTS J Hobart iv22 WHY Correspondene to: Dr Jeremy Hobart, Department of Clinial Neurosienes, Peninsula Medial Shool, Derriford Hospital, Plymouth PL6 8DH, UK; Jeremy.Hobart@

More information

Parametric model of IP-networks in the form of colored Petri net

Parametric model of IP-networks in the form of colored Petri net Parametri model of IP-networks in the form of olored Petri net Shmeleva T.R. Abstrat A parametri model of IP-networks in the form of olored Petri net was developed; it onsists of a fixed number of Petri

More information

INCOME TAX WITHHOLDING GUIDE FOR EMPLOYERS

INCOME TAX WITHHOLDING GUIDE FOR EMPLOYERS Virginia Department of Taxation INCOME TAX WITHHOLDING GUIDE FOR EMPLOYERS www.tax.virginia.gov 2614086 Rev. 01/16 Table of Contents Introdution... 1 Important... 1 Where to Get Assistane... 1 Online File

More information

Table of Contents. Appendix II Application Checklist. Export Finance Program Working Capital Financing...7

Table of Contents. Appendix II Application Checklist. Export Finance Program Working Capital Financing...7 Export Finane Program Guidelines Table of Contents Setion I General...........................................................1 A. Introdution............................................................1

More information

1.3 Complex Numbers; Quadratic Equations in the Complex Number System*

1.3 Complex Numbers; Quadratic Equations in the Complex Number System* 04 CHAPTER Equations and Inequalities Explaining Conepts: Disussion and Writing 7. Whih of the following pairs of equations are equivalent? Explain. x 2 9; x 3 (b) x 29; x 3 () x - 2x - 22 x - 2 2 ; x

More information

User s Guide VISFIT: a computer tool for the measurement of intrinsic viscosities

User s Guide VISFIT: a computer tool for the measurement of intrinsic viscosities File:UserVisfit_2.do User s Guide VISFIT: a omputer tool for the measurement of intrinsi visosities Version 2.a, September 2003 From: Multiple Linear Least-Squares Fits with a Common Interept: Determination

More information

Chapter 6 A N ovel Solution Of Linear Congruenes Proeedings NCUR IX. (1995), Vol. II, pp. 708{712 Jerey F. Gold Department of Mathematis, Department of Physis University of Utah Salt Lake City, Utah 84112

More information

Improved Vehicle Classification in Long Traffic Video by Cooperating Tracker and Classifier Modules

Improved Vehicle Classification in Long Traffic Video by Cooperating Tracker and Classifier Modules Improved Vehile Classifiation in Long Traffi Video by Cooperating Traker and Classifier Modules Brendan Morris and Mohan Trivedi University of California, San Diego San Diego, CA 92093 {b1morris, trivedi}@usd.edu

More information

In order to be able to design beams, we need both moments and shears. 1. Moment a) From direct design method or equivalent frame method

In order to be able to design beams, we need both moments and shears. 1. Moment a) From direct design method or equivalent frame method BEAM DESIGN In order to be able to design beams, we need both moments and shears. 1. Moment a) From diret design method or equivalent frame method b) From loads applied diretly to beams inluding beam weight

More information

OpenScape 4000 CSTA V7 Connectivity Adapter - CSTA III, Part 2, Version 4.1. Developer s Guide A31003-G9310-I200-1-76D1

OpenScape 4000 CSTA V7 Connectivity Adapter - CSTA III, Part 2, Version 4.1. Developer s Guide A31003-G9310-I200-1-76D1 OpenSape 4000 CSTA V7 Connetivity Adapter - CSTA III, Part 2, Version 4.1 Developer s Guide A31003-G9310-I200-1-76 Our Quality and Environmental Management Systems are implemented aording to the requirements

More information

Fixed-income Securities Lecture 2: Basic Terminology and Concepts. Present value (fixed interest rate) Present value (fixed interest rate): the arb

Fixed-income Securities Lecture 2: Basic Terminology and Concepts. Present value (fixed interest rate) Present value (fixed interest rate): the arb Fixed-inome Seurities Leture 2: Basi Terminology and Conepts Philip H. Dybvig Washington University in Saint Louis Various interest rates Present value (PV) and arbitrage Forward and spot interest rates

More information

Electrician'sMathand BasicElectricalFormulas

Electrician'sMathand BasicElectricalFormulas Eletriian'sMathand BasiEletrialFormulas MikeHoltEnterprises,In. 1.888.NEC.CODE www.mikeholt.om Introdution Introdution This PDF is a free resoure from Mike Holt Enterprises, In. It s Unit 1 from the Eletrial

More information

Findings and Recommendations

Findings and Recommendations Contrating Methods and Administration Findings and Reommendations Finding 9-1 ESD did not utilize a formal written pre-qualifiations proess for seleting experiened design onsultants. ESD hose onsultants

More information

THE PERFORMANCE OF TRANSIT TIME FLOWMETERS IN HEATED GAS MIXTURES

THE PERFORMANCE OF TRANSIT TIME FLOWMETERS IN HEATED GAS MIXTURES Proeedings of FEDSM 98 998 ASME Fluids Engineering Division Summer Meeting June 2-25, 998 Washington DC FEDSM98-529 THE PERFORMANCE OF TRANSIT TIME FLOWMETERS IN HEATED GAS MIXTURES John D. Wright Proess

More information

A DESIGN OF A FAST PARALLEL-PIPELINED IMPLEMENTATION OF AES: ADVANCED ENCRYPTION STANDARD

A DESIGN OF A FAST PARALLEL-PIPELINED IMPLEMENTATION OF AES: ADVANCED ENCRYPTION STANDARD International Journal of Computer Siene & Information Tehnology (IJCSIT) Vol 6, No 6, Deemer 2014 A DESIGN OF A FAST PARALLEL-PIPELINED IMPLEMENTATION OF AES: ADVANCED ENCRYPTION STANDARD Ghada F.Elkaany,

More information

International Journal of Supply and Operations Management. Mathematical modeling for EOQ inventory system with advance payment and fuzzy Parameters

International Journal of Supply and Operations Management. Mathematical modeling for EOQ inventory system with advance payment and fuzzy Parameters nternational Journal of Supply and Operations Management JSOM November 0, Volume, ssue 3, pp. 60-78 SSN-Print: 383-359 SSN-Online: 383-55 www.ijsom.om Mathematial modeling for EOQ inventory system with

More information

Srinivas Bollapragada GE Global Research Center. Abstract

Srinivas Bollapragada GE Global Research Center. Abstract Sheduling Commerial Videotapes in Broadast Television Srinivas Bollapragada GE Global Researh Center Mihael Bussiek GAMS Development Corporation Suman Mallik University of Illinois at Urbana Champaign

More information

Recovering Articulated Motion with a Hierarchical Factorization Method

Recovering Articulated Motion with a Hierarchical Factorization Method Reovering Artiulated Motion with a Hierarhial Fatorization Method Hanning Zhou and Thomas S Huang University of Illinois at Urbana-Champaign, 405 North Mathews Avenue, Urbana, IL 680, USA {hzhou, huang}@ifpuiuedu

More information

i e AT 35 of 1986 ALCOHOLIC LIQUOR DUTIES ACT 1986

i e AT 35 of 1986 ALCOHOLIC LIQUOR DUTIES ACT 1986 i e AT 35 of 1986 ALCOHOLIC LIQUOR DUTIES ACT 1986 Aloholi Liquor Duties At 1986 Index i e ALCOHOLIC LIQUOR DUTIES ACT 1986 Index Setion Page PART I PRELIMINARY 9 1 The aloholi liquors dutiable under

More information

Impedance Method for Leak Detection in Zigzag Pipelines

Impedance Method for Leak Detection in Zigzag Pipelines 10.478/v10048-010-0036-0 MEASUREMENT SCIENCE REVIEW, Volume 10, No. 6, 010 Impedane Method for Leak Detetion in igzag Pipelines A. Lay-Ekuakille 1, P. Vergallo 1, A. Trotta 1 Dipartimento d Ingegneria

More information

3 Game Theory: Basic Concepts

3 Game Theory: Basic Concepts 3 Game Theory: Basi Conepts Eah disipline of the soial sienes rules omfortably ithin its on hosen domain: : : so long as it stays largely oblivious of the others. Edard O. Wilson (1998):191 3.1 and and

More information

SOFTWARE ENGINEERING I

SOFTWARE ENGINEERING I SOFTWARE ENGINEERING I CS 10 Catalog Desription PREREQUISITE: CS 21. Introdution to the systems development life yle, software development models, analysis and design tehniques and tools, and validation

More information

Petri nets for the verification of Ubiquitous Systems with Transient Secure Association

Petri nets for the verification of Ubiquitous Systems with Transient Secure Association Petri nets for the verifiation of Ubiquitous Systems with Transient Seure Assoiation Fernando Rosa-Velardo Tehnial Report 2/07 Dpto. de Sistemas Informátios y Computaión Universidad Complutense de Madrid

More information

Agile ALM White Paper: Redefining ALM with Five Key Practices

Agile ALM White Paper: Redefining ALM with Five Key Practices Agile ALM White Paper: Redefining ALM with Five Key Praties by Ethan Teng, Cyndi Mithell and Chad Wathington 2011 ThoughtWorks ln. All rights reserved www.studios.thoughtworks.om Introdution The pervasiveness

More information

Solving the Game of Awari using Parallel Retrograde Analysis

Solving the Game of Awari using Parallel Retrograde Analysis Solving the Game of Awari using Parallel Retrograde Analysis John W. Romein and Henri E. Bal Vrije Universiteit, Faulty of Sienes, Department of Mathematis and Computer Siene, Amsterdam, The Netherlands

More information

Impact Simulation of Extreme Wind Generated Missiles on Radioactive Waste Storage Facilities

Impact Simulation of Extreme Wind Generated Missiles on Radioactive Waste Storage Facilities Impat Simulation of Extreme Wind Generated issiles on Radioative Waste Storage Failities G. Barbella Sogin S.p.A. Via Torino 6 00184 Rome (Italy), barbella@sogin.it Abstrat: The strutural design of temporary

More information

A Three-Hybrid Treatment Method of the Compressor's Characteristic Line in Performance Prediction of Power Systems

A Three-Hybrid Treatment Method of the Compressor's Characteristic Line in Performance Prediction of Power Systems A Three-Hybrid Treatment Method of the Compressor's Charateristi Line in Performane Predition of Power Systems A Three-Hybrid Treatment Method of the Compressor's Charateristi Line in Performane Predition

More information

i e AT 6 of 2001 REHABILITATION OF OFFENDERS ACT 2001

i e AT 6 of 2001 REHABILITATION OF OFFENDERS ACT 2001 i e AT 6 of 2001 REHABILITATION OF OFFENDERS ACT 2001 Rehabilitation of Offenders At 2001 Index i e REHABILITATION OF OFFENDERS ACT 2001 Index Setion Page 1 Rehabilitated persons and spent onvitions...

More information

Retirement Option Election Form with Partial Lump Sum Payment

Retirement Option Election Form with Partial Lump Sum Payment Offie of the New York State Comptroller New York State and Loal Retirement System Employees Retirement System Polie and Fire Retirement System 110 State Street, Albany, New York 12244-0001 Retirement Option

More information

TRENDS IN EXECUTIVE EDUCATION: TOWARDS A SYSTEMS APPROACH TO EXECUTIVE DEVELOPMENT PLANNING

TRENDS IN EXECUTIVE EDUCATION: TOWARDS A SYSTEMS APPROACH TO EXECUTIVE DEVELOPMENT PLANNING INTERMAN 7 TRENDS IN EXECUTIVE EDUCATION: TOWARDS A SYSTEMS APPROACH TO EXECUTIVE DEVELOPMENT PLANNING by Douglas A. Ready, Albert A. Viere and Alan F. White RECEIVED 2 7 MAY 1393 International Labour

More information

Interpretable Fuzzy Modeling using Multi-Objective Immune- Inspired Optimization Algorithms

Interpretable Fuzzy Modeling using Multi-Objective Immune- Inspired Optimization Algorithms Interpretable Fuzzy Modeling using Multi-Objetive Immune- Inspired Optimization Algorithms Jun Chen, Mahdi Mahfouf Abstrat In this paper, an immune inspired multi-objetive fuzzy modeling (IMOFM) mehanism

More information

Chapter 1: Introduction

Chapter 1: Introduction Chapter 1: Introdution 1.1 Pratial olumn base details in steel strutures 1.1.1 Pratial olumn base details Every struture must transfer vertial and lateral loads to the supports. In some ases, beams or

More information

F220 Series. Installation Instructions. Photoelectric Smoke/Heat Detectors

F220 Series. Installation Instructions. Photoelectric Smoke/Heat Detectors F0 Series EN Installation Instrutions Photoeletri Smoke/Heat Detetors F0 Series Installation Instrutions.0 General Information EN.0 General Information. F0-B6 Series Bases Use with the F0 Series Heat and

More information

Optimal Sales Force Compensation

Optimal Sales Force Compensation Optimal Sales Fore Compensation Matthias Kräkel Anja Shöttner Abstrat We analyze a dynami moral-hazard model to derive optimal sales fore ompensation plans without imposing any ad ho restritions on the

More information

A Survey of Usability Evaluation in Virtual Environments: Classi cation and Comparison of Methods

A Survey of Usability Evaluation in Virtual Environments: Classi cation and Comparison of Methods Doug A. Bowman bowman@vt.edu Department of Computer Siene Virginia Teh Joseph L. Gabbard Deborah Hix [ jgabbard, hix]@vt.edu Systems Researh Center Virginia Teh A Survey of Usability Evaluation in Virtual

More information

Transfer of Functions (Isle of Man Financial Services Authority) TRANSFER OF FUNCTIONS (ISLE OF MAN FINANCIAL SERVICES AUTHORITY) ORDER 2015

Transfer of Functions (Isle of Man Financial Services Authority) TRANSFER OF FUNCTIONS (ISLE OF MAN FINANCIAL SERVICES AUTHORITY) ORDER 2015 Transfer of Funtions (Isle of Man Finanial Servies Authority) Order 2015 Index TRANSFER OF FUNCTIONS (ISLE OF MAN FINANCIAL SERVICES AUTHORITY) ORDER 2015 Index Artile Page 1 Title... 3 2 Commenement...

More information

Soft-Edge Flip-flops for Improved Timing Yield: Design and Optimization

Soft-Edge Flip-flops for Improved Timing Yield: Design and Optimization Soft-Edge Flip-flops for Improved Timing Yield: Design and Optimization Abstrat Parameter variations ause high yield losses due to their large impat on iruit delay. In this paper, we propose the use of

More information

A Comparison of Default and Reduced Bandwidth MR Imaging of the Spine at 1.5 T

A Comparison of Default and Reduced Bandwidth MR Imaging of the Spine at 1.5 T 9 A Comparison of efault and Redued Bandwidth MR Imaging of the Spine at 1.5 T L. Ketonen 1 S. Totterman 1 J. H. Simon 1 T. H. Foster 2. K. Kido 1 J. Szumowski 1 S. E. Joy1 The value of a redued bandwidth

More information

Automated Test Generation from Vulnerability Signatures

Automated Test Generation from Vulnerability Signatures Automated Test Generation from Vulneraility Signatures Adulaki Aydin, Muath Alkhalaf, and Tevfik Bultan Computer Siene Department University of California, Santa Barara Email: {aki,muath,ultan}@s.us.edu

More information

On Some Mathematics for Visualizing High Dimensional Data

On Some Mathematics for Visualizing High Dimensional Data On Some Mathematis for Visualizing High Dimensional Data Edward J. Wegman Jeffrey L. Solka Center for Computational Statistis George Mason University Fairfax, VA 22030 This paper is dediated to Professor

More information

BENEFICIARY CHANGE REQUEST

BENEFICIARY CHANGE REQUEST Poliy/Certifiate Number(s) BENEFICIARY CHANGE REQUEST *L2402* *L2402* Setion 1: Insured First Name Middle Name Last Name Permanent Address: City, State, Zip Code Please hek if you would like the address

More information

SCHEME FOR FINANCING SCHOOLS

SCHEME FOR FINANCING SCHOOLS SCHEME FOR FINANCING SCHOOLS UNDER SECTION 48 OF THE SCHOOL STANDARDS AND FRAMEWORK ACT 1998 DfE Approved - Marh 1999 With amendments Marh 2001, Marh 2002, April 2003, July 2004, Marh 2005, February 2007,

More information

Performance Analysis of IEEE 802.11 in Multi-hop Wireless Networks

Performance Analysis of IEEE 802.11 in Multi-hop Wireless Networks Performane Analysis of IEEE 80.11 in Multi-hop Wireless Networks Lan Tien Nguyen 1, Razvan Beuran,1, Yoihi Shinoda 1, 1 Japan Advaned Institute of Siene and Tehnology, 1-1 Asahidai, Nomi, Ishikawa, 93-19

More information

TECHNOLOGY-ENHANCED LEARNING FOR MUSIC WITH I-MAESTRO FRAMEWORK AND TOOLS

TECHNOLOGY-ENHANCED LEARNING FOR MUSIC WITH I-MAESTRO FRAMEWORK AND TOOLS TECHNOLOGY-ENHANCED LEARNING FOR MUSIC WITH I-MAESTRO FRAMEWORK AND TOOLS ICSRiM - University of Leeds Shool of Computing & Shool of Musi Leeds LS2 9JT, UK +44-113-343-2583 kia@i-maestro.org www.i-maestro.org,

More information

On the Notion of the Measure of Inertia in the Special Relativity Theory

On the Notion of the Measure of Inertia in the Special Relativity Theory www.senet.org/apr Applied Physis Researh Vol. 4, No. ; 1 On the Notion of the Measure of Inertia in the Speial Relativity Theory Sergey A. Vasiliev 1 1 Sientifi Researh Institute of Exploration Geophysis

More information

Asymmetric Error Correction and Flash-Memory Rewriting using Polar Codes

Asymmetric Error Correction and Flash-Memory Rewriting using Polar Codes 1 Asymmetri Error Corretion and Flash-Memory Rewriting using Polar Codes Eyal En Gad, Yue Li, Joerg Kliewer, Mihael Langberg, Anxiao (Andrew) Jiang and Jehoshua Bruk Abstrat We propose effiient oding shemes

More information

Big Data Analysis and Reporting with Decision Tree Induction

Big Data Analysis and Reporting with Decision Tree Induction Big Data Analysis and Reporting with Deision Tree Indution PETRA PERNER Institute of Computer Vision and Applied Computer Sienes, IBaI Postbox 30 11 14, 04251 Leipzig GERMANY pperner@ibai-institut.de,

More information

JEFFREY ALLAN ROBBINS. Bachelor of Science. Blacksburg, Virginia

JEFFREY ALLAN ROBBINS. Bachelor of Science. Blacksburg, Virginia A PROGRAM FOR SOLUtiON OF LARGE SCALE VEHICLE ROUTING PROBLEMS By JEFFREY ALLAN ROBBINS Bahelor of Siene Virginia Polytehni Institute and State University Blaksburg, Virginia 1974 II Submitted to the Faulty

More information

cos t sin t sin t cos t

cos t sin t sin t cos t Exerise 7 Suppose that t 0 0andthat os t sin t At sin t os t Compute Bt t As ds,andshowthata and B ommute 0 Exerise 8 Suppose A is the oeffiient matrix of the ompanion equation Y AY assoiated with the

More information

Outline. Planning. Search vs. Planning. Search vs. Planning Cont d. Search vs. planning. STRIPS operators Partial-order planning.

Outline. Planning. Search vs. Planning. Search vs. Planning Cont d. Search vs. planning. STRIPS operators Partial-order planning. Outline Searh vs. planning Planning STRIPS operators Partial-order planning Chapter 11 Artifiial Intelligene, lp4 2005/06, Reiner Hähnle, partly based on AIMA Slides Stuart Russell and Peter Norvig, 1998

More information

Active Load Balancing in a Three-Phase Network by Reactive Power Compensation

Active Load Balancing in a Three-Phase Network by Reactive Power Compensation Ative Load Balaning in a hree-phase Network by eative Power Compensation Adrian Pană Politehnia University of imisoara omania. ntrodution. Brief overview of the auses, effets and methods to redue voltage

More information

Design Implications for Enterprise Storage Systems via Multi-Dimensional Trace Analysis

Design Implications for Enterprise Storage Systems via Multi-Dimensional Trace Analysis Design Impliations for Enterprise Storage Systems via Multi-Dimensional Trae Analysis Yanpei Chen, Kiran Srinivasan, Garth Goodson, Randy Katz University of California, Berkeley, NetApp In. {yhen2, randy}@ees.berkeley.edu,

More information

Interaction-Driven Virtual Reality Application Design

Interaction-Driven Virtual Reality Application Design Nar s Parés npares@iua.upf.es Ro Parés rpares@iua.upf.es Audiovisual Institute, Universitat Pompeu Fabra, Pg. Cirumval. laió, 8 08003 Barelona, Spain www.iua.upf.es/, gvirtual Interation-Driven Virtual

More information

Deliverability on the Interstate Natural Gas Pipeline System

Deliverability on the Interstate Natural Gas Pipeline System DOE/EIA-0618(98) Distribution Category UC-950 Deliverability on the Interstate Natural Gas Pipeline System May 1998 This report was prepared by the, the independent statistial and analytial ageny within

More information