Ignore:
Timestamp:
Jul 5, 2024, 4:38:48 PM (2 months ago)
Author:
Sebastien Nguyen
Message:

include ISO keys in pbl_surface and associated routines in phylmd

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/ocean_forced_mod.F90

    r4523 r5022  
    2222       radsol, snow, agesno, &
    2323       qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, &
    24        tsurf_new, dflux_s, dflux_l, sens_prec_liq, rhoa)
     24       tsurf_new, dflux_s, dflux_l, sens_prec_liq, rhoa &
     25#ifdef ISO
     26       ,xtprecip_rain, xtprecip_snow, xtspechum,Roce,rlat, &
     27       xtsnow,xtevap,h1 & 
     28#endif           
     29       )
    2530!
    2631! This subroutine treats the "open ocean", all grid points that are not entierly covered
     
    3641    USE phys_output_var_mod, ONLY : sens_prec_liq_o, sens_prec_sol_o, lat_prec_liq_o, lat_prec_sol_o
    3742    use config_ocean_skin_m, only: activate_ocean_skin
     43#ifdef ISO
     44    USE infotrac_phy, ONLY: ntiso,niso
     45    USE isotopes_routines_mod, ONLY: calcul_iso_surf_oce_vectall, calcul_iso_surf_sic_vectall   
     46#ifdef ISOVERIF
     47    USE isotopes_mod, ONLY: iso_eau,ridicule
     48    !USE isotopes_verif_mod, ONLY: errmax,errmaxrel,iso_verif_egalite_choix
     49    USE isotopes_verif_mod
     50#endif
     51#endif
    3852
    3953    INCLUDE "YOMCST.h"
     
    5771    real, intent(in):: rhoa(:) ! (knon) density of moist air  (kg / m3)
    5872
     73#ifdef ISO
     74    REAL, DIMENSION(ntiso,klon), INTENT(IN)  :: xtprecip_rain, xtprecip_snow
     75    REAL, DIMENSION(ntiso,klon), INTENT(IN)  :: xtspechum
     76    REAL, DIMENSION(klon),       INTENT(IN)  :: rlat
     77#endif
     78
    5979! In/Output arguments
    6080!****************************************************************************************
     
    6282    REAL, DIMENSION(klon), INTENT(INOUT)     :: snow
    6383    REAL, DIMENSION(klon), INTENT(INOUT)     :: agesno !? put to 0 in ocean
    64  
     84#ifdef ISO     
     85    REAL, DIMENSION(niso,klon), INTENT(IN)   :: xtsnow
     86    REAL, DIMENSION(niso,klon), INTENT(INOUT):: Roce
     87#endif
     88
    6589! Output arguments
    6690!****************************************************************************************
     
    7296    REAL, intent(out):: sens_prec_liq(:) ! (knon)
    7397
     98#ifdef ISO     
     99    REAL, DIMENSION(ntiso,klon), INTENT(OUT) :: xtevap ! isotopes in evaporation flux
     100    REAL, DIMENSION(klon),       INTENT(OUT) :: h1 ! just a diagnostic, not useful for the simulation
     101#endif
     102
    74103! Local variables
    75104!****************************************************************************************
     
    80109    REAL, DIMENSION(klon)       :: u1_lay, v1_lay
    81110    LOGICAL                     :: check=.FALSE.
    82     REAL sens_prec_sol(knon)
    83     REAL, DIMENSION(klon) :: lat_prec_liq, lat_prec_sol   
     111    REAL, DIMENSION(knon)       :: sens_prec_sol
     112    REAL, DIMENSION(klon)       :: lat_prec_liq, lat_prec_sol   
     113#ifdef ISO   
     114    REAL, PARAMETER :: t_coup = 273.15     
     115#endif
     116
    84117
    85118!****************************************************************************************
     
    87120!****************************************************************************************
    88121    IF (check) WRITE(*,*)' Entering ocean_forced_noice'
    89    
     122
     123#ifdef ISO
     124#ifdef ISOVERIF
     125    DO i = 1, knon
     126      IF (iso_eau > 0) THEN         
     127        CALL iso_verif_egalite_choix(xtspechum(iso_eau,i), &
     128     &                  spechum(i),'ocean_forced_mod 111', &
     129     &                  errmax,errmaxrel)     
     130        CALL iso_verif_egalite_choix(snow(i), &
     131     &                  xtsnow(iso_eau,i),'ocean_forced_mod 117', &
     132     &                  errmax,errmaxrel)
     133      ENDIF !IF (iso_eau > 0) THEN
     134    ENDDO !DO i=1,knon
     135#endif     
     136#endif
     137
    90138!****************************************************************************************
    91139! 1)   
     
    103151
    104152    else ! GCM
    105       CALL limit_read_sst(knon,knindex,tsurf_lim)
     153      CALL limit_read_sst(knon,knindex,tsurf_lim &
     154#ifdef ISO
     155     &     ,Roce,rlat &
     156#endif     
     157     &     )
    106158    endif ! knon
    107159!sb--
     
    161213         flux_u1, flux_v1) 
    162214
     215#ifdef ISO     
     216    CALL calcul_iso_surf_oce_vectall(klon, knon,t_coup, &
     217     &    ps,tsurf_new,spechum,u1_lay, v1_lay, xtspechum, &
     218     &    evap, Roce,xtevap,h1 &
     219#ifdef ISOTRAC
     220     &    ,knindex &
     221#endif
     222     &    )
     223#endif         
     224
     225#ifdef ISO
     226#ifdef ISOVERIF
     227!          write(*,*) 'ocean_forced_mod 176: sortie de ocean_forced_noice'
     228    IF (iso_eau > 0) THEN
     229      DO i = 1, knon               
     230        CALL iso_verif_egalite_choix(snow(i), &
     231     &          xtsnow(iso_eau,i),'ocean_forced_mod 180', &
     232     &          errmax,errmaxrel)
     233      ENDDO ! DO j=1,knon
     234    ENDIF !IF (iso_eau > 0) THEN
     235#endif
     236#endif   
     237
    163238  END SUBROUTINE ocean_forced_noice
    164239!
     
    173248       radsol, snow, qsol, agesno, tsoil, &
    174249       qsurf, alb1_new, alb2_new, evap, fluxsens, fluxlat, flux_u1, flux_v1, &
    175        tsurf_new, dflux_s, dflux_l, rhoa)
     250       tsurf_new, dflux_s, dflux_l, rhoa &
     251#ifdef ISO
     252       ,xtprecip_rain, xtprecip_snow, xtspechum,Roce, &
     253       xtsnow, xtsol,xtevap,Rland_ice & 
     254#endif           
     255       )
    176256!
    177257! This subroutine treats the ocean where there is ice.
     
    187267    USE indice_sol_mod
    188268    USE phys_output_var_mod, ONLY : sens_prec_liq_o, sens_prec_sol_o, lat_prec_liq_o, lat_prec_sol_o
     269#ifdef ISO
     270    USE infotrac_phy, ONLY: niso, ntiso
     271    USE isotopes_routines_mod, ONLY: calcul_iso_surf_oce_vectall, calcul_iso_surf_sic_vectall
     272#ifdef ISOVERIF
     273    USE isotopes_mod, ONLY: iso_eau,ridicule
     274    !USE isotopes_verif_mod, ONLY: errmax,errmaxrel,iso_verif_egalite_choix
     275    USE isotopes_verif_mod
     276#endif
     277#endif
    189278
    190279!   INCLUDE "indicesol.h"
     
    209298    REAL, DIMENSION(klon), INTENT(IN)    :: u1, v1, gustiness
    210299    real, intent(in):: rhoa(:) ! (knon) density of moist air  (kg / m3)
     300#ifdef ISO
     301    REAL, DIMENSION(ntiso,klon), INTENT(IN) :: xtprecip_rain, xtprecip_snow
     302    REAL, DIMENSION(ntiso,klon), INTENT(IN) :: xtspechum
     303    REAL, DIMENSION(niso,klon),  INTENT(IN) :: Roce
     304    REAL, DIMENSION(niso,klon),  INTENT(IN) :: Rland_ice
     305#endif
    211306
    212307! In/Output arguments
     
    216311    REAL, DIMENSION(klon), INTENT(INOUT)          :: agesno
    217312    REAL, DIMENSION(klon, nsoilmx), INTENT(INOUT) :: tsoil
     313#ifdef ISO     
     314    REAL, DIMENSION(niso,klon), INTENT(INOUT)     :: xtsnow
     315    REAL, DIMENSION(niso,klon), INTENT(IN)        :: xtsol
     316#endif
    218317
    219318! Output arguments
     
    226325    REAL, DIMENSION(klon), INTENT(OUT)            :: tsurf_new
    227326    REAL, DIMENSION(klon), INTENT(OUT)            :: dflux_s, dflux_l     
     327#ifdef ISO     
     328    REAL, DIMENSION(ntiso,klon), INTENT(OUT)      :: xtevap
     329#endif     
    228330
    229331! Local variables
     
    238340    REAL, DIMENSION(klon)       :: u0, v0
    239341    REAL, DIMENSION(klon)       :: u1_lay, v1_lay
    240     REAL sens_prec_liq(knon), sens_prec_sol (knon)   
     342    REAL, DIMENSION(knon)       :: sens_prec_liq, sens_prec_sol
    241343    REAL, DIMENSION(klon)       :: lat_prec_liq, lat_prec_sol   
    242344
     345#ifdef ISO
     346    REAL, PARAMETER :: t_coup = 273.15
     347    REAL, DIMENSION(klon) :: fq_fonte_diag
     348    REAL, DIMENSION(klon) :: fqfonte_diag
     349    REAL, DIMENSION(klon) :: snow_evap_diag
     350    REAL, DIMENSION(klon) :: fqcalving_diag
     351    REAL, DIMENSION(klon) :: run_off_lic_diag
     352    REAL :: coeff_rel_diag
     353    REAL :: max_eau_sol_diag 
     354    REAL, DIMENSION(klon) :: runoff_diag   
     355    INTEGER IXT
     356    REAL, DIMENSION(niso,klon) :: xtsnow_prec, xtsol_prec
     357    REAL, DIMENSION(klon) :: snow_prec, qsol_prec 
     358#endif
    243359
    244360!****************************************************************************************
     
    307423!
    308424!****************************************************************************************
     425#ifdef ISO
     426   ! verif
     427#ifdef ISOVERIF
     428    DO i = 1, knon
     429      IF (iso_eau > 0) THEN
     430        IF (snow(i) > ridicule) THEN
     431          CALL iso_verif_egalite_choix(xtsnow(iso_eau,i),snow(i), &
     432   &              'interfsurf 964',errmax,errmaxrel)
     433        ENDIF !IF ((snow(i) > ridicule)) THEN
     434      ENDIF !IF (iso_eau > 0) THEN     
     435    ENDDO !DO i=1,knon 
     436#endif
     437   ! end verif
     438
     439    DO i = 1, knon
     440      snow_prec(i) = snow(i)
     441      DO ixt = 1, niso
     442      xtsnow_prec(ixt,i) = xtsnow(ixt,i)
     443      ENDDO !DO ixt=1,niso
     444      ! initialisation:
     445      fq_fonte_diag(i) = 0.0
     446      fqfonte_diag(i)  = 0.0
     447      snow_evap_diag(i)= 0.0
     448    ENDDO !DO i=1,knon
     449#endif
     450
     451
    309452    CALL fonte_neige( knon, is_sic, knindex, dtime, &
    310453         tsurf_tmp, precip_rain, precip_snow, &
    311          snow, qsol, tsurf_new, evap)
     454         snow, qsol, tsurf_new, evap &
     455#ifdef ISO   
     456     &  ,fq_fonte_diag,fqfonte_diag,snow_evap_diag,fqcalving_diag   &
     457     &  ,max_eau_sol_diag,runoff_diag,run_off_lic_diag,coeff_rel_diag   &
     458#endif
     459     &   )
     460
     461
     462#ifdef ISO
     463! isotopes: tout est externalisé
     464!#ifdef ISOVERIF
     465!        write(*,*) 'ocean_forced_mod 377: call calcul_iso_surf_sic_vectall'
     466!        write(*,*) 'klon,knon=',klon,knon
     467!#endif
     468    CALL calcul_iso_surf_sic_vectall(klon,knon, &
     469     &          evap,snow_evap_diag,Tsurf_new,Roce,snow, &
     470     &          fq_fonte_diag,fqfonte_diag,dtime,t_coup, &
     471     &          precip_snow,xtprecip_snow,xtprecip_rain, snow_prec,xtsnow_prec, &
     472     &          xtspechum,spechum,ps, &
     473     &          xtevap,xtsnow,fqcalving_diag, &
     474     &          knindex,is_sic,run_off_lic_diag,coeff_rel_diag,Rland_ice &
     475     &   )
     476#ifdef ISOVERIF
     477        !write(*,*) 'ocean_forced_mod 391: sortie calcul_iso_surf_sic_vectall'
     478    IF (iso_eau > 0) THEN
     479      DO i = 1, knon 
     480        CALL iso_verif_egalite_choix(snow(i), &
     481     &           xtsnow(iso_eau,i),'ocean_forced_mod 396', &
     482     &           errmax,errmaxrel)
     483      ENDDO ! DO j=1,knon
     484    ENDIF !IF (iso_eau > 0) then
     485#endif
     486!#ifdef ISOVERIF
     487#endif   
     488!#ifdef ISO
    312489   
    313490! Calculation of albedo at snow (alb_neig) and update the age of snow (agesno)
Note: See TracChangeset for help on using the changeset viewer.