Ignore:
Timestamp:
Jul 28, 2025, 7:23:15 PM (6 days ago)
Author:
aborella
Message:

Merge with trunk r5789

Location:
LMDZ6/branches/contrails
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/contrails

  • LMDZ6/branches/contrails/libf/phylmd/phys_output_mod.F90

    r5618 r5791  
    66  USE phys_output_var_mod
    77  USE phys_output_write_mod, ONLY : phys_output_write
     8
    89  REAL, DIMENSION(nfiles),SAVE :: ecrit_files
     10  LOGICAL, DIMENSION(nfiles)   :: phys_out_filekeys
    911
    1012
     
    5153    USE vertical_layers_mod, ONLY: ap,bp,preff,presnivs, aps, bps, pseudoalt, presinter
    5254    USE time_phylmdz_mod, ONLY: day_ini, itau_phy, start_time, annee_ref, day_ref
     55
     56    USE AERO_MOD, ONLY : nbands_lw_rrtm !FC
     57
    5358    ! ug Pour les sorties XIOS
    5459    use wxios_mod
     
    123128    CHARACTER(LEN=20), DIMENSION(nfiles)  :: chtimestep = (/ 'Default', 'Default', 'Default', 'Default', 'Default', &
    124129                                                             'Default', 'Default', 'Default', 'Default', 'Default' /)
    125     LOGICAL, DIMENSION(nfiles)            :: phys_out_filekeys
    126130    LOGICAL, DIMENSION(nfiles)            :: phys_out_filestations
    127131
     
    155159    REAL, DIMENSION(NSW)            :: spectband  !mean wavenumb. of each sp.band
    156160    REAL, DIMENSION(NSW,2)          :: spbnds_sun !bounds of spectband
     161!FC
     162    INTEGER                         :: ILW
     163    REAL,  DIMENSION(nbands_lw_rrtm)  :: wl1_lw, wl2_lw
    157164
    158165    WRITE(lunout,*) 'Debut phys_output_mod.F90'
    159     ! Initialisations (Valeurs par defaut
     166! Initialisations (Valeurs par defaut
     167!FC
     168       wl1_lw = [ 10., 250., 500., 630., 700., 820., 980.,1080. &
     169     & ,1180.,1390.,1480.,1800.,2080.,2250.,2380.,2600.]
     170       wl2_lw = [250., 500., 630., 700., 820., 980.,1080.,1180. &
     171     & ,1390.,1480.,1800.,2080.,2250.,2380.,2600.,3000.]
     172!         print*, 'avant boucle', nbands_lw_rrtm
     173!        DO ILW=1,nbands_lw_rrtm
     174!        spectbandLW(ILW)= (wl1_lw(ilw) + wl2_lw(ILW) )/2
     175!        print*, 'on a les canaux ? ',ILW,spectbandLW(ILW),wl1_lw(ILW),wl2_lw(ilw)
     176!        enddo
     177!        print*, 'spectbandLW',spectbandLW
     178
     179!FC
     180
    160181
    161182    DO ilev=1,klev
     
    229250    type_ecri(10)= 'ave(X)'
    230251
    231     clef_files(1) = ok_mensuel
    232     clef_files(2) = ok_journe
    233     clef_files(3) = ok_hf
    234     clef_files(4) = ok_instan
    235     clef_files(5) = ok_LES
    236     clef_files(6) = ok_instan
    237     clef_files(7) = ok_histNMC(1)
    238     clef_files(8) = ok_histNMC(2)
    239     clef_files(9) = ok_histNMC(3)
     252    clef_files(1:3) = .TRUE.
     253    clef_files(4:10) = .FALSE.
    240254    IF (CPPKEY_STRATAER) THEN
    241255      clef_files(10)= .TRUE.
     
    245259
    246260    !sortir des fichiers "stations" si clef_stations(:)=.TRUE.
    247     clef_stations(1) = .FALSE.
    248     clef_stations(2) = .FALSE.
    249     clef_stations(3) = .FALSE.
    250     clef_stations(4) = .FALSE.
    251     clef_stations(5) = .FALSE.
    252     clef_stations(6) = .FALSE.
    253     clef_stations(7) = .FALSE.
    254     clef_stations(8) = .FALSE.
    255     clef_stations(9) = .FALSE.
    256     clef_stations(10)= .FALSE.
    257 
    258     lev_files(1) = lev_histmth
    259     lev_files(2) = lev_histday
    260     lev_files(3) = lev_histhf
    261     lev_files(4) = lev_histins
    262     lev_files(5) = lev_histLES
    263     lev_files(6) = lev_histins
    264     lev_files(7) = levout_histNMC(1)
    265     lev_files(8) = levout_histNMC(2)
    266     lev_files(9) = levout_histNMC(3)
    267     lev_files(10)= 5
    268 
     261    clef_stations(1:10) = .FALSE.
     262    lev_files(1:10) = 5
     263
     264    print*,'A ecrit_mth=',ecrit_mth
     265    ! Frequencies of the history files;
     266    ! Defaut
     267    ! overwritten by chtimestep given to convers_timesteps
    269268    ecrit_files(1) = ecrit_mth
    270269    ecrit_files(2) = ecrit_day
     
    272271    ecrit_files(4) = ecrit_ins
    273272    ecrit_files(5) = ecrit_LES
    274     ecrit_files(6) = ecrit_ins
    275     ecrit_files(7) = freq_outNMC(1)
    276     ecrit_files(8) = freq_outNMC(2)
    277     ecrit_files(9) = freq_outNMC(3)
    278     ecrit_files(10)= ecrit_mth
     273    ecrit_files(6:10) = ecrit_ins
    279274
    280275    !! Lectures des parametres de sorties dans physiq.def
     
    367362      ELSE
    368363       CALL convers_timesteps(chtimestep(iff),dtime,ecrit_files(iff))
     364      print*,'Dans phys_output_open, iff=',iff,' ecrit_files=',ecrit_files(iff)
    369365      ENDIF
     366      ! ecrit_files contains frequency of file iif in seconds
     367
    370368
    371369       WRITE(lunout,*)'ecrit_files(',iff,')= ',ecrit_files(iff)
     
    502500          CALL histvert(nid_files(iff), "Alt","Height approx for scale heigh of 8km at levels", "Km", &                       
    503501               levmax(iff) - levmin(iff) + 1,pseudoalt,nvertAlt(iff))
     502!FC
     503!          CALL histvert(nid_files(iff), "spectbandLW"," LW bands ", "cm-1", &
     504!                  nbands_lw_rrtm ,wl1_lw, ncanaux(iff))
     505!          print *, ' apres ncanaux = ' , ncanaux(iff),iff
     506!FC
     507
    504508
    505509          ELSE
     
    624628   ! Updated write frequencies due to phys_out_filetimesteps.
    625629    ! Write frequencies are now in seconds. 
    626     ecrit_mth = ecrit_files(1)
    627     ecrit_day = ecrit_files(2)
    628     ecrit_hf  = ecrit_files(3)
    629     ecrit_ins = ecrit_files(4)
    630     ecrit_LES = ecrit_files(5)
    631     ecrit_ins = ecrit_files(6)
     630! WHY CHANGING ecrit_mth ?
     631! For Cosp ?
     632!    ecrit_mth = ecrit_files(1)
     633!    print*,'B ecrit_mth=',ecrit_mth
     634!    ecrit_day = ecrit_files(2)
     635!    ecrit_hf  = ecrit_files(3)
     636!    ecrit_ins = ecrit_files(4)
     637!    ecrit_LES = ecrit_files(5)
     638!    ecrit_ins = ecrit_files(6)
    632639
    633640    IF (prt_level >= 10) THEN
     
    638645      WRITE(lunout,*)'phys_output_open: ends here'
    639646    ENDIF
     647    print*,'Dans phys_output_open,ecrit_files B',ecrit_files(1:6)
    640648
    641649!  DO iq=1,nqtot
     
    679687    IF ( type == 'day'.or.type == 'days'.or.type == 'd'.or.type == 'jours'.or.type == 'jour'.or.type == 'j' )&
    680688           &  timestep = ttt * dayseconde
    681     IF ( type == 'months'.or.type == 'month'.or.type == 'mth'.or.type == 'mois'.or.type == 'm' ) THEN
     689    IF ( type == 'months'.or.type == 'month'.or.type == 'mth'.or.type == 'mois'.or.type == 'm' .or.type == 'mo' ) THEN
    682690       WRITE(lunout,*)'annee_ref,day_ref mon_len',annee_ref,day_ref,mth_len
    683691       timestep = ttt * dayseconde * mth_len
     
    687695    IF ( type == 'mn'.or.type == 'minutes'.or.type == 'minute'.or.type == 'm' ) timestep = ttt * 60.
    688696    IF ( type == 's'.or.type == 'sec'.or.type == 'secondes'.or.type =='seconde'   ) timestep = ttt
    689     IF ( type == 'TS' ) timestep = ttt * dtime
     697    IF ( type == 'TS' .or. type == 'ts' ) timestep = ttt * dtime
    690698
    691699    WRITE(lunout,*)'type =      ',type
Note: See TracChangeset for help on using the changeset viewer.