Ignore:
Timestamp:
Feb 17, 2012, 12:59:00 PM (13 years ago)
Author:
Ehouarn Millour
Message:

Some cleanup around what is done during the integration step of dynamical tendencies and namely removed computation of (unused) finvmaold, thereby saving us the expense of a call to the (costly) filter at every dynamical time step.
Checked (on Vargas, in seq, omp, mpi and mixed mode) that this doesn't change the GCM results, as expected.
EM

Location:
LMDZ5/trunk/libf/dyn3dpar
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3dpar/integrd_p.F

    r1550 r1616  
    44      SUBROUTINE integrd_p
    55     $  (  nq,vcovm1,ucovm1,tetam1,psm1,massem1,
    6      $     dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps0,masse,phis,finvmaold)
     6     $     dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps0,masse,phis) !,finvmaold)
    77      USE parallel
    88      USE control_mod, only : planet_type
     
    3333#include "temps.h"
    3434#include "serre.h"
     35#include "iniprint.h"
    3536
    3637c   Arguments:
    3738c   ----------
    3839
    39       INTEGER nq
    40 
    41       REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm),teta(ip1jmp1,llm)
    42       REAL q(ip1jmp1,llm,nq)
    43       REAL ps0(ip1jmp1),masse(ip1jmp1,llm),phis(ip1jmp1)
    44 
    45       REAL vcovm1(ip1jm,llm),ucovm1(ip1jmp1,llm)
    46       REAL tetam1(ip1jmp1,llm),psm1(ip1jmp1),massem1(ip1jmp1,llm)
    47 
    48       REAL dv(ip1jm,llm),du(ip1jmp1,llm)
    49       REAL dteta(ip1jmp1,llm),dp(ip1jmp1)
    50       REAL dq(ip1jmp1,llm,nq), finvmaold(ip1jmp1,llm)
     40      integer,intent(in) :: nq ! number of tracers to handle in this routine
     41      real,intent(inout) :: vcov(ip1jm,llm) ! covariant meridional wind
     42      real,intent(inout) :: ucov(ip1jmp1,llm) ! covariant zonal wind
     43      real,intent(inout) :: teta(ip1jmp1,llm) ! potential temperature
     44      real,intent(inout) :: q(ip1jmp1,llm,nq) ! advected tracers
     45      real,intent(inout) :: ps0(ip1jmp1) ! surface pressure
     46      real,intent(inout) :: masse(ip1jmp1,llm) ! atmospheric mass
     47      real,intent(in) :: phis(ip1jmp1) ! ground geopotential !!! unused
     48      ! values at previous time step
     49      real,intent(inout) :: vcovm1(ip1jm,llm)
     50      real,intent(inout) :: ucovm1(ip1jmp1,llm)
     51      real,intent(inout) :: tetam1(ip1jmp1,llm)
     52      real,intent(inout) :: psm1(ip1jmp1)
     53      real,intent(inout) :: massem1(ip1jmp1,llm)
     54      ! the tendencies to add
     55      real,intent(in) :: dv(ip1jm,llm)
     56      real,intent(in) :: du(ip1jmp1,llm)
     57      real,intent(in) :: dteta(ip1jmp1,llm)
     58      real,intent(in) :: dp(ip1jmp1)
     59      real,intent(in) :: dq(ip1jmp1,llm,nq) !!! unused
     60!      real,intent(out) :: finvmaold(ip1jmp1,llm) !!! unused
    5161
    5262c   Local:
     
    5464
    5565      REAL vscr( ip1jm ),uscr( ip1jmp1 ),hscr( ip1jmp1 ),pscr(ip1jmp1)
    56       REAL massescr( ip1jmp1,llm ), finvmasse(ip1jmp1,llm)
     66      REAL massescr( ip1jmp1,llm )
     67!      REAL finvmasse(ip1jmp1,llm)
    5768      REAL,SAVE :: p(ip1jmp1,llmp1)
    5869      REAL tpn,tps,tppn(iim),tpps(iim)
     
    6071      REAL,SAVE :: deltap( ip1jmp1,llm )
    6172
    62       INTEGER  l,ij,iq
     73      INTEGER  l,ij,iq,i,j
    6374
    6475      REAL SSUM
     
    126137       
    127138        IF( .NOT. checksum ) THEN
    128          PRINT*,' Au point ij = ',stop_it, ' , pression sol neg. '
    129      &         , ps(stop_it)
    130          print *, ' dans integrd'
    131          stop 1
     139         write(lunout,*) "integrd: negative surface pressure ",
     140     &                                                ps(stop_it)
     141         write(lunout,*) " at node ij =", stop_it
     142         ! since ij=j+(i-1)*jjp1 , we have
     143         j=modulo(stop_it,jjp1)
     144         i=1+(stop_it-j)/jjp1
     145         write(lunout,*) " lon = ",rlonv(i)*180./pi, " deg",
     146     &                   " lat = ",rlatu(j)*180./pi, " deg"
    132147        ENDIF
    133148
     
    167182      CALL massdair_p (     p  , masse         )
    168183
    169 c      CALL   SCOPY( ijp1llm  , masse, 1, finvmasse,  1      )
    170       ijb=ij_begin
    171       ije=ij_end
    172      
    173 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    174       DO  l = 1,llm
    175         finvmasse(ijb:ije,l)=masse(ijb:ije,l)
    176       ENDDO
    177 c$OMP END DO NOWAIT
    178 
    179       jjb=jj_begin
    180       jje=jj_end
    181       CALL filtreg_p( finvmasse,jjb,jje, jjp1, llm, -2, 2, .TRUE., 1  )
     184! Ehouarn : we don't use/need finvmaold and finvmasse,
     185!           so might as well not compute them
     186!c      CALL   SCOPY( ijp1llm  , masse, 1, finvmasse,  1      )
     187!      ijb=ij_begin
     188!      ije=ij_end
     189!     
     190!c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     191!      DO  l = 1,llm
     192!        finvmasse(ijb:ije,l)=masse(ijb:ije,l)
     193!      ENDDO
     194!c$OMP END DO NOWAIT
     195!
     196!      jjb=jj_begin
     197!      jje=jj_end
     198!      CALL filtreg_p( finvmasse,jjb,jje, jjp1, llm, -2, 2, .TRUE., 1  )
    182199c
    183200
     
    330347      ENDIF
    331348     
    332 c         CALL  SCOPY( ijp1llm , finvmasse, 1, finvmaold, 1 )
    333 
    334 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    335       DO l = 1, llm     
    336         finvmaold(ijb:ije,l)=finvmasse(ijb:ije,l)       
    337       ENDDO
    338 c$OMP END DO NOWAIT
     349! Ehouarn: forget about finvmaold
     350!c         CALL  SCOPY( ijp1llm , finvmasse, 1, finvmaold, 1 )
     351!
     352!c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     353!      DO l = 1, llm     
     354!        finvmaold(ijb:ije,l)=finvmasse(ijb:ije,l)       
     355!      ENDDO
     356!c$OMP END DO NOWAIT
    339357
    340358      endif ! of if (planet_type.eq."earth")
  • LMDZ5/trunk/libf/dyn3dpar/leapfrog_p.F

    r1615 r1616  
    124124      REAL  SSUM
    125125      REAL time_0
    126       REAL,SAVE :: finvmaold(ip1jmp1,llm)
     126!      REAL,SAVE :: finvmaold(ip1jmp1,llm)
    127127
    128128cym      LOGICAL  lafin
     
    284284         massem1= masse
    285285         psm1= ps
    286          
    287          finvmaold = masse
    288          CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 )
     286
     287! Ehouarn: finvmaold is actually not used       
     288!         finvmaold = masse
     289!         CALL filtreg ( finvmaold ,jjp1, llm, -2,2, .TRUE., 1 )
    289290c$OMP END MASTER
    290291c$OMP BARRIER
     
    304305           tetam1   (ijb:ije,l) = teta  (ijb:ije,l)
    305306           massem1  (ijb:ije,l) = masse (ijb:ije,l)
    306            finvmaold(ijb:ije,l)=masse(ijb:ije,l)
     307!           finvmaold(ijb:ije,l)=masse(ijb:ije,l)
    307308                 
    308309           if (pole_sud) ije=ij_end-iip1
     
    313314c$OMP ENDDO 
    314315
    315 
    316           CALL filtreg_p ( finvmaold ,jj_begin,jj_end,jjp1,
    317      .                    llm, -2,2, .TRUE., 1 )
     316! Ehouarn: finvmaold not used
     317!          CALL filtreg_p ( finvmaold ,jj_begin,jj_end,jjp1,
     318!     .                    llm, -2,2, .TRUE., 1 )
    318319
    319320       endif ! of if (FirstCaldyn)
     
    476477         call Register_SwapFieldHallo(phi,phi,ip1jmp1,llm,
    477478     &                                jj_Nb_caldyn,0,0,TestRequest)
    478          call Register_SwapFieldHallo(finvmaold,finvmaold,ip1jmp1,llm,
    479      &                                jj_Nb_caldyn,0,0,TestRequest)
     479!         call Register_SwapFieldHallo(finvmaold,finvmaold,ip1jmp1,llm,
     480!     &                                jj_Nb_caldyn,0,0,TestRequest)
    480481 
    481482        do j=1,nqtot
     
    634635
    635636       CALL integrd_p ( 2,vcovm1,ucovm1,tetam1,psm1,massem1 ,
    636      $         dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis ,
    637      $              finvmaold                                    )
     637     $         dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps,masse,phis )
     638!     $              finvmaold                                    )
    638639
    639640!       CALL FTRACE_REGION_END("integrd")
Note: See TracChangeset for help on using the changeset viewer.