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/dyn3d_common/tourpot.F90

    r2335 r2336  
     1SUBROUTINE tourpot ( vcov, ucov, massebxy, vorpot )
    12!
    2 ! $Header$
    3 !
    4       SUBROUTINE tourpot ( vcov, ucov, massebxy, vorpot )
    5       IMPLICIT NONE
     3!-------------------------------------------------------------------------------
     4! Authors: P. Le Van.
     5!-------------------------------------------------------------------------------
     6! Purpose: Compute potential vorticity.
     7  IMPLICIT NONE
     8  include "dimensions.h"
     9  include "paramet.h"
     10  include "comgeom.h"
     11  include "logic.h"
     12!===============================================================================
     13! Arguments:
     14  REAL, INTENT(IN)  :: vcov    (ip1jm,  llm)
     15  REAL, INTENT(IN)  :: ucov    (ip1jmp1,llm)
     16  REAL, INTENT(IN)  :: massebxy(ip1jm,  llm)
     17  REAL, INTENT(OUT) :: vorpot  (ip1jm,  llm)
     18!===============================================================================
     19! Method used:
     20!   vorpot = ( Filtre( d(vcov)/dx - d(ucov)/dy ) + fext ) /psbarxy
     21!===============================================================================
     22! Local variables:
     23  INTEGER :: l, ij
     24  REAL    :: rot(ip1jm,llm)
     25!===============================================================================
    626
    7 c=======================================================================
    8 c
    9 c   Auteur:  P. Le Van
    10 c   -------
    11 c
    12 c   Objet:
    13 c   ------
    14 c
    15 c    *******************************************************************
    16 c    .........      calcul du tourbillon potentiel             .........
    17 c    *******************************************************************
    18 c
    19 c     vcov,ucov,fext et pbarxyfl sont des argum. d'entree pour le s-pg .
    20 c             vorpot            est  un argum.de sortie pour le s-pg .
    21 c
    22 c=======================================================================
     27!--- Wind vorticity ; correction: rot(iip1,j,l) = rot(1,j,l)
     28  DO l=1,llm
     29    DO ij=1,ip1jm-1
     30      rot(ij,l)=vcov(ij+1,l)-vcov(ij,l)+ucov(ij+iip1,l)-ucov(ij,l)
     31    END DO
     32    DO ij=iip1,ip1jm,iip1; rot(ij,l)=rot(ij-iim,l); END DO
     33  END DO
    2334
    24 #include "dimensions.h"
    25 #include "paramet.h"
    26 #include "comgeom.h"
    27 #include "logic.h"
     35!--- Filter
     36  CALL  filtreg(rot,jjm,llm,2,1,.FALSE.,1)
    2837
    29       REAL  rot( ip1jm,llm )
    30       REAL vcov( ip1jm,llm ),ucov( ip1jmp1,llm )
    31       REAL massebxy( ip1jm,llm ),vorpot( ip1jm,llm )
     38!--- Potential vorticity ; correction: rot(iip1,j,l) = rot(1,j,l)
     39  DO l=1,llm
     40    DO ij=1,ip1jm-1
     41      vorpot(ij,l)=(rot(ij,l)+fext(ij))/massebxy(ij,l)
     42    END DO
     43    DO ij=iip1,ip1jm,iip1; vorpot(ij,l)=vorpot(ij-iim,l); END DO
     44  END DO
    3245
    33       INTEGER l, ij
    34 
    35 
    36 
    37 
    38 c  ... vorpot = ( Filtre( d(vcov)/dx - d(ucov)/dy ) + fext ) /psbarxy ..
    39 
    40 
    41 
    42 c    ........  Calcul du rotationnel du vent V  puis filtrage  ........
    43 
    44       DO 5 l = 1,llm
    45 
    46       DO 2 ij = 1, ip1jm - 1
    47       rot( ij,l ) = vcov(ij+1,l)-vcov(ij,l)+ucov(ij+iip1,l)-ucov(ij,l)
    48    2  CONTINUE
    49 
    50 c    ....  correction pour  rot( iip1,j,l )  .....
    51 c    ....     rot(iip1,j,l) = rot(1,j,l)    .....
    52 
    53 CDIR$ IVDEP
    54 
    55       DO 3 ij = iip1, ip1jm, iip1
    56       rot( ij,l ) = rot( ij -iim, l )
    57    3  CONTINUE
    58 
    59    5  CONTINUE
    60 
    61 
    62       CALL  filtreg( rot, jjm, llm, 2, 1, .FALSE., 1 )
    63 
    64 
    65       DO 10 l = 1, llm
    66 
    67       DO 6 ij = 1, ip1jm - 1
    68       vorpot( ij,l ) = ( rot(ij,l) + fext(ij) ) / massebxy(ij,l)
    69    6  CONTINUE
    70 
    71 c    ..... correction pour  vorpot( iip1,j,l)  .....
    72 c    ....   vorpot(iip1,j,l)= vorpot(1,j,l) ....
    73 CDIR$ IVDEP
    74       DO 8 ij = iip1, ip1jm, iip1
    75       vorpot( ij,l ) = vorpot( ij -iim,l )
    76    8  CONTINUE
    77 
    78   10  CONTINUE
    79 
    80       RETURN
    81       END
     46END SUBROUTINE tourpot
Note: See TracChangeset for help on using the changeset viewer.