rksuite 90: Fortran 90 software for ordinary dierential equation initial value problems Abstract

Size: px
Start display at page:

Download "rksuite 90: Fortran 90 software for ordinary dierential equation initial value problems Abstract"

Transcription

1 rksuite 90: Fortran 90 software for ordinary dierential equation initial value problems R.W. Brankin The Numerical Algorithm Group Ltd. Wilkinson House, Jordan Hill Road Oxford, OX2 8DR, UK I. Gladwell Department of Mathematics Southern Methodist University Dallas, TX 75275, USA Abstract We present Fortran 90 software for the initial value problem in ordinary dierential equations, including the interfaces and how Fortran 90 language features aord the opportunity both to address dierent types and structures of variables and to provide additional functionality. A novel feature of this software is the availability of Unix scripts which enable presentation of the software for multiple problem types. Keywords: Fortran 90, ordinary dierential equations, initial value problems, recursion, complex AMS Subject classications: 65-04, 34-04, 65L05, 65L06, 65Y15, 65D30 1 Introduction MODULE rksuite 90 contains Fortran 90 software for the initial value problem (IVP) in ordinary dierential equations (ODEs): y 0 = f(t; y); y(a) = y a where a; t; b 2 R; a < t < b (or b < t < a) and y; f; y a 2 R; R n ; R mn ; C; C n or C mn. In rksuite 90 we have deliberately adopted the integration algorithms of the FORTRAN 77 code RKSUITE though modied the code in many ways to exploit the eciencies and facilities of Fortran 90; see [3] for a fuller account of the design issues in FORTRAN 77 and [1] for the FORTRAN 77 codes and documentation. In [2] we outlined our initial design of the Fortran 90 IVP software concentrating on the language features exploited internally; for example, long names, array syntax used internally, OPTIONAL arguments, the use of MODULEs, INTERFACE blocks, and INTENT speciers, etc. Here we discuss the software, its use, and its transformation to address dierent problem types and the algorithmic changes thus required. It is from features such as the OPTIONAL arguments and the transformations that the user will gain most benets in comparison with the FORTRAN 77 software: An easier-to-use interface, once Fortran 90 is familiar; A somewhat more ecient code for large problems when Fortran 90 compilers produce code similarly ecient to that produced by FORTRAN 77 compilers; A more robust code, far more likely to trap subtle user coding errors at compile time; A code able to deal directly with a wider range of problems types; and A code which the moderately sophisticated Unix user can transform further by modifying the scripts supplied. As in RKSUITE, we provide two procedures to integrate across a range and compute approximations to y. One procedure is used to setup the integration with initial values, range, error requirements and various options. The other integrates across the range and computes approximations to y at user specied points t; for more complicated tasks we provide another procedure which integrates one step at a time. This is initialized using the same setup routine. Associated with the step integrator are procedures for interpolation and resetting the integration range. For use with either integrator are utility procedures which provide diagnostic information and memory deallocation. In Section 2, we describe the interfaces provided in rksuite 90. Our emphasis is on the novel features in ODE software design permitted by the use of Fortran 90 (in contrast to FORTRAN 77). Section 3 discusses three design features. The rst is a novel set of transformational tools to enable various formulations of the IVP to be solved directly without prior user transformation. The second concerns the method of managing global variables in a way which is \multiprocessor safe" and this permits the third, the use of recursion. We provide an example using recursion for the invariant imbedding solution 1

2 of boundary value problems. Finally we conclude with a brief section discussing the eorts made to provide tags to identify independent variable types for further transformation. An earlier, but almost identical, version of the code and examples has been available publicly for some time; we indicate where, and how it was tested. As we have seen, we use upper case typewriter face letters for the names of xed reserved Fortran 90 words; also we use lower case typewriter face letters for dummy and actual variables, and italicized lower case letters for names of varying words and mathematical variables. We hope by these means to provide markers for those who are unfamiliar with Fortran 90 syntax. 2 The Fortran 90 Interfaces We need a few preliminaries. Throughout, when computing with REAL machine numbers we work in a consistent precision, or KIND in Fortran 90 terminology. This KIND is set as an integer parameter wp used throughout MODULE rksuite 90 and set once in its own MODULE rksuite 90 prec. For procedures to communicate we dene a special derived TYPE which we give the generic name rk comm. Its contents are PRIVATE so as to prevent accidental modication. They include scalars, arrays whose extents depend on the structure of the dependent variables, character variables and logicals. We employ a number of generic terms: (i) type(independent variable) (ii) type(dependent variable) (iii) dimension (iv) TYPE(rk comm) where type and dimension have dierent, but related, meanings to the Fortran 90 terms TYPE and DIMENSION. In the instances created by our Unix scripts, these terms can be interpreted: (i) type(independent variable) is equivalent to REAL of KIND wp. (ii) type(dependent variable) is equivalent to REAL or COMPLEX of KIND wp. (iii) dimension is: absent for a scalar; DIMENSION(:) for a vector; and DIMENSION(:,:) for a matrix; this is used as an attribute for assumed-shape array arguments which are related to the dependent variable(s). When we specify the dimensionality of the result of a function (possibly array-valued) with respect to the dependent variable(s) y we write dimension (y), which is: absent for a scalar; DIMENSION(SIZE(y)) for a vector; and DIMENSION(SIZE(y,1),SIZE(y,2)) for a matrix. (iv) for the types and dimensionalities of dependent variables currently available in rksuite 90, rk comm is equivalent to real complex zero dimensions rk comm real 0d rk comm complex 0d one dimension rk comm real 1d rk comm complex 1d two dimensions rk comm real 2d rk comm complex 2d Otherwise the usual syntax of Fortran 90 applies. Figure 1 is a simple template using the interfaces described below for the usual dependent variable case, a real vector ODE system integrated over a real interval. The precision-dening MODULE rksuite 90 prec is USEd by MODULE rksuite 90. Hence, PROGRAM integrate f derives its precision from USEing MODULE rksuite 90. When f is an array valued FUNCTION, it must have an explicit INTERFACE, which enables checking at compile-time. This INTERFACE can be provided by including the FUNCTION in a MODULE, as in Figure 1, or by including an INTERFACE block in the calling PROGRAM. To ensure use of the correct precision the MODULE define f should also USE the MODULE rksuite 90 prec. MODULE define_f USE rksuite_90_prec, ONLY:wp! get precision of rksuite_90 CONTAINS REAL(KIND=wp), INTENT(IN) :: t REAL(KIND=wp), DIMENSION(:), INTENT(IN) :: y REAL(KIND=wp), DIMENSION(SIZE(y)) :: f f =...! evaluate f END MODULE define_f PROGRAM integrate_f USE rksuite_90! access rksuite_90 2

