Ignore:
Timestamp:
Jul 31, 2015, 7:22:21 PM (9 years ago)
Author:
dcugnet
Message:
  • Add parallel capability for ce0l.
  • Small bug in grid_noro fixed (smoothed topography was used instead of unsmoothed one for geopotential computation at north pole).
  • Removed average of mass at poles in etat0dyn_netcdf after start_init_dyn => different results in the zoomed grid case.
  • ok_etat0=n and ok_limit=y combination now works fine (if no initial state is needed, but only limit.nc file). This required:
    • to move grid_noro0 and start_init_noro0 subroutines from etat0dyn_netcdf.F90 to limit_netcdf.F90
    • to create init_ssrf_m.F90 file, so that sub-surfaces can be initialized from limit_netcdf.F90 without any etat0*_netcdf routines call).
  • Simplified somehow the corresponding code, in particular: 1) removed obsolete flags "oldice". 2) removed flag "ibar": barycentric interpolation is used everywhere (except in start_init_subsurf, still calling grille_m - to be changed soon). 3) removed useless CPP_PHY precompilation directives, considering the possibility to run ce0l without physics is useless (ce0l is dedicated to Earth physics).
File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3dmem/tourpot_loc.F90

    r2335 r2336  
    1       SUBROUTINE tourpot_loc ( vcov, ucov, massebxy, vorpot )
    2       USE parallel_lmdz
    3       USE mod_filtreg_p
    4       IMPLICIT NONE
     1SUBROUTINE tourpot_loc ( vcov, ucov, massebxy, vorpot )
     2!
     3!-------------------------------------------------------------------------------
     4! Authors: P. Le Van.
     5!-------------------------------------------------------------------------------
     6! Purpose: Compute potential vorticity.
     7  USE parallel_lmdz
     8  USE mod_filtreg_p
     9  IMPLICIT NONE
     10  include "dimensions.h"
     11  include "paramet.h"
     12  include "comgeom.h"
     13  include "logic.h"
     14!===============================================================================
     15! Arguments:
     16  REAL, INTENT(IN)  :: vcov    (ijb_v:ije_v,llm)
     17  REAL, INTENT(IN)  :: ucov    (ijb_u:ije_u,llm)
     18  REAL, INTENT(IN)  :: massebxy(ijb_v:ije_v,llm)
     19  REAL, INTENT(OUT) :: vorpot  (ijb_v:ije_v,llm)
     20!===============================================================================
     21! Method used:
     22!   vorpot = ( Filtre( d(vcov)/dx - d(ucov)/dy ) + fext ) /psbarxy
     23!===============================================================================
     24! Local variables:
     25  INTEGER :: l, ij, ije, ijb, jje, jjb
     26  REAL    :: rot(ijb_v:ije_v,llm)
     27!===============================================================================
    528
    6 c=======================================================================
    7 c
    8 c   Auteur:  P. Le Van
    9 c   -------
    10 c
    11 c   Objet:
    12 c   ------
    13 c
    14 c    *******************************************************************
    15 c    .........      calcul du tourbillon potentiel             .........
    16 c    *******************************************************************
    17 c
    18 c     vcov,ucov,fext et pbarxyfl sont des argum. d'entree pour le s-pg .
    19 c             vorpot            est  un argum.de sortie pour le s-pg .
    20 c
    21 c=======================================================================
     29  ijb=ij_begin-iip1
     30  ije=ij_end
     31  IF(pole_nord) ijb=ij_begin
    2232
    23 #include "dimensions.h"
    24 #include "paramet.h"
    25 #include "comgeom.h"
    26 #include "logic.h"
     33!--- Wind vorticity ; correction: rot(iip1,j,l) = rot(1,j,l)
     34!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     35  DO l=1,llm
     36    IF(pole_sud) ije=ij_end-iip1-1
     37    DO ij=ijb,ije
     38      rot(ij,l)=vcov(ij+1,l)-vcov(ij,l)+ucov(ij+iip1,l)-ucov(ij,l)
     39    END DO
     40    IF(pole_sud) ije=ij_end-iip1
     41    DO ij=ijb+iip1-1,ije,iip1; rot(ij,l)=rot(ij-iim,l); END DO
     42  END DO
     43!$OMP END DO NOWAIT
    2744
    28       REAL  rot( ijb_v:ije_v,llm )
    29       REAL vcov( ijb_v:ije_v,llm ),ucov( ijb_u:ije_u,llm )
    30       REAL massebxy( ijb_v:ije_v,llm ),vorpot( ijb_v:ije_v,llm )
     45!--- Filter
     46  jjb=jj_begin-1
     47  jje=jj_end
     48  IF(pole_nord) jjb=jjb+1
     49  IF(pole_sud)  jje=jje-1
     50  CALL filtreg_p(rot,jjb_v,jje_v,jjb,jje,jjm,llm,2,1,.FALSE.,1)
    3151
    32       INTEGER l, ij ,ije,ijb,jje,jjb
     52!--- Potential vorticity ; correction: rot(iip1,j,l) = rot(1,j,l)
     53!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     54  DO l=1,llm
     55    IF(pole_sud) ije=ij_end-iip1-1
     56    DO ij=ijb,ije
     57      vorpot(ij,l)=(rot(ij,l)+fext(ij))/massebxy(ij,l)
     58    END DO
     59    IF(pole_sud) ije=ij_end-iip1
     60    DO ij=ijb+iip1-1,ije,iip1; vorpot(ij,l)=vorpot(ij-iim,l); END DO
     61  END DO
     62!$OMP END DO NOWAIT
    3363
     64END SUBROUTINE tourpot_loc
    3465
    35       ijb=ij_begin-iip1
    36       ije=ij_end
    37      
    38       if (pole_nord) ijb=ij_begin
    39      
    40      
    41 c  ... vorpot = ( Filtre( d(vcov)/dx - d(ucov)/dy ) + fext ) /psbarxy ..
    42 
    43 
    44 
    45 c    ........  Calcul du rotationnel du vent V  puis filtrage  ........
    46 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    47       DO 5 l = 1,llm
    48 
    49       if (pole_sud)  ije=ij_end-iip1-1
    50       DO 2 ij = ijb, ije
    51       rot( ij,l ) = vcov(ij+1,l)-vcov(ij,l)+ucov(ij+iip1,l)-ucov(ij,l)
    52    2  CONTINUE
    53 
    54 c    ....  correction pour  rot( iip1,j,l )  .....
    55 c    ....     rot(iip1,j,l) = rot(1,j,l)    .....
    56 
    57 CDIR$ IVDEP
    58 
    59       if (pole_sud)  ije=ij_end-iip1
    60      
    61       DO 3 ij = ijb+iip1-1, ije, iip1
    62       rot( ij,l ) = rot( ij -iim, l )
    63    3  CONTINUE
    64 
    65    5  CONTINUE
    66 c$OMP END DO NOWAIT
    67       jjb=jj_begin-1
    68       jje=jj_end
    69      
    70       if (pole_nord) jjb=jjb+1
    71       if (pole_sud)  jje=jje-1
    72       CALL  filtreg_p( rot, jjb_v,jje_v,jjb,jje,jjm, llm,
    73      &                 2, 1, .FALSE., 1 )
    74 
    75 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)     
    76       DO 10 l = 1, llm
    77      
    78       if (pole_sud)  ije=ij_end-iip1-1 
    79      
    80       DO 6 ij = ijb, ije
    81       vorpot( ij,l ) = ( rot(ij,l) + fext(ij) ) / massebxy(ij,l)
    82    6  CONTINUE
    83 
    84 c    ..... correction pour  vorpot( iip1,j,l)  .....
    85 c    ....   vorpot(iip1,j,l)= vorpot(1,j,l) ....
    86 CDIR$ IVDEP
    87       if (pole_sud)  ije=ij_end-iip1
    88       DO 8 ij = ijb+iip1-1, ije, iip1
    89       vorpot( ij,l ) = vorpot( ij -iim,l )
    90    8  CONTINUE
    91 
    92   10  CONTINUE
    93 c$OMP END DO NOWAIT
    94       RETURN
    95       END
Note: See TracChangeset for help on using the changeset viewer.