Ignore:
Timestamp:
12/19/17 15:26:51 (7 years ago)
Author:
dubos
Message:

devel/unstructured : bubble test case with Fortran time stepping

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/unstructured/timestep_unstructured.F90

    r638 r642  
    3636#define HASNAN(field) (ANY(.NOT.ABS(field)<1e20)) 
    3737 
    38 SUBROUTINE caldyn_unstructured(tau, mass_col,rhodz,theta_rhodz,u,geopot,w, & ! IN : flow state 
    39                                theta,ps,pk,hflux,qv, &    ! OUT : diags (except surface geopot : IN) 
    40                                dmass_col,drhodz,dtheta_rhodz,du_fast,du_slow, & 
    41                                dPhi_fast, dPhi_slow, dW_fast, dW_slow) BINDC(caldyn_unstructured) ! OUT : tendencies 
    42   DBL, VALUE :: tau 
    43   FIELD_MASS   :: rhodz, drhodz, pk, berni         ! IN, OUT, DIAG 
    44   FIELD_THETA  :: theta_rhodz, dtheta_rhodz, theta ! IN, OUT, DIAG 
    45   FIELD_GEOPOT :: wflux, w, geopot, &              ! DIAG, INOUT 
    46        dPhi_fast, dPhi_slow, dW_fast, dW_slow      ! OUT 
    47   FIELD_U      :: u,du_fast,du_slow,hflux,qu       ! INOUT,OUT,OUT,DIAG 
    48   FIELD_Z      :: qv                               ! DIAG 
    49   FIELD_PS     :: ps,dmass_col,mass_col            ! OUT,OUT,IN (if eta_mass) or OUT,UNUSED,UNUSED (if eta_lag) 
    50   DOUBLE2(llm+1, edge_num) :: wwuu 
    51   DBL          :: time1,time2 
    52   INTEGER :: ij 
    53  
    54 !  CALL CPU_TIME(time1) 
    55   time1=OMP_GET_WTIME() 
    56  
    57   IF(hydrostatic) THEN 
    58  
    59     !$OMP PARALLEL NUM_THREADS(nb_threads) 
    60     !$OMP DO SCHEDULE(STATIC) 
    61     DO ij=1,edge_num 
    62       du_fast(:,ij)=0. 
    63       du_slow(:,ij)=0. 
    64     END DO 
    65     !$OMP END DO 
    66     CALL compute_theta(mass_col,rhodz,theta_rhodz, theta) 
    67     CALL compute_geopot(rhodz,theta, ps,pk,geopot) 
    68  
    69     CALL compute_caldyn_fast(tau, pk,berni,theta,geopot, du_fast,u) 
    70  
    71     CALL compute_pvort_only(rhodz,u,qv,qu) 
    72     CALL compute_caldyn_slow_hydro(rhodz,theta,u, berni,hflux,du_slow) 
    73     CALL compute_coriolis(hflux,theta,qu, drhodz,dtheta_rhodz,du_slow) 
    74     IF(caldyn_eta == eta_mass) THEN 
    75        CALL caldyn_vert(drhodz,rhodz,theta,u, dmass_col,wflux,dtheta_rhodz,du_slow,wwuu) 
     38  SUBROUTINE caldyn_unstructured(tau, mass_col,rhodz,theta_rhodz,u,geopot,w, & ! IN : flow state 
     39                                 theta,ps,pk,hflux,qv, &    ! OUT : diags (except surface geopot : IN) 
     40                                 dmass_col,drhodz,dtheta_rhodz,du_fast,du_slow, & 
     41                                 dPhi_fast, dPhi_slow, dW_fast, dW_slow) BINDC(caldyn_unstructured) ! OUT : tendencies 
     42    DBL, VALUE :: tau 
     43    FIELD_MASS   :: rhodz, drhodz, pk, berni         ! IN, OUT, DIAG 
     44    FIELD_THETA  :: theta_rhodz, dtheta_rhodz, theta ! IN, OUT, DIAG 
     45    FIELD_GEOPOT :: wflux, w, geopot, &              ! DIAG, INOUT 
     46         dPhi_fast, dPhi_slow, dW_fast, dW_slow      ! OUT 
     47    FIELD_U      :: u,du_fast,du_slow,hflux,qu       ! INOUT,OUT,OUT,DIAG 
     48    FIELD_Z      :: qv                               ! DIAG 
     49    FIELD_PS     :: ps,dmass_col,mass_col            ! OUT,OUT,IN (if eta_mass) or OUT,UNUSED,UNUSED (if eta_lag) 
     50    FIELD_UL     :: wwuu 
     51    DBL          :: time1,time2 
     52    INTEGER :: ij 
     53     
     54    !  CALL CPU_TIME(time1) 
     55    time1=OMP_GET_WTIME() 
     56     
     57    IF(hydrostatic) THEN 
     58        
     59       !$OMP PARALLEL NUM_THREADS(nb_threads) 
     60       !$OMP DO SCHEDULE(STATIC) 
     61       DO ij=1,edge_num 
     62          du_fast(:,ij)=0. 
     63          du_slow(:,ij)=0. 
     64       END DO 
     65       !$OMP END DO 
     66       CALL compute_theta(mass_col,rhodz,theta_rhodz, theta) 
     67       CALL compute_geopot(rhodz,theta, ps,pk,geopot) 
     68        
     69       CALL compute_caldyn_fast(tau, pk,berni,theta,geopot, du_fast,u) 
     70        
     71       CALL compute_pvort_only(rhodz,u,qv,qu) 
     72       CALL compute_caldyn_slow_hydro(rhodz,theta,u, berni,hflux,du_slow) 
     73       CALL compute_coriolis(hflux,theta,qu, drhodz,dtheta_rhodz,du_slow) 
     74       IF(caldyn_eta == eta_mass) THEN 
     75          CALL caldyn_vert(drhodz,rhodz,theta,u, dmass_col,wflux,dtheta_rhodz,du_slow,wwuu) 
     76       END IF 
     77       !$OMP END PARALLEL 
     78        
     79    ELSE ! NH 
     80       DO ij=1,edge_num 
     81          du_fast(:,ij)=0. 
     82          du_slow(:,ij)=0. 
     83       END DO 
     84       DO ij=1,primal_num 
     85          wflux(1,ij)=0. 
     86          wflux(llm+1,ij)=0. 
     87       END DO 
     88       CALL compute_theta(mass_col,rhodz,theta_rhodz, theta) 
     89       CALL compute_caldyn_solver(tau,rhodz,theta,pk,geopot,W,dPhi_fast,dW_fast,du_fast) 
     90       CALL compute_caldyn_fast(tau, pk,berni,theta,geopot, du_fast,u) 
     91       CALL compute_pvort_only(rhodz,u,qv,qu) 
     92       CALL compute_caldyn_slow_NH(u,rhodz,geopot,W, hflux,du_slow,dPhi_slow,dW_slow)  
     93       CALL compute_coriolis(hflux,theta,qu, drhodz,dtheta_rhodz,du_slow) 
     94       IF(caldyn_eta == eta_mass) THEN 
     95          CALL caldyn_vert(drhodz,rhodz,theta,u, dmass_col,wflux,dtheta_rhodz,du_slow,wwuu) 
     96          CALL compute_caldyn_vert_NH(rhodz,geopot,W,wflux, du_slow,dPhi_slow,dW_slow) 
     97       END IF 
    7698    END IF 
    77 !$OMP END PARALLEL 
    78  
    79  
    80   ELSE ! NH 
    81     DO ij=1,edge_num 
    82       du_fast(:,ij)=0. 
    83       du_slow(:,ij)=0. 
    84     END DO 
    85     DO ij=1,primal_num 
    86       wflux(1,ij)=0. 
    87       wflux(llm+1,ij)=0. 
    88     END DO 
    89     CALL compute_theta(mass_col,rhodz,theta_rhodz, theta) 
    90     CALL compute_caldyn_solver(tau,rhodz,theta,pk,geopot,W,dPhi_fast,dW_fast,du_fast) 
    91     CALL compute_caldyn_fast(tau, pk,berni,theta,geopot, du_fast,u) 
    92     CALL compute_pvort_only(rhodz,u,qv,qu) 
    93     CALL compute_caldyn_slow_NH(u,rhodz,geopot,W, hflux,du_slow,dPhi_slow,dW_slow)  
    94     CALL compute_coriolis(hflux,theta,qu, drhodz,dtheta_rhodz,du_slow) 
    95     IF(caldyn_eta == eta_mass) THEN 
    96        CALL caldyn_vert(drhodz,rhodz,theta,u, dmass_col,wflux,dtheta_rhodz,du_slow,wwuu) 
    97        CALL compute_caldyn_vert_NH(rhodz,geopot,W,wflux, du_slow,dPhi_slow,dW_slow) 
    98     END IF 
    99   END IF 
    100   
    101   time2=OMP_GET_WTIME() 
    102 !  CALL CPU_TIME(time2) 
    103   IF(time2>time1) elapsed = elapsed + time2-time1 
    104 END SUBROUTINE caldyn_unstructured 
    105 ! 
    106 !----------------------------- Time stepping ------------------------------- 
    107  
    108 ! 
    109   SUBROUTINE ARK_step(mass_col,rhodz,theta_rhodz,u,geopot,w, & ! INOUT : flow state 
     99     
     100    time2=OMP_GET_WTIME() 
     101    !  CALL CPU_TIME(time2) 
     102    IF(time2>time1) elapsed = elapsed + time2-time1 
     103  END SUBROUTINE caldyn_unstructured 
     104  ! 
     105  !----------------------------- Time stepping ------------------------------- 
     106   
     107  ! 
     108  SUBROUTINE ARK_step(nstep, mass_col,rhodz,theta_rhodz,u,geopot,w, & ! INOUT : flow state 
    110109       theta,ps,pk,hflux,qv, &    ! OUT : diags (except surface geopot : IN) 
    111110       dmass_col,drhodz,dtheta_rhodz,du_fast,du_slow, & 
    112111       dPhi_fast, dPhi_slow, dW_fast, dW_slow) BINDC(ARK_step) ! OUT : tendencies 
     112    INTEGER, VALUE :: nstep ! advance by nstep time steps 
    113113    FIELD_PS     :: mass_col, ps                     ! OUT,IN (if eta_mass) or OUT,UNUSED (if eta_lag) 
    114114    FIELD_MASS   :: rhodz, pk, berni                 ! IN, DIAG 
     
    123123    DOUBLE3(llm+1, primal_num, max_nb_stage) :: & 
    124124         dPhi_fast, dPhi_slow, dW_fast, dW_slow      ! OUT 
    125     FIELD_UL     :: DePhil, v_el, G_el               ! DIAG*3 
    126     DOUBLE2(llm+1, edge_num) :: wwuu 
     125    FIELD_UL     :: DePhil, v_el, G_el, wwuu         ! DIAG*4 
    127126    DBL       :: time1,time2 
    128     INTEGER :: stage, ij 
    129  
     127    INTEGER :: step, stage, ij 
     128     
    130129    !CALL CPU_TIME(time1) 
    131130    time1=OMP_GET_WTIME() 
    132  
     131     
    133132    !$OMP PARALLEL NUM_THREADS(nb_threads) 
    134133     
    135     DO stage=1, nb_stage 
    136         
    137        IF(hydrostatic) THEN 
    138  
    139           !$OMP DO SCHEDULE(STATIC) 
    140           DO ij=1,edge_num 
    141              du_fast(:,ij,stage)=0. 
    142              du_slow(:,ij,stage)=0. 
    143           END DO 
    144  
    145           CALL compute_theta(mass_col,rhodz,theta_rhodz, theta) 
    146           CALL compute_geopot(rhodz,theta, ps,pk,geopot) 
    147            
    148           CALL compute_caldyn_fast(tauj(stage), pk,berni,theta,geopot, du_fast(:,:,stage), u) 
    149            
    150           CALL compute_pvort_only(rhodz,u,qv,qu) 
    151           CALL compute_caldyn_slow_hydro(rhodz,theta,u, berni,hflux,du_slow(:,:,stage)) 
    152           CALL compute_coriolis(hflux,theta,qu, drhodz(:,:,stage), dtheta_rhodz(:,:,:,stage),du_slow(:,:,stage)) 
    153           IF(caldyn_eta == eta_mass) THEN 
    154              STOP ! FIXME 
    155              CALL caldyn_vert(drhodz(:,:,stage),rhodz,theta,u, & 
    156                   dmass_col(:,stage),wflux,dtheta_rhodz(:,:,:,stage),du_slow(:,:,stage),wwuu) 
     134    DO step=1, nstep 
     135       DO stage=1, nb_stage 
     136           
     137          IF(hydrostatic) THEN 
     138              
     139             !$OMP DO SCHEDULE(STATIC) 
     140             DO ij=1,edge_num 
     141                du_fast(:,ij,stage)=0. 
     142                du_slow(:,ij,stage)=0. 
     143             END DO 
     144              
     145             CALL compute_theta(mass_col,rhodz,theta_rhodz, theta) 
     146             CALL compute_geopot(rhodz,theta, ps,pk,geopot) 
     147              
     148             CALL compute_caldyn_fast(tauj(stage), pk,berni,theta,geopot, du_fast(:,:,stage), u) 
     149              
     150             CALL compute_pvort_only(rhodz,u,qv,qu) 
     151             CALL compute_caldyn_slow_hydro(rhodz,theta,u, berni,hflux,du_slow(:,:,stage)) 
     152             CALL compute_coriolis(hflux,theta,qu, drhodz(:,:,stage), dtheta_rhodz(:,:,:,stage),du_slow(:,:,stage)) 
     153             IF(caldyn_eta == eta_mass) THEN 
     154                CALL caldyn_vert(drhodz(:,:,stage),rhodz,theta,u, & 
     155                     dmass_col(:,stage),wflux,dtheta_rhodz(:,:,:,stage),du_slow(:,:,stage),wwuu) 
     156             END IF 
     157              
     158          ELSE ! NH 
     159             !$OMP DO SCHEDULE(STATIC) 
     160             DO ij=1,primal_num 
     161                wflux(1,ij)=0. 
     162                wflux(llm+1,ij)=0. 
     163             END DO 
     164             !$OMP END DO 
     165             CALL compute_theta(mass_col,rhodz,theta_rhodz, theta) 
     166             CALL compute_caldyn_solver(tauj(stage),rhodz,theta,pk,geopot,W, & 
     167                  dPhi_fast(:,:,stage), dW_fast(:,:,stage), du_fast(:,:,stage)) 
     168             CALL compute_caldyn_fast(tauj(stage), pk,berni,theta,geopot, du_fast(:,:,stage),u) 
     169             CALL compute_pvort_only(rhodz,u,qv,qu) 
     170             CALL compute_caldyn_slow_NH(u,rhodz,geopot,W, hflux, du_slow(:,:,stage), dPhi_slow(:,:,stage), dW_slow(:,:,stage)) 
     171             CALL compute_coriolis(hflux,theta,qu, drhodz(:,:,stage),dtheta_rhodz(:,:,:,stage), du_slow(:,:,stage)) 
     172             IF(caldyn_eta == eta_mass) THEN 
     173                CALL caldyn_vert(drhodz(:,:,stage),rhodz,theta,u, & 
     174                     dmass_col(:,stage),wflux,dtheta_rhodz(:,:,:,stage), du_slow(:,:,stage), wwuu) 
     175                CALL compute_caldyn_vert_NH(rhodz,geopot,W,wflux, du_slow(:,:,stage), dPhi_slow(:,:,stage), dW_slow(:,:,stage) ) 
     176             END IF 
     177          END IF ! NH 
     178           
     179          ! FIXME : mass_col is computed from rhodz 
     180          ! so that the DOFs are the same whatever caldyn_eta 
     181          ! in DYNAMICO mass_col is prognosed rather than rhodz 
     182           
     183#define UPDATE(clj,field,dfield) update(stage,SIZE(field),clj,field,dfield) 
     184           
     185          CALL UPDATE(cslj, rhodz, drhodz) 
     186          CALL UPDATE(cslj, theta_rhodz, dtheta_rhodz) 
     187          CALL UPDATE(cslj, u, du_slow) 
     188          CALL UPDATE(cflj, u, du_fast) 
     189           
     190          IF(.NOT.hydrostatic) THEN 
     191             CALL UPDATE(cslj, geopot, dPhi_slow) 
     192             CALL UPDATE(cflj, geopot, dPhi_fast) 
     193             CALL UPDATE(cslj, W, dW_slow) 
     194             CALL UPDATE(cflj, W, dW_fast) 
    157195          END IF 
    158196           
    159        ELSE ! NH 
    160           STOP ! FIXME 
    161           !$OMP DO SCHEDULE(STATIC) 
    162           DO ij=1,primal_num 
    163              wflux(1,ij)=0. 
    164              wflux(llm+1,ij)=0. 
    165           END DO 
    166           !$OMP END DO 
    167           CALL compute_theta(mass_col,rhodz,theta_rhodz, theta) 
    168           CALL compute_caldyn_solver(tauj(stage),rhodz,theta,pk,geopot,W, & 
    169                dPhi_fast(:,:,stage), dW_fast(:,:,stage), du_fast(:,:,stage)) 
    170           CALL compute_caldyn_fast(tauj(stage), pk,berni,theta,geopot, du_fast(:,:,stage),u) 
    171           CALL compute_pvort_only(rhodz,u,qv,qu) 
    172           CALL compute_caldyn_slow_NH(u,rhodz,geopot,W, hflux, du_slow(:,:,stage), dPhi_slow(:,:,stage), dW_slow(:,:,stage)) 
    173           CALL compute_coriolis(hflux,theta,qu, drhodz(:,:,stage),dtheta_rhodz(:,:,:,stage), du_slow(:,:,stage)) 
    174           IF(caldyn_eta == eta_mass) THEN 
    175              CALL caldyn_vert(drhodz(:,:,stage),rhodz,theta,u, & 
    176                   dmass_col(:,stage),wflux,dtheta_rhodz(:,:,:,stage), du_slow(:,:,stage), wwuu) 
    177              CALL compute_caldyn_vert_NH(rhodz,geopot,W,wflux, du_slow(:,:,stage), dPhi_slow(:,:,stage), dW_slow(:,:,stage) ) 
    178           END IF 
    179        END IF ! NH 
    180         
    181       ! FIXME : mass_col is computed from rhodz 
    182       ! so that the DOFs are the same whatever caldyn_eta 
    183       ! in DYNAMICO mass_col is prognosed rather than rhodz 
    184  
    185 #define UPDATE(clj,field,dfield) update(stage,SIZE(field),clj,field,dfield) 
    186  
    187        CALL UPDATE(cslj, rhodz, drhodz) 
    188        CALL UPDATE(cslj, theta_rhodz, dtheta_rhodz) 
    189        CALL UPDATE(cslj, u, du_slow) 
    190        CALL UPDATE(cflj, u, du_fast) 
    191  
    192        IF(.NOT.hydrostatic) THEN 
    193           STOP ! FIXME 
    194           CALL UPDATE(cslj, geopot, dPhi_slow) 
    195           CALL UPDATE(cflj, geopot, dPhi_fast) 
    196           CALL UPDATE(cslj, W, dW_slow) 
    197           CALL UPDATE(cflj, W, dW_fast) 
    198        END IF 
    199  
     197       END DO 
    200198    END DO 
    201 !$OMP END PARALLEL 
    202      
    203   time2=OMP_GET_WTIME() 
    204 !  CALL CPU_TIME(time2) 
    205   IF(time2>time1) elapsed = elapsed + time2-time1 
    206  
     199    !$OMP END PARALLEL 
     200     
     201    time2=OMP_GET_WTIME() 
     202    !  CALL CPU_TIME(time2) 
     203    IF(time2>time1) elapsed = elapsed + time2-time1 
     204     
    207205  END SUBROUTINE ARK_step 
    208   ! 
    209 ! 
    210 SUBROUTINE update(j,sz,clj,field,dfield) 
    211   INTEGER :: j, sz ! stage in ARK scheme, field size 
    212   DOUBLE2(max_nb_stage,max_nb_stage) :: clj ! modified Butcher tableau 
    213   DOUBLE1(sz) :: field 
    214   DOUBLE2(sz, max_nb_stage) :: dfield 
    215   ! 
    216   INTEGER :: l, ij 
    217 !  PRINT *, clj(1:j,j) 
    218   SELECT CASE(j) 
    219   CASE(1) 
    220      !$OMP DO SCHEDULE(static) 
    221      DO ij=1,sz 
    222         field(ij) = field(ij) & 
    223              + clj(1,j)*dfield(ij,1) 
    224      END DO 
    225   CASE(2) 
    226      !$OMP DO SCHEDULE(static) 
    227      DO ij=1,sz 
    228         field(ij) = field(ij) & 
    229              + clj(1,j)*dfield(ij,1) & 
    230              + clj(2,j)*dfield(ij,2) 
    231      END DO 
    232   CASE(3) 
    233      !$OMP DO SCHEDULE(static) 
    234      DO ij=1,sz 
    235         field(ij) = field(ij) & 
    236              + clj(1,j)*dfield(ij,1) & 
    237              + clj(2,j)*dfield(ij,2) & 
    238              + clj(3,j)*dfield(ij,3) 
    239  
    240      END DO 
    241   CASE(4) 
    242      !$OMP DO SCHEDULE(static) 
    243      DO ij=1,sz 
    244         field(ij) = field(ij) & 
    245              + clj(1,j)*dfield(ij,1) & 
    246              + clj(2,j)*dfield(ij,2) & 
    247              + clj(3,j)*dfield(ij,3) & 
    248              + clj(4,j)*dfield(ij,4) 
    249      END DO 
    250   CASE(5) 
    251      !$OMP DO SCHEDULE(static) 
    252      DO ij=1,sz 
    253         field(ij) = field(ij) & 
    254              + clj(1,j)*dfield(ij,1) & 
    255              + clj(2,j)*dfield(ij,2) & 
    256              + clj(3,j)*dfield(ij,3) & 
    257              + clj(4,j)*dfield(ij,4) & 
    258              + clj(5,j)*dfield(ij,5) 
    259      END DO 
    260   END SELECT 
    261 END SUBROUTINE update 
    262  
    263 !---------------------------------------------- XIOS ---------------------------------------- 
     206   
     207   
     208  SUBROUTINE update(j,sz,clj,field,dfield) 
     209    INTEGER :: j, sz ! stage in ARK scheme, field size 
     210    DOUBLE2(max_nb_stage,max_nb_stage) :: clj ! modified Butcher tableau 
     211    DOUBLE1(sz) :: field 
     212    DOUBLE2(sz, max_nb_stage) :: dfield 
     213    ! 
     214    INTEGER :: l, ij 
     215    !  PRINT *, clj(1:j,j) 
     216    SELECT CASE(j) 
     217    CASE(1) 
     218       !$OMP DO SCHEDULE(static) 
     219       DO ij=1,sz 
     220          field(ij) = field(ij) & 
     221               + clj(1,j)*dfield(ij,1) 
     222       END DO 
     223    CASE(2) 
     224       !$OMP DO SCHEDULE(static) 
     225       DO ij=1,sz 
     226          field(ij) = field(ij) & 
     227               + clj(1,j)*dfield(ij,1) & 
     228               + clj(2,j)*dfield(ij,2) 
     229       END DO 
     230    CASE(3) 
     231       !$OMP DO SCHEDULE(static) 
     232       DO ij=1,sz 
     233          field(ij) = field(ij) & 
     234               + clj(1,j)*dfield(ij,1) & 
     235               + clj(2,j)*dfield(ij,2) & 
     236               + clj(3,j)*dfield(ij,3) 
     237           
     238       END DO 
     239    CASE(4) 
     240       !$OMP DO SCHEDULE(static) 
     241       DO ij=1,sz 
     242          field(ij) = field(ij) & 
     243               + clj(1,j)*dfield(ij,1) & 
     244               + clj(2,j)*dfield(ij,2) & 
     245               + clj(3,j)*dfield(ij,3) & 
     246               + clj(4,j)*dfield(ij,4) 
     247       END DO 
     248    CASE(5) 
     249       !$OMP DO SCHEDULE(static) 
     250       DO ij=1,sz 
     251          field(ij) = field(ij) & 
     252               + clj(1,j)*dfield(ij,1) & 
     253               + clj(2,j)*dfield(ij,2) & 
     254               + clj(3,j)*dfield(ij,3) & 
     255               + clj(4,j)*dfield(ij,4) & 
     256               + clj(5,j)*dfield(ij,5) 
     257       END DO 
     258    END SELECT 
     259  END SUBROUTINE update 
     260   
     261  !---------------------------------------------- XIOS ---------------------------------------- 
    264262 
    265263#ifdef CPP_USING_XIOS 
    266  
     264   
    267265  SUBROUTINE setup_xios() BINDC(setup_xios) 
    268266    ! MPI_INIT / MPI_finalize are assumed to be called BEFORE/AFTER this routine 
Note: See TracChangeset for help on using the changeset viewer.