Ignore:
Timestamp:
Oct 28, 2024, 1:11:48 PM (6 hours ago)
Author:
abarral
Message:

Turn iniprint.h clesphys.h into modules
Remove unused description.h

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/ocean_cpl_mod.f90

    r5274 r5282  
    88!
    99
    10   IMPLICIT NONE
     10  USE clesphys_mod_h
     11    IMPLICIT NONE
    1112  PRIVATE
    1213
     
    4041! Initialize module cpl_init
    4142    CALL cpl_init(dtime, rlon, rlat)
    42    
     43
    4344  END SUBROUTINE ocean_cpl_init
    4445!
     
    6061!
    6162! This subroutine treats the "open ocean", all grid points that are not entierly covered
    62 ! by ice. The subroutine first receives fields from coupler, then some calculations at 
     63! by ice. The subroutine first receives fields from coupler, then some calculations at
    6364! surface is done and finally it sends some fields to the coupler.
    6465!
     
    8283         cpl_send_ocean_fields
    8384    use config_ocean_skin_m, only: activate_ocean_skin
    84 
    85 
    86     INCLUDE "clesphys.h"
    87 !   
    88 ! Input arguments 
     85    USE clesphys_mod_h
     86! Input arguments
    8987!****************************************************************************************
    9088    INTEGER, INTENT(IN)                      :: itime, knon
     
    132130    REAL, DIMENSION(klon), INTENT(INOUT)     :: snow
    133131    REAL, DIMENSION(klon), INTENT(INOUT)     :: agesno
    134  
     132
    135133! Output arguments
    136134!****************************************************************************************
     
    139137    REAL, DIMENSION(klon), INTENT(OUT)       :: flux_u1, flux_v1
    140138    REAL, DIMENSION(klon), INTENT(OUT)       :: tsurf_new
    141     REAL, DIMENSION(klon), INTENT(OUT)       :: dflux_s, dflux_l     
     139    REAL, DIMENSION(klon), INTENT(OUT)       :: dflux_s, dflux_l
    142140    REAL, intent(out):: sens_prec_liq(:) ! (knon)
    143141
    144142    REAL, INTENT(OUT):: sss(:) ! (klon)
    145143    ! bulk salinity of the surface layer of the ocean, in ppt
    146  
     144
    147145
    148146! Local variables
     
    156154    REAL, DIMENSION(klon) :: u1_lay, v1_lay
    157155    LOGICAL               :: check=.FALSE.
    158     REAL sens_prec_sol(knon) 
    159     REAL, DIMENSION(klon) :: lat_prec_liq, lat_prec_sol   
     156    REAL sens_prec_sol(knon)
     157    REAL, DIMENSION(klon) :: lat_prec_liq, lat_prec_sol
    160158
    161159! End definitions
     
    180178    agesno(:) = 0.
    181179    lat_prec_liq = 0.; lat_prec_sol = 0.
    182    
     180
    183181
    184182    DO i = 1, knon
     
    203201
    204202    ! assertion: tsurf_new == tsurf_cpl
    205    
     203
    206204    do j = 1, knon
    207205      i = knindex(j)
     
    213211
    214212
    215    
     213
    216214! - Flux calculation at first modele level for U and V
    217215    CALL calcul_flux_wind(knon, dtime, &
     
    219217         AcoefU, AcoefV, BcoefU, BcoefV, &
    220218         p1lay, temp_air, &
    221          flux_u1, flux_v1) 
     219         flux_u1, flux_v1)
    222220
    223221!****************************************************************************************
     
    226224!****************************************************************************************
    227225    fder_new(:) = fder_old(:) + dflux_s(:) + dflux_l(:)
    228    
     226
    229227    iloc = MAXLOC(fder_new(1:klon))
    230228    IF (check .AND. fder_new(iloc(1))> 0.) THEN
     
    262260       tsurf_new, dflux_s, dflux_l, rhoa)
    263261!
    264 ! This subroutine treats the ocean where there is ice. The subroutine first receives 
    265 ! fields from coupler, then some calculations at surface is done and finally sends 
     262! This subroutine treats the ocean where there is ice. The subroutine first receives
     263! fields from coupler, then some calculations at surface is done and finally sends
    266264! some fields to the coupler.
    267 !   
     265!
    268266    USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
    269267          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
     
    285283
    286284
    287     INCLUDE "clesphys.h"
    288285
    289286! Input arguments
Note: See TracChangeset for help on using the changeset viewer.