Changeset 3238 for LMDZ6


Ignore:
Timestamp:
Mar 5, 2018, 5:15:48 PM (6 years ago)
Author:
Laurent Fairhead
Message:

Adding some debugging information

File:
1 edited

Legend:

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

    r3107 r3238  
    1212  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: nptabij
    1313  INTEGER, SAVE :: itau_iophy
     14  LOGICAL :: check_dim = .false.
    1415
    1516!$OMP THREADPRIVATE(itau_iophy)
     
    457458
    458459    USE ioipsl, ONLY: histdef
    459     USE mod_phys_lmdz_para, ONLY: jj_nb
     460    USE mod_phys_lmdz_para, ONLY: jj_nb, is_master
    460461    USE phys_output_var_mod, ONLY: type_ecri, zoutm, zdtime_moy, lev_files, &
    461462                                   nid_files, nhorim, swaero_diag, dryaod_diag, nfiles, &
     
    463464    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    464465    USE aero_mod, ONLY : naero_tot, name_aero_tau
     466    USE print_control_mod, ONLY: prt_level,lunout
    465467
    466468    IMPLICIT NONE
     
    483485       zstophym=zdtime_moy
    484486    ENDIF
    485 
     487    IF (check_dim .AND. is_master) WRITE(lunout,*)'histdef2d_old for ', nomvar
    486488    ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def
    487489    CALL conf_physoutputs(nomvar,flag_var)
     
    533535    USE ioipsl, ONLY: histdef
    534536    USE dimphy, ONLY: klev
    535     USE mod_phys_lmdz_para, ONLY: jj_nb
     537    USE mod_phys_lmdz_para, ONLY: jj_nb, is_master
    536538    USE phys_output_var_mod, ONLY: type_ecri, zoutm, lev_files, nid_files, &
    537539                                   nhorim, zdtime_moy, levmin, levmax, &
    538540                                   nvertm, nfiles
    539541    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
     542    USE print_control_mod, ONLY: prt_level,lunout
    540543    IMPLICIT NONE
    541544
     
    553556    ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def
    554557    CALL conf_physoutputs(nomvar,flag_var)
     558
     559    IF (check_dim .AND. is_master) WRITE(lunout,*)'histdef3d_old for ', nomvar
    555560
    556561    IF (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') THEN
     
    580585
    581586    USE ioipsl, ONLY: histdef
    582     USE mod_phys_lmdz_para, ONLY: jj_nb
     587    USE mod_phys_lmdz_para, ONLY: jj_nb, is_master
    583588    USE phys_output_var_mod, ONLY: ctrl_out, type_ecri_files, zoutm, zdtime_moy, &
    584589                                   clef_stations, phys_out_filenames, lev_files, &
     
    591596    USE wxios, ONLY: wxios_add_field_to_file
    592597#endif
     598    USE print_control_mod, ONLY: prt_level,lunout
    593599    IMPLICIT NONE
    594600
     
    601607    REAL zstophym
    602608    CHARACTER(LEN=20) :: typeecrit
     609
     610    IF (check_dim .AND. is_master) WRITE(lunout,*)'histdef2d for ', var%name
    603611
    604612    ! ug On récupère le type écrit de la structure:
     
    695703    USE ioipsl, ONLY: histdef
    696704    USE dimphy, ONLY: klev
    697     USE mod_phys_lmdz_para, ONLY: jj_nb
     705    USE mod_phys_lmdz_para, ONLY: jj_nb, is_master
    698706    USE phys_output_var_mod, ONLY: ctrl_out, type_ecri_files, zoutm, zdtime_moy, &
    699707                                   clef_stations, phys_out_filenames, lev_files, &
     
    705713    USE wxios, ONLY: wxios_add_field_to_file
    706714#endif
     715    USE print_control_mod, ONLY: prt_level,lunout
    707716    IMPLICIT NONE
    708717
     
    714723    REAL zstophym
    715724    CHARACTER(LEN=20) :: typeecrit
     725
     726    IF (check_dim .AND. is_master) WRITE(lunout,*)'histdef3d for ', var%name
    716727
    717728    ! ug On récupère le type écrit de la structure:
     
    801812  USE mod_phys_lmdz_para, ONLY: Gather_omp, grid1Dto2D_mpi, &
    802813                                is_sequential, klon_mpi_begin, klon_mpi_end, &
    803                                 jj_nb, klon_mpi
     814                                jj_nb, klon_mpi, is_master
    804815  USE ioipsl, ONLY: histwrite
    805816  USE print_control_mod, ONLY: prt_level,lunout
     
    820831
    821832    IF (size(field)/=klon) CALL abort_physic('iophy::histwrite2d','Field first DIMENSION not equal to klon',1)
    822    
     833    IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite2d_phy_old for ', name
     834
    823835    CALL Gather_omp(field,buffer_omp)   
    824836!$OMP MASTER
     
    865877  USE mod_phys_lmdz_para, ONLY: Gather_omp, grid1Dto2D_mpi, &
    866878                                is_sequential, klon_mpi_begin, klon_mpi_end, &
    867                                 jj_nb, klon_mpi
     879                                jj_nb, klon_mpi, is_master
    868880  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    869881  USE ioipsl, ONLY: histwrite
     
    882894    REAL,allocatable, DIMENSION(:,:) :: fieldok
    883895
     896    IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite3d_phy_old for ', name
    884897
    885898    IF (size(field,1)/=klon) CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
     
    936949  USE mod_phys_lmdz_para, ONLY: gather_omp, grid1dto2d_mpi, &
    937950                                jj_nb, klon_mpi, klon_mpi_begin, &
    938                                 klon_mpi_end, is_sequential
     951                                klon_mpi_end, is_sequential, is_master
    939952  USE ioipsl, ONLY: histwrite
    940953  USE phys_output_var_mod, ONLY: ctrl_out, clef_files, lev_files, &
     
    965978    INTEGER :: ip
    966979    REAL, ALLOCATABLE, DIMENSION(:) :: fieldok
     980
     981    IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite2d_phy for ',trim(var%name)
    967982
    968983    IF (prt_level >= 10) THEN
     
    11031118  USE mod_phys_lmdz_para, ONLY: gather_omp, grid1dto2d_mpi, &
    11041119                                jj_nb, klon_mpi, klon_mpi_begin, &
    1105                                 klon_mpi_end, is_sequential
     1120                                klon_mpi_end, is_sequential, is_master
    11061121  USE ioipsl, ONLY: histwrite
    11071122  USE phys_output_var_mod, ONLY: ctrl_out, clef_files, lev_files, &
     
    11291144    INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d
    11301145    REAL,ALLOCATABLE, DIMENSION(:,:) :: fieldok
     1146
     1147  IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite3d_phy for ', trim(var%name)
    11311148
    11321149  IF (prt_level >= 10) write(lunout,*)'Begin histrwrite3d ',var%name
     
    12671284  USE mod_phys_lmdz_para, ONLY: gather_omp, grid1Dto2D_mpi, &
    12681285                                is_sequential, klon_mpi_begin, klon_mpi_end, &
    1269                                 jj_nb, klon_mpi
     1286                                jj_nb, klon_mpi, is_master
    12701287  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
    12711288  USE xios, ONLY: xios_send_field
     
    12831300    INTEGER :: ip
    12841301    REAL, ALLOCATABLE, DIMENSION(:) :: fieldok
     1302
     1303    IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite2d_xios for ', field_name
    12851304
    12861305    IF (prt_level >= 10) WRITE(lunout,*)'Begin histrwrite2d_xios ',field_name
     
    13431362  USE mod_phys_lmdz_para, ONLY: gather_omp, grid1Dto2D_mpi, &
    13441363                                is_sequential, klon_mpi_begin, klon_mpi_end, &
    1345                                 jj_nb, klon_mpi
     1364                                jj_nb, klon_mpi, is_master
    13461365  USE xios, ONLY: xios_send_field
    13471366  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
     
    13591378    REAL,ALLOCATABLE, DIMENSION(:,:) :: fieldok
    13601379
    1361   IF (prt_level >= 10) write(lunout,*)'Begin histrwrite3d_xios ',field_name
     1380    IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite3d_xios for ', field_name
     1381
     1382    IF (prt_level >= 10) write(lunout,*)'Begin histrwrite3d_xios ',field_name
    13621383
    13631384    !Et on.... écrit
     
    14181439  SUBROUTINE histwrite0d_xios(field_name, field)
    14191440  USE xios, ONLY: xios_send_field
     1441  USE mod_phys_lmdz_para, ONLY: is_master
     1442  USE print_control_mod, ONLY: prt_level,lunout
    14201443  IMPLICIT NONE
    14211444
    14221445    CHARACTER(LEN=*), INTENT(IN) :: field_name
    14231446    REAL, INTENT(IN) :: field ! --> scalar
     1447
     1448    IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite0d_xios for ', field_name
    14241449
    14251450!$OMP MASTER
Note: See TracChangeset for help on using the changeset viewer.