Ignore:
Timestamp:
Dec 14, 2015, 11:43:09 AM (9 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes r2298:2396 into testing branch

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/phylmd/phys_output_mod.F90

    r2187 r2408  
    3636    USE iophy
    3737    USE dimphy
    38     USE infotrac
     38    USE infotrac_phy, ONLY: nqtot, nqo, niadv, tname, ttext
    3939    USE ioipsl
    40     USE phys_cal_mod, only : hour
     40    USE phys_cal_mod, only : hour, calend
    4141    USE mod_phys_lmdz_para
    4242    USE aero_mod, only : naero_spc,name_aero
     
    4444    USE surface_data, ONLY : ok_snow
    4545    USE phys_output_ctrlout_mod
    46     USE mod_grid_phy_lmdz, only: klon_glo
    47 
     46    USE mod_grid_phy_lmdz, only: klon_glo,nbp_lon,nbp_lat
     47    USE print_control_mod, ONLY: prt_level,lunout
     48    USE vertical_layers_mod, ONLY: ap,bp,preff,presnivs
     49    USE time_phylmdz_mod, ONLY: day_ini, itau_phy, start_time, annee_ref, day_ref
    4850#ifdef CPP_XIOS
    4951    ! ug Pour les sorties XIOS
     
    5254
    5355    IMPLICIT NONE
    54     include "dimensions.h"
    55     include "temps.h"
    5656    include "clesphys.h"
    5757    include "thermcell.h"
    58     include "comvert.h"
    59     include "iniprint.h"
    6058
    6159    ! ug Nouveaux arguments n\'ecessaires au histwrite_mod:
     
    6967    REAL, DIMENSION(klon, klev+1), INTENT(IN)   :: paprs
    7068    REAL, DIMENSION(klon,klev,nqtot), INTENT(IN):: qx, d_qx
    71     REAL, DIMENSION(klon, llm), INTENT(IN)      :: zmasse
     69    REAL, DIMENSION(klon, klev), INTENT(IN)      :: zmasse
    7270
    7371
     
    106104    CHARACTER(LEN=2)                      :: bb3
    107105    CHARACTER(LEN=6)                      :: type_ocean
    108     INTEGER, DIMENSION(iim*jjmp1)         ::  ndex2d
    109     INTEGER, DIMENSION(iim*jjmp1*klev)    :: ndex3d
     106    INTEGER, DIMENSION(nbp_lon*jjmp1)         ::  ndex2d
     107    INTEGER, DIMENSION(nbp_lon*jjmp1*klev)    :: ndex3d
    110108    INTEGER                               :: imin_ins, imax_ins
    111109    INTEGER                               :: jmin_ins, jmax_ins
     
    290288    WRITE(lunout,*)'Alt approx des couches pour une haut d echelle de 8km = ',Alt(1:klev)
    291289    !          endif
     290
     291  ecrit_files(7) = ecrit_files(1)
     292  ecrit_files(8) = ecrit_files(2)
     293  ecrit_files(9) = ecrit_files(3)
     294
    292295  DO iff=1,nfiles
    293296
     
    343346          IF (phys_out_regfkey(iff)) then
    344347             imin_ins=1
    345              imax_ins=iim
     348             imax_ins=nbp_lon
    346349             jmin_ins=1
    347350             jmax_ins=jjmp1
    348351
    349352             ! correction abderr       
    350              do i=1,iim
     353             do i=1,nbp_lon
    351354                WRITE(lunout,*)'io_lon(i)=',io_lon(i)
    352355                IF (io_lon(i).le.phys_out_lonmin(iff)) imin_ins=i
     
    367370                  io_lat(jmax_ins),io_lat(jmin_ins)
    368371
    369              CALL histbeg(phys_out_filenames(iff),iim,io_lon,jjmp1,io_lat, &
     372             CALL histbeg(phys_out_filenames(iff),nbp_lon,io_lon,jjmp1,io_lat, &
    370373                  imin_ins,imax_ins-imin_ins+1, &
    371374                  jmin_ins,jmax_ins-jmin_ins+1, &
     
    418421            DO iq=nqo+1,nqtot
    419422            iiq=niadv(iq)
    420             o_trac(iq-nqo) = ctrl_out((/ 4, 5, 1, 1, 1, 10, 11, 11, 11 /), &
     423            o_trac(iq-nqo) = ctrl_out((/ 4, 5, 5, 5, 10, 10, 11, 11, 11 /), &
    421424                           tname(iiq),'Tracer '//ttext(iiq), "-",  &
    422425                           (/ '', '', '', '', '', '', '', '', '' /))
     
    523526    use ioipsl
    524527    USE phys_cal_mod
     528    USE time_phylmdz_mod, ONLY: day_ref, annee_ref
     529    USE print_control_mod, ONLY: lunout
    525530
    526531    IMPLICIT NONE
     
    531536    real                :: ttt,xxx,timestep,dayseconde,dtime
    532537    parameter (dayseconde=86400.)
    533     include "temps.h"
    534     include "comconst.h"
    535     include "iniprint.h"
    536538
    537539    ipos=scan(str,'0123456789.',.TRUE.)
     
    540542    WRITE(lunout,*) "ipos = ", ipos
    541543    WRITE(lunout,*) "il = ", il
    542     if (ipos == 0) call abort_gcm("convers_timesteps", "bad str", 1)
     544    if (ipos == 0) call abort_physic("convers_timesteps", "bad str", 1)
    543545    read(str(1:ipos),*) ttt
    544546    WRITE(lunout,*)ttt
     
    568570END MODULE phys_output_mod
    569571
     572
Note: See TracChangeset for help on using the changeset viewer.