Ignore:
Timestamp:
Feb 16, 2023, 5:29:48 PM (22 months ago)
Author:
romain.vande
Message:

Mars PEM:
Deep cleaning of variables name and allocate.
All the "dyn to phys" grid change is done in subroutines and not in the main program.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/evolution/compute_tendencies_mod_slope.F90

    r2835 r2897  
    22! $Id $
    33!
    4 SUBROUTINE compute_tendencies_slope(tendencies_h2o_ice,min_h2o_ice_Y1,&
    5      min_h2o_ice_Y2,iim_input,jjm_input,ngrid,tendencies_h2o_ice_phys,nslope)
     4SUBROUTINE compute_tendencies_slope(ngrid,nslope,min_ice_Y1,&
     5     min_ice_Y2,tendencies_ice)
    66
    77      IMPLICIT NONE
     
    1818!   INPUT
    1919
    20      INTEGER, intent(in) :: iim_input,jjm_input,ngrid  ,nslope                           ! # of grid points along longitude/latitude/ total
    21      REAL, intent(in) , dimension(iim_input+1,jjm_input+1,nslope):: min_h2o_ice_Y1       ! LON x LAT field : minimum of water ice at each point for the first year
    22      REAL, intent(in) , dimension(iim_input+1,jjm_input+1,nslope):: min_h2o_ice_Y2       ! LON x LAT field : minimum of water ice at each point for the second year
     20     INTEGER, intent(in) :: ngrid, nslope                           ! # of grid points along longitude/latitude/ total
     21     REAL, intent(in) , dimension(ngrid,nslope):: min_ice_Y1       ! LON x LAT field : minimum of water ice at each point for the first year
     22     REAL, intent(in) , dimension(ngrid,nslope):: min_ice_Y2       ! LON x LAT field : minimum of water ice at each point for the second year
    2323
    2424!   OUTPUT
    25      REAL, intent(out) , dimension(iim_input+1,jjm_input+1,nslope) :: tendencies_h2o_ice ! LON x LAT field : difference between the minima = evolution of perenial ice
    26      REAL, intent(out) , dimension(ngrid,nslope)   :: tendencies_h2o_ice_phys            ! physical point field : difference between the minima = evolution of perenial ice
     25     REAL, intent(out) , dimension(ngrid,nslope)   :: tendencies_ice            ! physical point field : difference between the minima = evolution of perenial ice
    2726
    2827!   local:
    2928!   ------
    30 
    31      INTEGER :: i,j,ig0,islope                                                           ! loop variable
     29     INTEGER :: ig,islope                                                           ! loop variable
    3230
    3331!=======================================================================
     
    3533!  We compute the difference
    3634
    37   DO j=1,jjm_input+1
    38     DO i = 1, iim_input
    39        DO islope = 1, nslope
    40          tendencies_h2o_ice(i,j,islope)=min_h2o_ice_Y2(i,j,islope)-min_h2o_ice_Y1(i,j,islope)
    41        enddo
    42     ENDDO
     35  DO ig=1,ngrid
     36    DO islope = 1, nslope
     37      tendencies_ice(ig,islope)=min_ice_Y2(ig,islope)-min_ice_Y1(ig,islope)
     38    enddo
    4339  ENDDO
    4440
    4541!  If the difference is too small; there is no evolution
    46   DO j=1,jjm_input+1
    47     DO i = 1, iim_input
    48        DO islope = 1, nslope
    49          if(abs(tendencies_h2o_ice(i,j,islope)).LT.1.0E-10) then
    50             tendencies_h2o_ice(i,j,islope)=0.
    51          endif
    52        enddo
    53     ENDDO
    54   ENDDO
    55 
    56   DO islope = 1,nslope
    57     CALL gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,tendencies_h2o_ice(:,:,islope),tendencies_h2o_ice_phys(:,islope))
     42  DO ig=1,ngrid
     43    DO islope = 1, nslope
     44      if(abs(tendencies_ice(ig,islope)).LT.1.0E-10) then
     45        tendencies_ice(ig,islope)=0.
     46      endif
     47    enddo
    5848  ENDDO
    5949
Note: See TracChangeset for help on using the changeset viewer.