Ignore:
Timestamp:
Oct 19, 2023, 4:02:57 PM (8 months ago)
Author:
idelkadi
Message:

Merged trunk changes -r4488:4726 LMDZ_ECRad branch

Location:
LMDZ6/branches/LMDZ_ECRad
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/LMDZ_ECRad

  • LMDZ6/branches/LMDZ_ECRad/libf/phylmdiso/phys_output_mod.F90

    r4170 r4727  
    4747    USE vertical_layers_mod, ONLY: ap,bp,preff,presnivs, aps, bps, pseudoalt
    4848    USE time_phylmdz_mod, ONLY: day_ini, itau_phy, start_time, annee_ref, day_ref
    49 #ifdef CPP_XIOS
    5049    ! ug Pour les sorties XIOS
    5150    USE wxios
    52 #endif
    5351#ifdef ISO
    5452    USE isotopes_mod, ONLY: isoName,iso_HTO
     
    140138    REAL, DIMENSION(klev+1)   :: lev_index
    141139               
    142 #ifdef CPP_XIOS
    143140    ! ug Variables utilis\'ees pour r\'ecup\'erer le calendrier pour xios
    144141    INTEGER :: x_an, x_mois, x_jour
     
    146143    INTEGER :: ini_an, ini_mois, ini_jour
    147144    REAL :: ini_heure
    148 #endif
    149145    INTEGER                         :: ISW
    150146    REAL, DIMENSION(NSW)            :: wl1_sun, wl2_sun !wavelength bounds (in um) for SW
     
    178174    ALLOCATE(o_xtpluc(ntraciso))
    179175    ALLOCATE(o_xtevap(ntraciso))
     176    ALLOCATE(o_xtevap_srf(ntraciso,4))
    180177    ALLOCATE(o_xtovap(ntraciso))
    181178    ALLOCATE(o_xtoliq(ntraciso))
     
    325322     ENDIF
    326323
    327 #ifdef CPP_XIOS
    328     ! ug R\'eglage du calendrier xios
    329     !Temps julian => an, mois, jour, heure
    330     CALL ju2ymds(zjulian, x_an, x_mois, x_jour, x_heure)
    331     CALL ju2ymds(zjulian_start, ini_an, ini_mois, ini_jour, ini_heure)
    332     CALL wxios_set_cal(dtime, calend, x_an, x_mois, x_jour, x_heure, ini_an, &
    333                        ini_mois, ini_jour, ini_heure )
    334 #endif
     324    IF (using_xios) THEN
     325      ! ug R\'eglage du calendrier xios
     326      !Temps julian => an, mois, jour, heure
     327      CALL ju2ymds(zjulian, x_an, x_mois, x_jour, x_heure)
     328      CALL ju2ymds(zjulian_start, ini_an, ini_mois, ini_jour, ini_heure)
     329      CALL wxios_set_cal(dtime, calend, x_an, x_mois, x_jour, x_heure, ini_an, &
     330                         ini_mois, ini_jour, ini_heure )
     331    ENDIF
    335332
    336333!!!!!!!!!!!!!!!!!!!!!!! Boucle sur les fichiers !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    365362
    366363
    367 #ifdef CPP_XIOS
     364    IF (using_xios) THEN
    368365!!! Ouverture de chaque fichier XIOS !!!!!!!!!!!
    369     IF (.not. ok_all_xml) THEN
     366      IF (.not. ok_all_xml) THEN
     367        IF (prt_level >= 10) THEN
     368         print*,'phys_output_open: call wxios_add_file with phys_out_filenames(iff)=',trim(phys_out_filenames(iff))   
     369        ENDIF
     370        CALL wxios_add_file(phys_out_filenames(iff),chtimestep(iff),lev_files(iff)) 
     371      ENDIF
     372
     373!!! Declaration des axes verticaux de chaque fichier:
    370374      IF (prt_level >= 10) THEN
    371         print*,'phys_output_open: call wxios_add_file with phys_out_filenames(iff)=',trim(phys_out_filenames(iff))   
     375        print*,'phys_output_open: Declare vertical axes for each file'
    372376      ENDIF
    373       CALL wxios_add_file(phys_out_filenames(iff),chtimestep(iff),lev_files(iff)) 
    374     ENDIF
    375 
    376 !!! Declaration des axes verticaux de chaque fichier:
    377     IF (prt_level >= 10) THEN
    378       print*,'phys_output_open: Declare vertical axes for each file'
    379     ENDIF
    380 
    381    IF (iff.LE.6.OR.iff.EQ.10) THEN
    382     CALL wxios_add_vaxis("presnivs", &
    383             levmax(iff) - levmin(iff) + 1, presnivs(levmin(iff):levmax(iff)))
    384     CALL wxios_add_vaxis("Ahyb", &
     377
     378      IF (iff.LE.6.OR.iff.EQ.10) THEN
     379        CALL wxios_add_vaxis("presnivs", &
     380             levmax(iff) - levmin(iff) + 1, presnivs(levmin(iff):levmax(iff)))
     381        CALL wxios_add_vaxis("Ahyb", &
    385382            levmax(iff) - levmin(iff) + 1, aps(levmin(iff):levmax(iff)), positif='down', &
    386383            bnds=Ahyb_bounds(levmin(iff):levmax(iff),:))
    387     CALL wxios_add_vaxis("Bhyb", &
     384        CALL wxios_add_vaxis("Bhyb", &
    388385            levmax(iff) - levmin(iff) + 1, bps(levmin(iff):levmax(iff)), positif='down', &
    389386            bnds=Bhyb_bounds(levmin(iff):levmax(iff),:))
    390     CALL wxios_add_vaxis("klev", levmax(iff) - levmin(iff) + 1, &
     387        CALL wxios_add_vaxis("klev", levmax(iff) - levmin(iff) + 1, &
    391388                          lev_index(levmin(iff):levmax(iff)))
    392     CALL wxios_add_vaxis("klevp1", klev+1, &
     389        CALL wxios_add_vaxis("klevp1", klev+1, &
    393390                          lev_index(1:klev+1))
    394     CALL wxios_add_vaxis("bnds", 2, (/1.,2./))
    395 
    396     CALL wxios_add_vaxis("Alt", &
     391        CALL wxios_add_vaxis("bnds", 2, (/1.,2./))
     392
     393        CALL wxios_add_vaxis("Alt", &
    397394            levmax(iff) - levmin(iff) + 1, pseudoalt)
    398 
    399     ! wl1_sun/wl2_sun: minimum/maximum bound of wavelength (in um)
    400     SELECT CASE(NSW)
    401       CASE(6)
    402         wl1_sun(1:6) = [0.180, 0.250, 0.440, 0.690, 1.190, 2.380]
    403         wl2_sun(1:6) = [0.250, 0.440, 0.690, 1.190, 2.380, 4.000]
    404       CASE(2)
    405         wl1_sun(1:2) = [0.250, 0.690]
    406         wl2_sun(1:2) = [0.690, 4.000]
    407     END SELECT
    408 
    409     DO ISW=1, NSW
    410      wn1_sun(ISW)=1.e+6/wl1_sun(ISW)
    411      wn2_sun(ISW)=1.e+6/wl2_sun(ISW)
    412      spbnds_sun(ISW,1)=wn2_sun(ISW)
    413      spbnds_sun(ISW,2)=wn1_sun(ISW)
    414      spectband(ISW)=(wn1_sun(ISW)+wn2_sun(ISW))/2
    415     ENDDO
     395 
     396        ! wl1_sun/wl2_sun: minimum/maximum bound of wavelength (in um)
     397        SELECT CASE(NSW)
     398          CASE(6)
     399          wl1_sun(1:6) = [0.180, 0.250, 0.440, 0.690, 1.190, 2.380]
     400          wl2_sun(1:6) = [0.250, 0.440, 0.690, 1.190, 2.380, 4.000]
     401        CASE(2)
     402          wl1_sun(1:2) = [0.250, 0.690]
     403          wl2_sun(1:2) = [0.690, 4.000]
     404        END SELECT
     405
     406        DO ISW=1, NSW
     407          wn1_sun(ISW)=1.e+6/wl1_sun(ISW)
     408          wn2_sun(ISW)=1.e+6/wl2_sun(ISW)
     409          spbnds_sun(ISW,1)=wn2_sun(ISW)
     410          spbnds_sun(ISW,2)=wn1_sun(ISW)
     411          spectband(ISW)=(wn1_sun(ISW)+wn2_sun(ISW))/2
     412        ENDDO
    416413!
    417414!!! ajout axe vertical spectband : solar band number
    418     CALL wxios_add_vaxis("spectband", NSW, spectband, positif='down')
    419    ELSE
     415        CALL wxios_add_vaxis("spectband", NSW, spectband, positif='down')
     416      ELSE
    420417    ! NMC files
    421     CALL wxios_add_vaxis("plev", &
     418        CALL wxios_add_vaxis("plev", &
    422419            levmax(iff) - levmin(iff) + 1, rlevSTD(levmin(iff):levmax(iff)))
    423    ENDIF
    424 #endif
     420      ENDIF
     421    ENDIF
    425422
    426423        IF (clef_files(iff)) THEN
     
    557554      o_xtplul  (ixt)=ctrl_out(flag,   'plul'//TRIM(outiso),   'Large-scale Precip.', unit, [('',i=1,nfiles)])
    558555      o_xtevap  (ixt)=ctrl_out(flag,   'evap'//TRIM(outiso),             'Evaporat.', unit, [('',i=1,nfiles)])
     556
     557      ! ajout Camille 8 mai 2023
     558      flag = [1, 6, 10, 10, 10, 10, 11, 11, 11, 11]
     559      o_xtevap_srf (ixt,1)=ctrl_out(flag,   'evap_ter'//TRIM(outiso), 'Evap sfc'//clnsurf(1), unit, [('',i=1,nfiles)])
     560      o_xtevap_srf (ixt,2)=ctrl_out(flag,   'evap_lic'//TRIM(outiso), 'Evap sfc'//clnsurf(2), unit, [('',i=1,nfiles)])
     561      o_xtevap_srf (ixt,3)=ctrl_out(flag,   'evap_oce'//TRIM(outiso), 'Evap sfc'//clnsurf(3), unit, [('',i=1,nfiles)])
     562      o_xtevap_srf (ixt,4)=ctrl_out(flag,   'evap_sic'//TRIM(outiso), 'Evap sfc'//clnsurf(4), unit, [('',i=1,nfiles)])
    559563
    560564      flag = [2,  3,  4, 10, 10, 10, 11, 11, 11, 11]; unit = 'kg/kg'
Note: See TracChangeset for help on using the changeset viewer.