--- trunk/libf/dyn3d/inter_barxy.f90 2008/02/27 13:16:39 3 +++ trunk/libf/dyn3d/inter_barxy.f90 2013/11/15 17:48:30 73 @@ -2,9 +2,6 @@ ! From inter_barxy.F, version 1.1.1.1 2004/05/19 12:53:07 - ! This file is clean: there is neither C preprocessor directive, nor - ! include line. - implicit none private @@ -16,8 +13,7 @@ ! Author: P. Le Van - use nrutil, only: assert_eq, assert - + use nr_util, only: assert_eq, assert use dimens_m, only: iim, jjm use comgeom, only: aire_2d, apoln, apols @@ -59,18 +55,25 @@ ! Check decreasing order for "rlatimod": DO i = 2, jjm - IF (rlatimod(i) >= rlatimod(i-1)) stop & - '"inter_barxy": "rlatimod" should be strictly decreasing' + IF (rlatimod(i) >= rlatimod(i-1)) then + print *, '"inter_barxy": "rlatimod" should be strictly decreasing' + stop 1 + end IF ENDDO yjmod(:jjm) = ord_coordm(rlatimod) IF (jmods == jjm + 1) THEN - IF (90. - yjmod(jjm) < 0.01) stop & - '"inter_barxy": with jmods = jjm + 1, yjmod(jjm) should be < 90.' + IF (90. - yjmod(jjm) < 0.01) then + print *, '"inter_barxy": with jmods = jjm + 1, ' & + // 'yjmod(jjm) should be < 90.' + stop 1 + end IF ELSE ! jmods = jjm - IF (ABS(yjmod(jjm) - 90.) > 0.01) stop & - '"inter_barxy": with jmods = jjm, yjmod(jjm) should be 90.' + IF (ABS(yjmod(jjm) - 90.) > 0.01) then + print *, '"inter_barxy": with jmods = jjm, yjmod(jjm) should be 90.' + stop 1 + end IF ENDIF if (jmods == jjm + 1) yjmod(jjm + 1) = 90. @@ -115,7 +118,7 @@ ! ( L'indice 1 correspond a l'interface mailLE 1 / maille 2) ! ( Les abscisses sont exprimées en degres) - use nrutil, only: assert_eq + use nr_util, only: assert_eq IMPLICIT NONE @@ -300,7 +303,7 @@ ! Version unidimensionnelle, en latitude. ! L'indice 1 correspond à l'interface maille 1 -- maille 2. - use nrutil, only: assert + use nr_util, only: assert IMPLICIT NONE @@ -349,7 +352,7 @@ dym = 0. jmod = jmod + 1 ELSE - ! yjmod(jmod) == yjdat(jdat) + ! {yjmod(jmod) == yjdat(jdat)} dy = yjmod(jmod) - y0 dym = dym + dy inter_bary(jmod) = (inter_bary(jmod) + dy * fdat(jdat)) / dym @@ -377,8 +380,7 @@ ! reverses their order. ! Finally, the procedure adds 90° as the last value of the array. - use nrutil, only: assert_eq - use comconst, only: pi + use nr_util, only: assert_eq, pi IMPLICIT NONE @@ -402,8 +404,10 @@ ! Check monotonicity: decrois = xi(2) < xi(1) DO i = 3, nmax - IF (decrois .neqv. xi(i) < xi(i-1)) stop & - '"ord_coord": latitudes are not monotonic' + IF (decrois .neqv. xi(i) < xi(i-1)) then + print *, '"ord_coord": latitudes are not monotonic' + stop 1 + end IF ENDDO IF (abs(xi(1)) < pi) then @@ -418,7 +422,7 @@ print *, "ord_coord" PRINT *, '"xi" should contain the latitudes of the boundaries of ' & // 'grid cells, not the centers of grid cells.' - STOP + STOP 1 ENDIF IF (decrois) xo(:nmax) = xo(nmax:1:- 1) @@ -436,7 +440,7 @@ ! This procedure converts to degrees, if necessary, and inverts the ! order. - use comconst, only: pi + use nr_util, only: pi IMPLICIT NONE