3 USE define_f! access f TYPE(rk_comm_real_1d) :: comm! the communication structure REAL(KIND=wp) :: t_start=..., t_end=..., y_start(...)=(/.../), & tolerance=..., thresholds(size(y_start))=(/.../), & t_want, t_inc=..., y_maxvals(size(y_start)), & t_got, y_got(size(y_start))) INTEGER :: flag CALL setup(comm,t_start,y_start,t_end,tolerance,thresholds) DO! Loops until t_end reached t_want = t_want + t_inc IF (t_want > t_end) EXIT! Assumed t_inc positive CALL range_integrate(comm,f,t_want,t_got,y_got,flag=flag)! If optional argument flag omitted never exits range_integrate IF (flag /= 1) EXIT! flag = 1 successful exit PRINT*,' t = ',t_got,' y = ',y_got END DO CALL statistics(comm,y_maxvals=y_maxvals)! optional call PRINT*,' y_maxvals = ',y_maxvals END PROGRAM integrate_f Figure 1: Template for integration - declarations etc. omitted 2.1 The setup and range integrate procedures setup initializes the computation, so is normally called only once; its specication is in Figure 2. A call to setup must precede the rst call to range integrate or step integrate. Any subsequent call to setup reinitializes the computation. The argument comm is an instance of TYPE(rk comm), t start, t end specify the range of integration [a; b], and y start the initial conditions y a. tolerance, thresholds dene the error requirements. More precisely the integration procedures ensure that the local error e in the computed solution y of SIZE magnitude y satises ABS(e) / MAX(magnitude y,thresholds) tolerance componentwise. If the OPTIONAL arguments in setup are omitted, the default is to select a moderate order integration method (equivalent to method=`m'), the integrator range integrate (task=`r'), automatic computation of the initial step (h start=0.0 wp), printing error messages (message=.true.), and no global error assessment (error assess=.false.). SUBROUTINE setup(comm,t start,y start,t end,tolerance,thresholds, & method,task,error assess,h start,message) TYPE(rk comm), INTENT(OUT) :: comm type(independent variable), INTENT(IN) :: t start, t end type(dependent variable), dimension, INTENT(IN) :: y start REAL(KIND=wp), INTENT(IN) :: tolerance REAL(KIND=wp), dimension, INTENT(IN) :: thresholds CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: method, task LOGICAL, OPTIONAL, INTENT(IN) :: error assess, message type(independent variable), OPTIONAL, INTENT(IN) :: h start Figure 2: Specication of setup range integrate computes approximations to the solution at user specied points; its specication is in Figure 3. The array function argument f denes the ODEs as in f; t want species where the solution is required, and y got, yderiv got return the solution, derivative at t got. In a successful integration t got = t want. Otherwise t got is the value of the independent variable where the integration halted; OPTIONALly the error message and the value of flag indicate the diculty. The program terminates on any error unless flag is provided when it returns with flag set to an error reporting value. Problems that may be reported include: too small a step size was required to satisfy the error requirements, the global error assessment (where activated) ceased to be reliable, too many f evaluations have been used, or stiness was detected. RECURSIVE SUBROUTINE range integrate(comm,f,t want,t got,y got,yderiv got,flag) INTERFACE type(independent variable), INTENT(IN) :: t 3

4 type(dependent variable), dimension, INTENT(IN) :: y type(dependent variable), dimension(y) :: f END INTERFACE type(independent variable), INTENT(IN) :: t want type(independent variable), INTENT(OUT) :: t got type(dependent variable), dimension, OPTIONAL, INTENT(OUT) :: INTEGER, OPTIONAL, INTENT(OUT) :: flag y got, yderiv got 2.2 Utility procedures Figure 3: Specication of range integrate The utility procedures can be used in conjunction with either integrator. global error reports the global error assessment if this option is selected in setup (via error assess); its specication is in Figure 4. rms error reports, for each component of the solution, an assessment of the global error so far in the integration. For a successful integration the components of rms error will usually be a moderate factor of tolerance. max error reports the maximum contribution to this assessment and t max error the rst point where max error was observed. SUBROUTINE global error(comm,rms error,max error,t max error) REAL(KIND=wp), dimension, OPTIONAL, INTENT(OUT) :: rms error REAL(KIND=wp), OPTIONAL, INTENT(OUT) :: max error type(independent variable), OPTIONAL, INTENT(OUT) :: t max error Figure 4: Specication of global error statistics reports on the cost and performance of the integration; its specication is in Figure 5. total f calls, step cost and num succ steps report respectively the number of f evaluations used so far (excluding any used for global error assessment), the number of f evaluations required to take a single step with the selected method, and the number of successful steps taken so far. waste reports the fraction of attempted steps which failed to meet the local error requirement. A \large" fraction indicates the problem may be \sti" or the solution may have discontinuities in a low order derivative. h next reports the step size the integrator plans to use for the next step. y maxvals reports the componentwise largest value of ABS(y) computed at any step in the integration so far. It may be used in exploratory computations to determine a suitable setting for thresholds. SUBROUTINE statistics(comm,total f calls,step cost,waste,num succ steps, & h next,y maxvals) INTEGER, OPTIONAL, INTENT(OUT) :: total f calls, step cost, num succ steps REAL(KIND=wp), OPTIONAL, INTENT(OUT) :: waste type(independent variable), OPTIONAL, INTENT(OUT) :: h next REAL(KIND=wp), dimension, OPTIONAL, INTENT(OUT) :: y maxvals Figure 5: Specication of statistics For each of global error and statistics, at least one of the OPTIONAL arguments must be present. That is we require that the call has an action, as a call without an action probably constitutes a user error. Either subroutine may be called at any time in the integration between calls to the integrators. Procedure garbage collect has a single argument of TYPE rk comm and is provided to enable ecient use of memory. It should be called after completion of each completed or failed integration and prior to any re-use of the same instance of an argument in a new integration. 2.3 step integrate and associated procedures step integrate is designed for tasks requiring close monitoring of the integration; its interface is in Figure 6. To ease use, less common demands are handled by the auxiliary procedures interpolate and reset t end. step integrate integrates the solution one step at a time from t start toward t end. Arguments comm, f, flag are as described for range integrate. y now, yderiv now report the solution, derivative at t now. If the integration has not been successful t now, y now, yderiv now retain their values at the end of the previous step. 4

5 RECURSIVE SUBROUTINE step integrate(comm,f,t now,y now,yderiv now,flag) INTERFACE type(independent variable), INTENT(IN) :: t type(dependent variable), dimension, INTENT(IN) :: y type(dependent variable), dimension(y) :: f END INTERFACE type(independent variable), INTENT(OUT) :: t now type(dependent variable), dimension, OPTIONAL, INTENT(OUT) :: y now, yderiv now INTEGER, OPTIONAL, INTENT(OUT) :: flag Figure 6: Specication of step integrate Procedure reset t end is used to reset the end of the integration range, for stepping to output points using step integrate; its specication is in Figure 7. The argument t end new redenes the end of the range. reset t end should be used in preference to reinitializing using setup. It cannot be used to redene the direction of integration. SUBROUTINE reset t end(comm,t end new) type(independent variable), INTENT(IN) :: t end new Figure 7: Specication of reset t end In general, the most ecient way to compute the solution at specied points is to use interpolate; its specication is in Figure 8. It uses information calculated over the step just taken and may require additional evaluations of f in that step. (The number of additional evaluations required on any one step is xed for any number of output points.) t want species the value of the independent variable where a solution value is required. Approximations to the solution, derivative are returned in y want, yderiv want. At least one of y want, yderiv want must be present so that the call has an action. RECURSIVE SUBROUTINE interpolate(comm,f,t want,y want,yderiv want) INTERFACE type(independent variable), INTENT(IN) :: t type(dependent variable), dimension, INTENT(IN) :: y type(dependent variable), dimension(y) :: f END INTERFACE type(independent variable), INTENT(IN) :: t want type(dependent variable), dimension, OPTIONAL, INTENT(OUT) :: y want,yderiv want Figure 8: Specication of interpolate The availability in rksuite 90 of an interpolant with an internal power series storage mechanism permits a relatively straightforward attempt at event location. In [6], we described a robust technique for a limited event location capability, for problems commonly solved by inverse interpolation. It describes a FORTRAN 77 event location code that can be used \side-by-side" with any FORTRAN 77 stepby-step integrator with the appropriate type of power series interpolant in the equivalent of a reverse communication scheme. Equally, it could be used side-by-side with step integrate since FORTRAN 77 is a subset of Fortran Internal Design of rksuite 90 The major programming language and algorithmic design issues for the initial release of rksuite 90 were discussed in [2]. This nal version contains three sets of changes: the treatment of a variety of dependent variables via transformations, the handling of global variables, and permitting recursion. 3.1 Dependent Variables Almost all IVP solvers treat the case t 2 R; y 2 R n. As a result a user whose problem naturally has a solution y 2 R or R mn or a complex equivalent, is forced to recast the problem in R n, a possibly 5

6 error prone task with a potentially inecient result. We have treated these cases directly, aiming to maintain just one copy of the base software. We restrict the independent variable so that t 2 R, but we have isolated the specications of local variables of type(independent variable) to ease production of future codes with t in another eld. We consider three aspects of this problem: the type of, the shape of, and the arithmetic operations involved with the dependent variable. We start from the software for y 2 R n. In the code for y 2 R n we have identied with a tag (a special in-line comment) all declarative sections of the code involving dependent variables. (We have used IMPLICIT NONE so that every entity has been declared.) This tag automatically identies all dependent variable quantities with an associated rank. However there are other quantities in the code which must have the same shape as the dependent variables. A further special tag has been inserted into the declarative sections to identify these. This tagging partially addresses the questions of type and shape of the variables, as mentioned above. For the arithmetic aspect we have examined all assignments involving dependent variables. Throughout, we have ensured that array assignments a = :::b + :::c are used. That is extents are not specied since the arrays are always conformable. We nd that: all divisions involve real conformable divisors; multiplications of dependent variable quantities involve a real scalar multiplier; the intrinsic ABS is used to return real quantities (magnitudes); the intrinsic MAX is used on real conformable quantities; and the intrinsics MINVAL, MAXVAL are used on real quantities. All operations involving y 2 R n require no transformation to address y 2 C n. Similarly, almost all assignments involving arrays require no transformation when considering y 2 R and y 2 R mn. The exceptions are expressions using the intrinsics MAXVAL, MINVAL, SUM which must take array arguments and are therefore inappropriate for y 2 R. Instances of these intrinsics have been specially tagged so that they can be transformed. We have created sed scripts exploiting the tags for use in a Unix environment to: 1. create a complex version from a real version 2. create a 2d version from a 1d version 3. create a 0d version from a 1d version Two minor diculties are addressed in the scripts. The rst involves using the ALLOCATE statement to assign internal workspace via pointers. The exact extents of the arrays to be allocated must be supplied and depend on the shape of y. We have inserted special tags so that the `1d to 2d' script can add the second dimension of appropriate size, and the `1d to 0d' script can remove the dimension information and allocate the equivalent scalar pointer. A residual problem in the scalar case is that some of the elemental array intrinsics used do not permit scalar arguments, requiring a work-around in the sed script. The second diculty arises in the internal procedures implementing a stiness check. A nonlinear power method is used to estimate eigenvalues of the Jacobian of f. It requires computation of inner products. For y; z 2 R n this inner product is simply y T z. However for y; z 2 C n the inner product is y T z. The quantity (y T z) is also required. Unfortunately the Fortran 90 elemental intrinsic CONJG requires an argument of type COMPLEX. In a complex arithmetic version of the code there are two places where CONJG is required. As before we have inserted tags so that the `real to complex' script can make the appropriate edit. Note that for y; z 2 R mn or C mn the inner product remains well dened in Fortran 90 since the matrix-matrix multiplication is performed elementally. To derive a generic code, we restructured the stiness check to use complex arithmetic even in the real arithmetic case (e.g., in a quadratic equation solver). After these changes, the results for y 2 R n are identical to those computed using the codes described in [1] and [3]. When solving problems with y 2 R or y 2 C, the usual denition of stiness (for systems) does not apply. However, it is still possible for a scalar ODE to be sti. Consider y 0 (t) = k(y(t)? p(t)) + p 0 (t); y(0) = A with solution y(t) = (A? p(0))e kt + p(t); see page 384 of [5]. If p(t) is smooth and slowly varying and k is large and negative this problem is sti. We have solved this problem using rksuite 90 for p(t) = cos(t); A = 0 and k =?10 n ; n = 1; 2; 3; : : :. Stiness is agged for all n > 2 on long enough ranges of integration. So the default mechanisms in the stiness check work here. Similarly, in RKSUITE and rksuite 90 these mechanisms work both for dependent variable arrays of length one and for scalars. The alternate versions of rksuite 90 are produced using a further Unix script provided with the Fortran 90 software. The user has the option of generating any individual version or all six. The version(s) are bundled in a generic interface which hides the number of interfaces. That is, the user sees just one each of setup, range integrate, etc. The Fortran 90 compiler determines the specic version by the dierences in types of the arguments in each generic interface. Particularly, the type of rk comm is used to determine which instance to use if there are no other dierences. 6

7 3.2 Global Variables In RKSUITE global variables were passed in COMMON or, for those of length depending on n, in an unspecied work array passed as an argument between procedures. In the rst version of rksuite 90 the same information was kept in PRIVATE (global variables) in a MODULE. This is natural in Fortran 90 but is not \multiprocessor safe" (nor is COMMON) and hence also unsuitable for multithreading environments as separate copies of the global variables cannot be made. So, we have reverted to the traditional \packed work array" approach using the derived TYPE rk comm for passing global information between procedures. A user (or system) may declare as many instances of TYPE(rk comm) as required. A side eect of the change in handling of global variables is to permit simultaneous (side-by-side) integrations to be performed in the same program. 3.3 Recursion The approach adopted for global variables also enables recursive calls to the integrators. Hence a differential equation can be dened in terms of the solution of other dierential equations. For example, recursion permits the direct evaluation of multidimensional quadrature using just the one-dimensional integration procedure dened by rksuite 90. It also permits solving invariant imbedding problems in a natural (though inecient) way. Consider the boundary value problem y 00 (t)? y(t) = 0; y(0) = 1; y 0 (T ) =?e?t with general solution y(t) = C 1e t + C 2e?t. The boundary conditions force C 1 = 0; C 2 = 1. Forward or backward shooting will be unsuccessful for large T due to the exponential solution behavior, but invariant imbedding may be used. As shown on page 68 of [4], an invariant imbedding method consists of (i) Integrate together the ODEs (ii) Find ^x by solving (iii) Integrate ODE u 0 (t) = 1? u(t) 2 ; v 0 (t) =?u(t)v(t); t 2 [0; T ]; u(0) = 0; v(0) = 1: \backwards" from t = T to t = 0. u(t )^x = e?t? v(t ): x 0 (t) = u(t)x(t) + v(t); x(t ) = ^x; t 2 [0; T ] The solution of the boundary value problem is y(t) = u(t)x(t) + v(t). To solve (iii), we need the solutions of (i) everywhere. Probably the most ecient approach would be to save the interpolants for u(t) and v(t) everywhere on [0; T ] and evaluate as necessary when solving (iii). This may be achieved by saving copies of rk comm on every step when using step integrate. Then, the saved copies are used in reverse order in calls to interpolate when integrating (iii). A more elegant, and much more expensive, approach is to use recursion calling step integrate to solve (iii) and calling range integrate for (i) from the function dening the ODE for (iii); a template is given in Figure 9. (Note that range integrate calls step integrate so this is a recursive call.) 4 Conclusions and Availability We have developed software to solve initial value problems when the dependent variables y 2 R, R n, R mn, C, C n, or C mn and the independent variable t 2 R. It would be a simple matter to address y of dimension greater than two. We have identied and tagged those parts of the declarative sections which involve quantities of the type dependent variable and independent variable. This should facilitate the creation of initial value solvers with variables in elds dierent to those already considered. For example, it is relatively straightforward to address t 2 C integrating along a complex straight line; indeed we have a version for this case produced by a further Unix script transformation, not included with rksuite 90. In contrast, modifying the software for integration along an arc requires further transformational tools to incorporate the denition of the arc and to measure distance along it (corresponding to a Fortran 90 intrinsic in the simple straight line cases); hence it requires a variation of the interface. To address other elds, we must redene various operations (such as addition, multiplication by a real scalar, a magnitude function, and an inner product). Implementation could be achieved by overloading the operators (using overloading procedures, with all the associated overhead). The interpretation of stiness in these cases requires careful rethinking. Indeed, our complex straight line version has an automatically produced stiness check but it is not clear that it monitors what is usually considered to be stiness. 7

8 MODULE forward USE rksuite_90_prec CONTAINS FUNCTION g(t,y) g(:) = (/ 1.0_wp - y(1)**2, -y(1)*y(2) /) END FUNCTION g END MODULE forward MODULE backward USE rksuite_90 USE forward TYPE(rk_comm_real_1d) :: comm_f! Type for forward integration REAL(KIND=wp) :: u, v CONTAINS u = 0.0_wp; v = 1.0_wp; y_start_f(:)= (/u, v/) t_end_f = t; twant = t IF (t_end_f /= t_start_f) THEN CALL setup(comm_f,t_start_f,y_start_f,t_end_f,tol,thresh_f) CALL range_integrate(comm_f,g,twant,t_got_f,y_got_f,yderiv_got_f) CALL collect_garbage(comm_f) u = y_got_f(1); v = y_got_f(2) END IF f = u*y + v END MODULE backward PROGRAM invar_imbed USE backward! Note uses forward and rksuite_90 TYPE(rk_comm_real_0d) :: comm_b! Type for backward integration! The forward integration CALL setup(comm_f,t_start_f,y_start_f,t_end_f,tol,thres_f,method='h') twant = t_end_f CALL range_integrate(comm_f,g,twant,t_got_f,y_got_f,yderiv_got_f) CALL collect_garbage(comm_f)! The backward integration y_start_b = (exp(-t_end_f) - y_got_f(2))/y_got_f(1) CALL setup(comm_b,t_start_b,y_start_b,t_end_b,tol,thres_b, & task='s',method='h') DO CALL step_integrate(comm_b,f,t_now_b,y_now_b) PRINT*,' t = ',t_now_b,' sol = ',u*y_now_b+v, ' true = ',exp(-t_now_b) IF (t_now_b == t_end_b) EXIT END DO END PROGRAM invar_imbed Figure 9: An invariant imbedding example - declarations etc. omitted 8

9 The package comprises the base software (for y 2 R n ), the Unix scripts to generate alternate versions, the documentation, and several example programs, including some using the alternate versions. The rst version of the software has been available on netlib (at netlib@research.att.com and its various mirror sites) in directory ode/rksuite and in the NAG Fortran 90 software repository at This software has been available and has been accessed frequently since mid The authors have received no error reports. The codes were developed using the NAGWare f90 compiler and tested on a variety of platforms using this compiler. They have also been tested using the latest versions available to us of the following: the DEC OSF/1 Fortran 90 compiler, the Cray CF90 compiler and the IBM AIX XL FORTRAN Compiler/6000. Acknowledgement The authors thank Jeremy Du Croz and the anonymous referees for their suggestions on improving the presentation of this paper. References [1] R.W. Brankin, I. Gladwell and L.F. Shampine, \RKSUITE: a Suite of Runge-Kutta Codes for the Initial Value Problem for ODEs", Softreport 92-S1, Math. Dept., Southern Methodist University, Dallas, Texas, U.S.A, 1992, (also available by anonymous ftp from Southern Methodist University and from netlib in directory ode/rksuite). [2] R.W. Brankin and I. Gladwell, \A Fortran 90 Version of RKSUITE: An ODE Initial Value Solver", Annals of Numer. Math., 1 (1994), [3] R.W. Brankin, I. Gladwell and L.F. Shampine, \RKSUITE: A Suite of Explicit Runge-Kutta Codes", pp of \Contributions to Numerical Mathematics" (ed. R.P. Agarwal), WSSIAA 2, World Scientic Press, [4] G.H. Meyer, \Initial Value Methods for Boundary Value Problems: Theory and Application of Invariant Imbedding", Math in Sci. and Eng., 100, Academic Press, [5] L.F. Shampine, \Numerical Solution of Ordinary Dierential Equations", Chapman and Hall, [6] L.F. Shampine, I. Gladwell and R.W. Brankin, Reliable Solution of Event Location Problems for ODEs, ACM Trans. Math. Software 17 (1991) pp

NAG Fortran Library Routine Document D02PZF.1

NAG Fortran Library Routine Document D02PZF.1 NAG Fortran Library Routine Document Note: before using this routine, please read the Users Note for your implementation to check the interpretation of bold italicised terms and other implementation-dependent

More information

D02PCF NAG Fortran Library Routine Document

D02PCF NAG Fortran Library Routine Document D02PCF NAG Fortran Library Routine Document Note. Before using this routine, please read the Users Note for your implementation to check the interpretation of bold italicised terms and other implementation-dependent

More information

2 3. Syllabus Time Event 9:00{10:00 morning lecture 10:00{10:30 morning break 10:30{12:30 morning practical session 12:30{1:30 lunch break 1:30{2:00 a

2 3. Syllabus Time Event 9:00{10:00 morning lecture 10:00{10:30 morning break 10:30{12:30 morning practical session 12:30{1:30 lunch break 1:30{2:00 a 1 Syllabus for the Advanced 3 Day Fortran 90 Course AC Marshall cuniversity of Liverpool, 1997 Abstract The course is scheduled for 3 days. The timetable allows for two sessions a day each with a one hour

More information

NAG Library Function Document nag_ode_ivp_rk_setup (d02pvc)

NAG Library Function Document nag_ode_ivp_rk_setup (d02pvc) NAG Library Function Document nag_ode_ivp_rk_setup () 1 Purpose nag_ode_ivp_rk_setup () is a setup function which must be called prior to the first call of either of the integration functions nag_ode_ivp_rk_range

More information

D02PDF NAG Fortran Library Routine Document

D02PDF NAG Fortran Library Routine Document D02 Ordinary Differential Equations D02PDF NAG Fortran Library Routine Document Note. Before using this routine, please read the Users Note for your implementation to check the interpretation of bold italicised

More information

NAG Library Function Document nag_ode_ivp_rk_interp (d02pxc)

NAG Library Function Document nag_ode_ivp_rk_interp (d02pxc) d02 Ordinary Differential NAG Library Function Document nag_ode_ivp_rk_interp () 1 Purpose nag_ode_ivp_rk_interp () is a function to compute the solution of a system of ordinary differential equations

More information

Our Strategy for Learning Fortran 90

Our Strategy for Learning Fortran 90 Our Strategy for Learning Fortran 90 We want to consider some computational problems which build in complexity. evaluating an integral solving nonlinear equations vector/matrix operations fitting data

More information

NAG Library Function Document nag_ode_ivp_rkts_errass (d02puc)

NAG Library Function Document nag_ode_ivp_rkts_errass (d02puc) d02 Ordinary Differential d02puc NAG Library Function Document nag_ode_ivp_rkts_errass (d02puc) 1 Purpose nag_ode_ivp_rkts_errass (d02puc) provides details about global error assessment computed during

More information

Welcome. Modern Fortran (F77 to F90 and beyond) Virtual tutorial starts at BST

Welcome. Modern Fortran (F77 to F90 and beyond) Virtual tutorial starts at BST Welcome Modern Fortran (F77 to F90 and beyond) Virtual tutorial starts at 15.00 BST Modern Fortran: F77 to F90 and beyond Adrian Jackson adrianj@epcc.ed.ac.uk @adrianjhpc Fortran Ancient History (1967)

More information

Module 5.5: nag sym bnd lin sys Symmetric Banded Systems of Linear Equations. Contents

Module 5.5: nag sym bnd lin sys Symmetric Banded Systems of Linear Equations. Contents Module Contents Module 5.5: nag sym bnd lin sys Symmetric Banded Systems of nag sym bnd lin sys provides a procedure for solving real symmetric or complex Hermitian banded systems of linear equations with

More information

NAG Fortran Library Routine Document D02KAF.1

NAG Fortran Library Routine Document D02KAF.1 NAG Fortran Library Routine Document Note: before using this routine, please read the Users Note for your implementation to check the interpretation of bold italicised terms and other implementation-dependent

More information

In context with optimizing Fortran 90 code it would be very helpful to have a selection of

In context with optimizing Fortran 90 code it would be very helpful to have a selection of 1 ISO/IEC JTC1/SC22/WG5 N1186 03 June 1996 High Performance Computing with Fortran 90 Qualiers and Attributes In context with optimizing Fortran 90 code it would be very helpful to have a selection of

More information

Subroutines and Functions

Subroutines and Functions Subroutines and Functions Procedures: Subroutines and Functions There are two types of procedures: SUBROUTINE: a parameterized named sequence of code which performs a specific task and can be invoked from

More information

Efficiency of second-order differentiation schemes by algorithmic differentiation: Case Study

Efficiency of second-order differentiation schemes by algorithmic differentiation: Case Study Efficiency of second-order differentiation schemes by algorithmic differentiation: Case Study Thorsten Lajewski Supervisor: Johannes Lotz STCE, RWTH Aachen May 6, 2013 1 Introduction In numerical calculations

More information

Module 7.2: nag sym fft Symmetric Discrete Fourier Transforms. Contents

Module 7.2: nag sym fft Symmetric Discrete Fourier Transforms. Contents Transforms Module Contents Module 7.2: nag sym fft Symmetric Discrete Fourier Transforms nag sym fft provides procedures for computations involving one-dimensional real symmetric discrete Fourier transforms.

More information

Review More Arrays Modules Final Review

Review More Arrays Modules Final Review OUTLINE 1 REVIEW 2 MORE ARRAYS Using Arrays Why do we need dynamic arrays? Using Dynamic Arrays 3 MODULES Global Variables Interface Blocks Modular Programming 4 FINAL REVIEW THE STORY SO FAR... Create

More information

D02KAF NAG Fortran Library Routine Document

D02KAF NAG Fortran Library Routine Document D02KAF NAG Fortran Library Routine Document Note. Before using this routine, please read the Users Note for your implementation to check the interpretation of bold italicised terms and other implementation-dependent

More information

International Standards Organisation. Parameterized Derived Types. Fortran

International Standards Organisation. Parameterized Derived Types. Fortran International Standards Organisation Parameterized Derived Types in Fortran Technical Report defining extension to ISO/IEC 1539-1 : 1996 {Produced 4-Jul-96} THIS PAGE TO BE REPLACED BY ISO CS ISO/IEC 1

More information

Hs01006: Language Features, Arithmetic Operators *

Hs01006: Language Features, Arithmetic Operators * OpenStax-CNX module: m37146 1 Hs01006: Language Features, Arithmetic Operators * R.G. (Dick) Baldwin This work is produced by OpenStax-CNX and licensed under the Creative Commons Attribution License 4.0

More information

Khoral Research, Inc. Khoros is a powerful, integrated system which allows users to perform a variety

Khoral Research, Inc. Khoros is a powerful, integrated system which allows users to perform a variety Data Parallel Programming with the Khoros Data Services Library Steve Kubica, Thomas Robey, Chris Moorman Khoral Research, Inc. 6200 Indian School Rd. NE Suite 200 Albuquerque, NM 87110 USA E-mail: info@khoral.com

More information

Cedar Fortran Programmer's Manual 1. Jay Hoeinger. Center for Supercomputing Research and Development. Urbana, Illinois

Cedar Fortran Programmer's Manual 1. Jay Hoeinger. Center for Supercomputing Research and Development. Urbana, Illinois Cedar Fortran Programmer's Manual 1 Jay Hoeinger Center for Supercomputing Research and Development University of Illinois at Urbana-Champaign Urbana, Illinois 61801 June 14, 1993 1 This work was supported

More information

residual residual program final result

residual residual program final result C-Mix: Making Easily Maintainable C-Programs run FAST The C-Mix Group, DIKU, University of Copenhagen Abstract C-Mix is a tool based on state-of-the-art technology that solves the dilemma of whether to

More information

TENTH WORLD CONGRESS ON THE THEORY OF MACHINES AND MECHANISMS Oulu, Finland, June 20{24, 1999 THE EFFECT OF DATA-SET CARDINALITY ON THE DESIGN AND STR

TENTH WORLD CONGRESS ON THE THEORY OF MACHINES AND MECHANISMS Oulu, Finland, June 20{24, 1999 THE EFFECT OF DATA-SET CARDINALITY ON THE DESIGN AND STR TENTH WORLD CONGRESS ON THE THEORY OF MACHINES AND MECHANISMS Oulu, Finland, June 20{24, 1999 THE EFFECT OF DATA-SET CARDINALITY ON THE DESIGN AND STRUCTURAL ERRORS OF FOUR-BAR FUNCTION-GENERATORS M.J.D.

More information

Plaintext (P) + F. Ciphertext (T)

Plaintext (P) + F. Ciphertext (T) Applying Dierential Cryptanalysis to DES Reduced to 5 Rounds Terence Tay 18 October 1997 Abstract Dierential cryptanalysis is a powerful attack developed by Eli Biham and Adi Shamir. It has been successfully

More information

ParaFEM Coding Standard for Fortran 90. Contents. 1.0 Introduction. 2.0 Documentation. 2.1 External Documentation

ParaFEM Coding Standard for Fortran 90. Contents. 1.0 Introduction. 2.0 Documentation. 2.1 External Documentation ParaFEM Coding Standard for Fortran 90 This standard has been prepared by Lee Margetts, Francisco Calvo and Vendel Szeremi at the University of Manchester. It is based on Version 1.1 of the European Standards

More information

Mid-Year Report. Discontinuous Galerkin Euler Equation Solver. Friday, December 14, Andrey Andreyev. Advisor: Dr.

Mid-Year Report. Discontinuous Galerkin Euler Equation Solver. Friday, December 14, Andrey Andreyev. Advisor: Dr. Mid-Year Report Discontinuous Galerkin Euler Equation Solver Friday, December 14, 2012 Andrey Andreyev Advisor: Dr. James Baeder Abstract: The focus of this effort is to produce a two dimensional inviscid,

More information

7. Procedures and Structured Programming

7. Procedures and Structured Programming 7. Procedures and Structured Programming ONE BIG PROGRAM external procedure: separated small and reusable program units to conduct individual subtasks smaller main program Each program unit can be debugged

More information

Outline. Computer Science 331. Information Hiding. What This Lecture is About. Data Structures, Abstract Data Types, and Their Implementations

Outline. Computer Science 331. Information Hiding. What This Lecture is About. Data Structures, Abstract Data Types, and Their Implementations Outline Computer Science 331 Data Structures, Abstract Data Types, and Their Implementations Mike Jacobson 1 Overview 2 ADTs as Interfaces Department of Computer Science University of Calgary Lecture #8

More information

Module 28.3: nag mv rotation Rotations. Contents

Module 28.3: nag mv rotation Rotations. Contents Multivariate Analysis Module Contents Module 28.3: nag mv rotation Rotations nag mv rotation contains a procedure to compute rotations for sets of data values. Contents Introduction..............................................................

More information

Allocating Storage for 1-Dimensional Arrays

Allocating Storage for 1-Dimensional Arrays Allocating Storage for 1-Dimensional Arrays Recall that if we know beforehand what size we want an array to be, then we allocate storage in the declaration statement, e.g., real, dimension (100 ) :: temperatures

More information

Algorithmic "imperative" language

Algorithmic imperative language Algorithmic "imperative" language Undergraduate years Epita November 2014 The aim of this document is to introduce breiy the "imperative algorithmic" language used in the courses and tutorials during the

More information

Fortran. (FORmula TRANslator) History

Fortran. (FORmula TRANslator) History Fortran (FORmula TRANslator) History FORTRAN vs. Fortran 1954 FORTRAN first successful high level language John Backus (IBM) 1958 FORTRAN II (Logical IF, subroutines, functions) 1961 FORTRAN IV 1966 FORTRAN

More information

Appendix D. Fortran quick reference

Appendix D. Fortran quick reference Appendix D Fortran quick reference D.1 Fortran syntax... 315 D.2 Coarrays... 318 D.3 Fortran intrisic functions... D.4 History... 322 323 D.5 Further information... 324 Fortran 1 is the oldest high-level

More information

Lecture V: Introduction to parallel programming with Fortran coarrays

Lecture V: Introduction to parallel programming with Fortran coarrays Lecture V: Introduction to parallel programming with Fortran coarrays What is parallel computing? Serial computing Single processing unit (core) is used for solving a problem One task processed at a time

More information

An Introduction to Numerical Analysis

An Introduction to Numerical Analysis Weimin Han AMCS & Dept of Math University of Iowa MATH:38 Example 1 Question: What is the area of the region between y = e x 2 and the x-axis for x 1? Answer: Z 1 e x 2 dx = : 1.9.8.7.6.5.4.3.2.1 1.5.5

More information

International Journal of Foundations of Computer Science c World Scientic Publishing Company DFT TECHNIQUES FOR SIZE ESTIMATION OF DATABASE JOIN OPERA

International Journal of Foundations of Computer Science c World Scientic Publishing Company DFT TECHNIQUES FOR SIZE ESTIMATION OF DATABASE JOIN OPERA International Journal of Foundations of Computer Science c World Scientic Publishing Company DFT TECHNIQUES FOR SIZE ESTIMATION OF DATABASE JOIN OPERATIONS KAM_IL SARAC, OMER E GEC_IO GLU, AMR EL ABBADI

More information

15 FUNCTIONS IN C 15.1 INTRODUCTION

15 FUNCTIONS IN C 15.1 INTRODUCTION 15 FUNCTIONS IN C 15.1 INTRODUCTION In the earlier lessons we have already seen that C supports the use of library functions, which are used to carry out a number of commonly used operations or calculations.

More information

Assignment 4. Overview. Prof. Stewart Weiss. CSci 335 Software Design and Analysis III Assignment 4

Assignment 4. Overview. Prof. Stewart Weiss. CSci 335 Software Design and Analysis III Assignment 4 Overview This assignment combines several dierent data abstractions and algorithms that we have covered in class, including priority queues, on-line disjoint set operations, hashing, and sorting. The project

More information

Annex A (Informative) Collected syntax The nonterminal symbols pointer-type, program, signed-number, simple-type, special-symbol, and structured-type

Annex A (Informative) Collected syntax The nonterminal symbols pointer-type, program, signed-number, simple-type, special-symbol, and structured-type Pascal ISO 7185:1990 This online copy of the unextended Pascal standard is provided only as an aid to standardization. In the case of dierences between this online version and the printed version, the

More information

Chapter 4. Fortran Arrays

Chapter 4. Fortran Arrays Chapter 4. Fortran Arrays Fortran arrays are any object with the dimension attribute. In Fortran 90/95, and in HPF, arrays may be very different from arrays in older versions of Fortran. Arrays can have

More information

Subroutines, Functions and Modules

Subroutines, Functions and Modules Subroutines, Functions and Modules Subdividing the Problem Most problems are thousands of lines of code. Few people can grasp all of the details. Good design principle: Exhibit the overall structure in

More information

Module 19.1: nag ip Integer Programming. Contents

Module 19.1: nag ip Integer Programming. Contents Operations Research Module Contents Module 19.1: nag ip Integer Programming nag ip contains a procedure for solving zero-one, general, mixed or all integer linear programming problems. Contents Introduction..............................................................

More information

SUBPROGRAMS AND MODULES

SUBPROGRAMS AND MODULES SUBPROGRAMS AND MODULES FORTRAN PROGRAMING Zerihun Alemayehu AAiT.CED Program structure Advantages of subprograms Program units can be written and tested independently A program unit that has a well defined

More information

Essential Introduction to the NAG Fortran Library

Essential Introduction to the NAG Fortran Library Introduction Essential Introduction to the NAG Fortran Library This document is essential reading for any prospective user of the Library. Contents 1 The Library and its Documentation 2 1.1 Structure of

More information

Some elements for Matlab programming

Some elements for Matlab programming Some elements for Matlab programming Nathalie Thomas 2018 2019 Matlab, which stands for the abbreviation of MATrix LABoratory, is one of the most popular language for scientic computation. The classical

More information

Goals for This Lecture:

Goals for This Lecture: Goals for This Lecture: Learn about multi-dimensional (rank > 1) arrays Learn about multi-dimensional array storage Learn about the RESHAPE function Learn about allocatable arrays & the ALLOCATE and DEALLOCATE

More information

NAGWare f95 and reliable, portable programming.

NAGWare f95 and reliable, portable programming. NAGWare f95 and reliable, portable programming. Malcolm Cohen The Numerical Algorithms Group Ltd., Oxford How to detect errors using NAGWare f95, and how to write portable, reliable programs. Support for

More information

Worst-case running time for RANDOMIZED-SELECT

Worst-case running time for RANDOMIZED-SELECT Worst-case running time for RANDOMIZED-SELECT is ), even to nd the minimum The algorithm has a linear expected running time, though, and because it is randomized, no particular input elicits the worst-case

More information

Edge detection based on single layer CNN simulator using RK6(4)

Edge detection based on single layer CNN simulator using RK6(4) Edge detection based on single layer CNN simulator using RK64) Osama H. Abdelwahed 1, and M. El-Sayed Wahed 1 Mathematics Department, Faculty of Science, Suez Canal University, Egypt Department of Computer

More information

Concurrent Programming Lecture 3

Concurrent Programming Lecture 3 Concurrent Programming Lecture 3 3rd September 2003 Atomic Actions Fine grain atomic action We assume that all machine instructions are executed atomically: observers (including instructions in other threads)

More information

An Object Oriented Finite Element Library

An Object Oriented Finite Element Library An Object Oriented Finite Element Library Release 3.1.0 Rachid Touzani Laboratoire de Mathématiques Blaise Pascal Université Clermont Auvergne 63177 Aubière, France e-mail: Rachid.Touzani@univ-bpclermont.fr

More information

Program Structure and Format

Program Structure and Format Program Structure and Format PROGRAM program-name IMPLICIT NONE specification part execution part subprogram part END PROGRAM program-name Comments Comments should be used liberally to improve readability.

More information

Bits, Words, and Integers

Bits, Words, and Integers Computer Science 52 Bits, Words, and Integers Spring Semester, 2017 In this document, we look at how bits are organized into meaningful data. In particular, we will see the details of how integers are

More information

Unit-II Programming and Problem Solving (BE1/4 CSE-2)

Unit-II Programming and Problem Solving (BE1/4 CSE-2) Unit-II Programming and Problem Solving (BE1/4 CSE-2) Problem Solving: Algorithm: It is a part of the plan for the computer program. An algorithm is an effective procedure for solving a problem in a finite

More information

Fortran 90 - A thumbnail sketch

Fortran 90 - A thumbnail sketch Fortran 90 - A thumbnail sketch Michael Metcalf CERN, Geneva, Switzerland. Abstract The main new features of Fortran 90 are presented. Keywords Fortran 1 New features In this brief paper, we describe in

More information

PACKAGE SPECIFICATION HSL 2013

PACKAGE SPECIFICATION HSL 2013 PACKAGE SPECIFICATION HSL 2013 1 SUMMARY Given a rank-one or rank-two allocatable array, reallocates the array to have a different size, and can copy all or part of the original array into the new array.

More information

NAG Library Routine Document C05RBF.1

NAG Library Routine Document C05RBF.1 C05 Roots of One or More Transcendental Equations NAG Library Routine Document Note: before using this routine, please read the Users Note for your implementation to check the interpretation of bold italicised

More information

A Multiple-Precision Division Algorithm

A Multiple-Precision Division Algorithm Digital Commons@ Loyola Marymount University and Loyola Law School Mathematics Faculty Works Mathematics 1-1-1996 A Multiple-Precision Division Algorithm David M. Smith Loyola Marymount University, dsmith@lmu.edu

More information

M4.1-R3: PROGRAMMING AND PROBLEM SOLVING THROUGH C LANGUAGE

M4.1-R3: PROGRAMMING AND PROBLEM SOLVING THROUGH C LANGUAGE M4.1-R3: PROGRAMMING AND PROBLEM SOLVING THROUGH C LANGUAGE NOTE: 1. There are TWO PARTS in this Module/Paper. PART ONE contains FOUR questions and PART TWO contains FIVE questions. 2. PART ONE is to be

More information

Conditional Branching is not Necessary for Universal Computation in von Neumann Computers Raul Rojas (University of Halle Department of Mathematics an

Conditional Branching is not Necessary for Universal Computation in von Neumann Computers Raul Rojas (University of Halle Department of Mathematics an Conditional Branching is not Necessary for Universal Computation in von Neumann Computers Raul Rojas (University of Halle Department of Mathematics and Computer Science rojas@informatik.uni-halle.de) Abstract:

More information

Programming Languages

Programming Languages Programming Languages Tevfik Koşar Lecture - VIII February 9 th, 2006 1 Roadmap Allocation techniques Static Allocation Stack-based Allocation Heap-based Allocation Scope Rules Static Scopes Dynamic Scopes

More information

Name :. Roll No. :... Invigilator s Signature : INTRODUCTION TO PROGRAMMING. Time Allotted : 3 Hours Full Marks : 70

Name :. Roll No. :... Invigilator s Signature : INTRODUCTION TO PROGRAMMING. Time Allotted : 3 Hours Full Marks : 70 Name :. Roll No. :..... Invigilator s Signature :.. 2011 INTRODUCTION TO PROGRAMMING Time Allotted : 3 Hours Full Marks : 70 The figures in the margin indicate full marks. Candidates are required to give

More information

Solving 0 = F (t; y(t);y 0 (t)) in Matlab L.F. Shampine Mathematics Department Southern Methodist University Dallas, TX U.S.A.

Solving 0 = F (t; y(t);y 0 (t)) in Matlab L.F. Shampine Mathematics Department Southern Methodist University Dallas, TX U.S.A. Solving 0 = F (t; y(t);y 0 (t)) in Matlab L.F. Shampine Mathematics Department Southern Methodist University Dallas, TX 75275 U.S.A. lshampin@mail.smu.edu Abstract Important algorithms and design decisions

More information

MACHINE INDEPENDENCE IN COMPILING*

MACHINE INDEPENDENCE IN COMPILING* MACHINE INDEPENDENCE IN COMPILING* Harry D. Huskey University of California Berkeley, California, USA Since 1958, there has been a substantial interest in the development of problem-oriented languages

More information

Page 1 of 7. Date: 1998/05/31 To: WG5 From: J3/interop Subject: Interoperability syntax (Part 1) References: J3/98-132r1, J3/98-139

Page 1 of 7. Date: 1998/05/31 To: WG5 From: J3/interop Subject: Interoperability syntax (Part 1) References: J3/98-132r1, J3/98-139 (J3/98-165r1) Date: 1998/05/31 To: WG5 From: J3/interop Subject: Interoperability syntax (Part 1) References: J3/98-132r1, J3/98-139 ISO/IEC JTC1/SC22/WG5 N1321 Page 1 of 7 Describing pre-defined C data

More information

An interesting related problem is Buffon s Needle which was first proposed in the mid-1700 s.

An interesting related problem is Buffon s Needle which was first proposed in the mid-1700 s. Using Monte Carlo to Estimate π using Buffon s Needle Problem An interesting related problem is Buffon s Needle which was first proposed in the mid-1700 s. Here s the problem (in a simplified form). Suppose

More information

Old Questions Name: a. if b. open c. output d. write e. do f. exit

Old Questions Name: a. if b. open c. output d. write e. do f. exit Old Questions Name: Part I. Multiple choice. One point each. 1. Which of the following is not a Fortran keyword? a. if b. open c. output d. write e. do f. exit 2. How many times will the code inside the

More information

Finite Element Analysis Prof. Dr. B. N. Rao Department of Civil Engineering Indian Institute of Technology, Madras. Lecture - 36

Finite Element Analysis Prof. Dr. B. N. Rao Department of Civil Engineering Indian Institute of Technology, Madras. Lecture - 36 Finite Element Analysis Prof. Dr. B. N. Rao Department of Civil Engineering Indian Institute of Technology, Madras Lecture - 36 In last class, we have derived element equations for two d elasticity problems

More information

Module 25.2: nag correl Correlation Analysis. Contents

Module 25.2: nag correl Correlation Analysis. Contents Correlation and Regression Analysis Module Contents Module 25.2: nag correl Correlation Analysis nag correl contains procedures that calculate the correlation coefficients for a set of data values. Contents

More information

Introduction to Programming, Aug-Dec 2008

Introduction to Programming, Aug-Dec 2008 Introduction to Programming, Aug-Dec 2008 Lecture 1, Monday 4 Aug 2008 Administrative matters Resource material Textbooks and other resource material for the course: The Craft of Functional Programming

More information

NAG Library Routine Document C05PBF/C05PBA

NAG Library Routine Document C05PBF/C05PBA NAG Library Routine Document /C05PBA Note: before using this routine, please read the Users Note for your implementation to check the interpretation of bold italicised terms and other implementation-dependent

More information

NAG Library Routine Document D02HBF.1

NAG Library Routine Document D02HBF.1 D02 Ordinary Differential Equations NAG Library Routine Document Note: before using this routine, please read the Users Note for your implementation to check the interpretation of bold italicised terms

More information

A Parallel Intermediate Representation based on. Lambda Expressions. Timothy A. Budd. Oregon State University. Corvallis, Oregon.

A Parallel Intermediate Representation based on. Lambda Expressions. Timothy A. Budd. Oregon State University. Corvallis, Oregon. A Parallel Intermediate Representation based on Lambda Expressions Timothy A. Budd Department of Computer Science Oregon State University Corvallis, Oregon 97331 budd@cs.orst.edu September 20, 1994 Abstract

More information

Dr Richard Greenaway

Dr Richard Greenaway SCHOOL OF PHYSICS, ASTRONOMY & MATHEMATICS 4PAM1008 MATLAB 2 Basic MATLAB Operation Dr Richard Greenaway 2 Basic MATLAB Operation 2.1 Overview 2.1.1 The Command Line In this Workshop you will learn how

More information

Write an iterative real-space Poisson solver in Python/C

Write an iterative real-space Poisson solver in Python/C Write an iterative real-space Poisson solver in Python/C Ask Hjorth Larsen asklarsen@gmail.com October 10, 2018 The Poisson equation is 2 φ(r) = ρ(r). (1) This is a second-order linear dierential equation

More information

Extrinsic Procedures. Section 6

Extrinsic Procedures. Section 6 Section Extrinsic Procedures 1 1 1 1 1 1 1 1 0 1 This chapter defines the mechanism by which HPF programs may call non-hpf subprograms as extrinsic procedures. It provides the information needed to write

More information

CS201 - Introduction to Programming Glossary By

CS201 - Introduction to Programming Glossary By CS201 - Introduction to Programming Glossary By #include : The #include directive instructs the preprocessor to read and include a file into a source code file. The file name is typically enclosed with

More information

Introduction to Matlab. By: Dr. Maher O. EL-Ghossain

Introduction to Matlab. By: Dr. Maher O. EL-Ghossain Introduction to Matlab By: Dr. Maher O. EL-Ghossain Outline: q What is Matlab? Matlab Screen Variables, array, matrix, indexing Operators (Arithmetic, relational, logical ) Display Facilities Flow Control

More information

KS3 Progression Map: Number

KS3 Progression Map: Number KS3 Progression Map: Number This progression map expands upon the statements of subject content in the DfE document Mathematics programmes of study: Key Stage 3 published September 2013. Suggested allocation

More information

Compiler and Runtime Support for Programming in Adaptive. Parallel Environments 1. Guy Edjlali, Gagan Agrawal, and Joel Saltz

Compiler and Runtime Support for Programming in Adaptive. Parallel Environments 1. Guy Edjlali, Gagan Agrawal, and Joel Saltz Compiler and Runtime Support for Programming in Adaptive Parallel Environments 1 Guy Edjlali, Gagan Agrawal, Alan Sussman, Jim Humphries, and Joel Saltz UMIACS and Dept. of Computer Science University

More information

A Friendly Fortran DDE Solver

A Friendly Fortran DDE Solver A Friendly Fortran DDE Solver S. Thompson Department of Mathematics & Statistics Radford University Radford, VA 24142 thompson@radford.edu L.F. Shampine Mathematics Department Southern Methodist University

More information

INTRODUCTION 1 AND REVIEW

INTRODUCTION 1 AND REVIEW INTRODUTION 1 AND REVIEW hapter SYS-ED/ OMPUTER EDUATION TEHNIQUES, IN. Programming: Advanced Objectives You will learn: Program structure. Program statements. Datatypes. Pointers. Arrays. Structures.

More information

PROJECTION MODELING SIMPLIFICATION MARKER EXTRACTION DECISION. Image #k Partition #k

PROJECTION MODELING SIMPLIFICATION MARKER EXTRACTION DECISION. Image #k Partition #k TEMPORAL STABILITY IN SEQUENCE SEGMENTATION USING THE WATERSHED ALGORITHM FERRAN MARQU ES Dept. of Signal Theory and Communications Universitat Politecnica de Catalunya Campus Nord - Modulo D5 C/ Gran

More information

NAG Library Routine Document C05QBF.1

NAG Library Routine Document C05QBF.1 NAG Library Routine Document Note: before using this routine, please read the Users Note for your implementation to check the interpretation of bold italicised terms and other implementation-dependent

More information

Heap-on-Top Priority Queues. March Abstract. We introduce the heap-on-top (hot) priority queue data structure that combines the

Heap-on-Top Priority Queues. March Abstract. We introduce the heap-on-top (hot) priority queue data structure that combines the Heap-on-Top Priority Queues Boris V. Cherkassky Central Economics and Mathematics Institute Krasikova St. 32 117418, Moscow, Russia cher@cemi.msk.su Andrew V. Goldberg NEC Research Institute 4 Independence

More information

Connecting special ordered inequalities and transformation and reformulation technique in multiple choice programming

Connecting special ordered inequalities and transformation and reformulation technique in multiple choice programming Computers & Operations Research 29 (2002) 1441}1446 Short communication Connecting special ordered inequalities and transformation and reformulation technique in multiple choice programming Edward Yu-Hsien

More information

CSE 230 Intermediate Programming in C and C++ Functions

CSE 230 Intermediate Programming in C and C++ Functions CSE 230 Intermediate Programming in C and C++ Functions Fall 2017 Stony Brook University Instructor: Shebuti Rayana shebuti.rayana@stonybrook.edu http://www3.cs.stonybrook.edu/~cse230/ Concept of Functions

More information

Egemen Tanin, Tahsin M. Kurc, Cevdet Aykanat, Bulent Ozguc. Abstract. Direct Volume Rendering (DVR) is a powerful technique for

Egemen Tanin, Tahsin M. Kurc, Cevdet Aykanat, Bulent Ozguc. Abstract. Direct Volume Rendering (DVR) is a powerful technique for Comparison of Two Image-Space Subdivision Algorithms for Direct Volume Rendering on Distributed-Memory Multicomputers Egemen Tanin, Tahsin M. Kurc, Cevdet Aykanat, Bulent Ozguc Dept. of Computer Eng. and

More information

GAS Tutorial - 7. Directives (3)

GAS Tutorial - 7. Directives (3) GAS Tutorial - 7. Directives (3) Young W. Lim 2016-07-13 Thr Young W. Lim GAS Tutorial - 7. Directives (3) 2016-07-13 Thr 1 / 48 Outline 1 Section Related Directivqes Young W. Lim GAS Tutorial - 7. Directives

More information

Extra-High Speed Matrix Multiplication on the Cray-2. David H. Bailey. September 2, 1987

Extra-High Speed Matrix Multiplication on the Cray-2. David H. Bailey. September 2, 1987 Extra-High Speed Matrix Multiplication on the Cray-2 David H. Bailey September 2, 1987 Ref: SIAM J. on Scientic and Statistical Computing, vol. 9, no. 3, (May 1988), pg. 603{607 Abstract The Cray-2 is

More information

Network. Department of Statistics. University of California, Berkeley. January, Abstract

Network. Department of Statistics. University of California, Berkeley. January, Abstract Parallelizing CART Using a Workstation Network Phil Spector Leo Breiman Department of Statistics University of California, Berkeley January, 1995 Abstract The CART (Classication and Regression Trees) program,

More information

A Linear-C Implementation of Dijkstra's Algorithm. Chung-Hsing Hsu and Donald Smith and Saul Levy. Department of Computer Science. Rutgers University

A Linear-C Implementation of Dijkstra's Algorithm. Chung-Hsing Hsu and Donald Smith and Saul Levy. Department of Computer Science. Rutgers University A Linear-C Implementation of Dijkstra's Algorithm Chung-Hsing Hsu and Donald Smith and Saul Levy Department of Computer Science Rutgers University LCSR-TR-274 October 9, 1996 Abstract Linear-C is a data-parallel

More information

Evolution of Fortran. Presented by: Tauqeer Ahmad. Seminar on Languages for Scientific Computing

Evolution of Fortran. Presented by: Tauqeer Ahmad. Seminar on Languages for Scientific Computing Evolution of Fortran Presented by: Seminar on Languages for Scientific Computing Outline (1) History of Fortran Versions FORTRAN I FORTRAN II FORTRAN III FORTRAN IV FORTRAN 66 FORTRAN 77 Evolution of FORTRAN

More information

Inner and outer approximation of capture basin using interval analysis

Inner and outer approximation of capture basin using interval analysis Inner and outer approximation of capture basin using interval analysis M. Lhommeau 1 L. Jaulin 2 L. Hardouin 1 1 Laboratoire d'ingénierie des Systèmes Automatisés ISTIA - Université d'angers 62, av. Notre

More information

III Data Structures. Dynamic sets

III Data Structures. Dynamic sets III Data Structures Elementary Data Structures Hash Tables Binary Search Trees Red-Black Trees Dynamic sets Sets are fundamental to computer science Algorithms may require several different types of operations

More information

Chapter 5 Lempel-Ziv Codes To set the stage for Lempel-Ziv codes, suppose we wish to nd the best block code for compressing a datavector X. Then we ha

Chapter 5 Lempel-Ziv Codes To set the stage for Lempel-Ziv codes, suppose we wish to nd the best block code for compressing a datavector X. Then we ha Chapter 5 Lempel-Ziv Codes To set the stage for Lempel-Ziv codes, suppose we wish to nd the best block code for compressing a datavector X. Then we have to take into account the complexity of the code.

More information

6.1 Expression Evaluation. 1 of 21

6.1 Expression Evaluation. 1 of 21 6.1 Expression Evaluation 1 of 21 The world of expressions In the absence of side effects, expressions are relatively simple and nice objects. Functional programming languages rely on expressions as their

More information

THE CONSTRUCTION OF AN ALGOL TRANSLATOR FOR A SMALL COMPUTER

THE CONSTRUCTION OF AN ALGOL TRANSLATOR FOR A SMALL COMPUTER i.i THE CONSTRUCTION OF AN ALGOL TRANSLATOR FOR A SMALL COMPUTER w. L. van der Poet Dr. Neher Laboratory PTT, Leidschendam, Netherlands For the computer Zebra we have undertaken a project of constructing

More information

Fundamentals of the J Programming Language

Fundamentals of the J Programming Language 2 Fundamentals of the J Programming Language In this chapter, we present the basic concepts of J. We introduce some of J s built-in functions and show how they can be applied to data objects. The pricinpals

More information

Introduction to Modern Fortran

Introduction to Modern Fortran Introduction to Modern Fortran p. 1/?? Introduction to Modern Fortran Advanced Use Of Procedures Nick Maclaren nmm1@cam.ac.uk March 2014 Introduction to Modern Fortran p. 2/?? Summary We have omitted some

More information