Ignore:
Timestamp:
Aug 21, 2015, 11:57:36 AM (9 years ago)
Author:
Ehouarn Millour
Message:

Physics/dynamics separation:

  • move test_disvert_m to dynlonlat_phylonlat/phylmd since it is only used by ce0l and relies on dynamics.
  • put "config_inca" in tracinca_mod so physics routines can get the info from there rather than from control_mod.
  • get rid of references to "control_mod" from within the physics.

EM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/cosp/cosp_output_write_mod.F90

    r2311 r2345  
    2121
    2222    USE ioipsl
    23     USE control_mod
     23    USE time_phylmdz_mod, ONLY: itau_phy, start_time, day_step_phy
    2424    USE print_control_mod, ONLY: lunout,prt_level
    2525
     
    4545  real, dimension(Npoints,PARASOL_NREFL) :: parasolcrefl, Ncref
    4646
    47   include "temps.h"
    48 
    4947  Nlevout = vgrid%Nlvgrid
    5048  Ncolout = Ncolumns
    5149
    5250! A refaire
    53        itau_wcosp = itau_phy + itap + start_time * day_step / iphysiq
     51       itau_wcosp = itau_phy + itap + start_time * day_step_phy
    5452        if (prt_level >= 10) then
    55              WRITE(lunout,*)'itau_wcosp, itap, start_time, day_step, iphysiq =', &
    56                              itau_wcosp, itap, start_time, day_step, iphysiq
     53             WRITE(lunout,*)'itau_wcosp, itap, start_time, day_step_phy =', &
     54                             itau_wcosp, itap, start_time, day_step_phy
    5755        endif
    5856
     
    268266    use iophy
    269267    USE mod_phys_lmdz_para
     268    USE mod_grid_phy_lmdz, ONLY: nbp_lon
    270269    USE print_control_mod, ONLY: lunout,prt_level
    271270#ifdef CPP_XIOS
     
    275274    IMPLICIT NONE
    276275
    277     INCLUDE "dimensions.h"
    278     INCLUDE "temps.h"
    279276    INCLUDE "clesphys.h"
    280277
     
    320317       IF ( var%cles(iff) ) THEN
    321318          CALL histdef (cosp_nidfiles(iff), var%name, var%description, var%unit, &
    322                iim,jj_nb,nhoricosp(iff), 1,1,1, -99, 32, &
     319               nbp_lon,jj_nb,nhoricosp(iff), 1,1,1, -99, 32, &
    323320               typeecrit, zstophym,zoutm_cosp(iff))
    324321       ENDIF
     
    332329    use iophy
    333330    USE mod_phys_lmdz_para
     331    USE mod_grid_phy_lmdz, ONLY: nbp_lon
    334332    USE print_control_mod, ONLY: lunout,prt_level
    335333
     
    341339    IMPLICIT NONE
    342340
    343     INCLUDE "dimensions.h"
    344     INCLUDE "temps.h"
    345341    INCLUDE "clesphys.h"
    346342
     
    415411       IF ( var%cles(iff) ) THEN
    416412          CALL histdef (cosp_nidfiles(iff), nom, var%description, var%unit, &
    417                iim, jj_nb, nhoricosp(iff), klevs, 1, &
     413               nbp_lon, jj_nb, nhoricosp(iff), klevs, 1, &
    418414               klevs, nvertsave, 32, typeecrit, &
    419415               zstophym, zoutm_cosp(iff))
     
    428424  USE ioipsl
    429425  use iophy
     426  USE mod_grid_phy_lmdz, ONLY: nbp_lon
    430427  USE print_control_mod, ONLY: lunout,prt_level
    431428
     
    435432
    436433  IMPLICIT NONE
    437   INCLUDE 'dimensions.h'
    438434  INCLUDE 'clesphys.h'
    439435
     
    445441    REAL,DIMENSION(klon_mpi) :: buffer_omp
    446442    INTEGER, allocatable, DIMENSION(:) :: index2d
    447     REAL :: Field2d(iim,jj_nb)
     443    REAL :: Field2d(nbp_lon,jj_nb)
    448444    CHARACTER(LEN=20) ::  nomi, nom
    449445    character(len=2) :: str2
     
    477473      DO iff=1, 3
    478474           IF (var%cles(iff) .AND. cosp_outfilekeys(iff)) THEN
    479                 ALLOCATE(index2d(iim*jj_nb))
     475                ALLOCATE(index2d(nbp_lon*jj_nb))
    480476#ifndef CPP_IOIPSL_NO_OUTPUT
    481         CALL histwrite(cosp_nidfiles(iff),var%name,itau_iocosp,Field2d,iim*jj_nb,index2d)
     477        CALL histwrite(cosp_nidfiles(iff),var%name,itau_iocosp,Field2d,nbp_lon*jj_nb,index2d)
    482478#endif
    483479                deallocate(index2d)
     
    517513  USE ioipsl
    518514  use iophy
     515  USE mod_grid_phy_lmdz, ONLY: nbp_lon
    519516  USE print_control_mod, ONLY: lunout,prt_level
    520517
     
    525522
    526523  IMPLICIT NONE
    527   INCLUDE 'dimensions.h'
    528524  INCLUDE 'clesphys.h'
    529525
     
    536532
    537533    REAL,DIMENSION(klon_mpi,SIZE(field,2)) :: buffer_omp
    538     REAL :: Field3d(iim,jj_nb,SIZE(field,2))
     534    REAL :: Field3d(nbp_lon,jj_nb,SIZE(field,2))
    539535    INTEGER :: ip, n, nlev
    540536    INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d
     
    580576     DO iff=1, 3
    581577        IF (var%cles(iff) .AND. cosp_outfilekeys(iff)) THEN
    582            ALLOCATE(index3d(iim*jj_nb*nlev))
     578           ALLOCATE(index3d(nbp_lon*jj_nb*nlev))
    583579#ifndef CPP_IOIPSL_NO_OUTPUT
    584     CALL histwrite(cosp_nidfiles(iff),nom,itau_iocosp,Field3d,iim*jj_nb*nlev,index3d)
     580    CALL histwrite(cosp_nidfiles(iff),nom,itau_iocosp,Field3d,nbp_lon*jj_nb*nlev,index3d)
    585581#endif
    586582
Note: See TracChangeset for help on using the changeset viewer.