Ignore:
Timestamp:
07/23/14 17:57:17 (10 years ago)
Author:
ymipsl
Message:

Adding xios output functionnalities

YM

Location:
codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf
Files:
1 added
4 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/dyn3dpar/initialize_physics.F90

    r245 r253  
    11SUBROUTINE initialize_unstructured_physics(nbp, nlayer, communicator, nb_proc, distrib, & 
    2                                            punjours, pdayref,ptimestep, lat,lon,area, & 
     2                                           punjours, pdayref,ptimestep,                  & 
     3                                           nb_vertex, lat, lon, area, bounds_lon, bounds_lat, & 
    34                                           prad,pg,pr,pcpp, preff,ap,bp ) 
    45USE mod_phys_lmdz_para 
     
    67USE dimphy 
    78USE comgeomphy, only :   initcomgeomphy, & 
     9                         nvertex,        & 
    810                         airephy, & ! physics grid area (m2) 
    911                         rlond, & ! longitudes 
    10                          rlatd ! latitudes 
     12                         rlatd,  & ! latitudes 
     13                         rbounds_lon,    & 
     14                         rbounds_lat 
    1115USE infotrac, only : nqtot ! number of advected tracers 
    1216USE planete_mod, only: ini_planete_mod 
     17USE xios_output_mod 
     18 
    1319IMPLICIT NONE 
    1420 
     
    2430    REAL,INTENT(in)    :: pcpp ! specific heat Cp 
    2531    REAL,INTENT(in)    :: punjours ! length (in s) of a standard day 
     32    INTEGER            :: nb_vertex 
    2633    REAL,INTENT(in)    :: lat(nbp) ! latitudes of the physics grid 
    2734    REAL,INTENT(in)    :: lon(nbp) ! longitudes of the physics grid 
    2835    REAL,INTENT(in)    :: area(nbp) ! area (m2) 
     36    REAL,INTENT(in)    :: bounds_lon(nbp,nb_vertex) ! longitude boundaries of cell 
     37    REAL,INTENT(in)    :: bounds_lat(nbp,nb_vertex) ! latitude boundaries of cell 
    2938    INTEGER,INTENT(in) :: pdayref ! reference day of for the simulation 
    3039    REAL,INTENT(in)    :: ptimestep ! physics time step (s) 
     
    3443 
    3544    INTEGER :: offset 
    36     REAL,SAVE,ALLOCATABLE    :: plat(:) ! latitudes of the physics grid 
    37     REAL,SAVE,ALLOCATABLE    :: plon(:) ! longitudes of the physics grid 
    38     REAL,SAVE,ALLOCATABLE    :: parea(:) ! area (m2) 
     45    REAL,SAVE,ALLOCATABLE    :: shared_lat(:) ! latitudes of the physics grid 
     46    REAL,SAVE,ALLOCATABLE    :: shared_lon(:) ! longitudes of the physics grid 
     47    REAL,SAVE,ALLOCATABLE    :: shared_area(:) ! area (m2) 
     48    REAL,SAVE,ALLOCATABLE    :: shared_bounds_lon(:,:) ! area (m2) 
     49    REAL,SAVE,ALLOCATABLE    :: shared_bounds_lat(:,:) ! area (m2) 
    3950 
    40     ALLOCATE(plat(nbp),plon(nbp),parea(nbp)) 
    41     plat(:)=lat(:) 
    42     plon(:)=lon(:) 
    43     parea(:)=area(:) 
     51    ALLOCATE(shared_lat(nbp),shared_lon(nbp),shared_area(nbp), shared_bounds_lat(nbp,nb_vertex), shared_bounds_lon(nbp,nb_vertex)) 
     52    shared_lat(:)=lat(:) 
     53    shared_lon(:)=lon(:) 
     54    shared_area(:)=area(:) 
     55    shared_bounds_lat(:,:) = bounds_lat(:,:) 
     56    shared_bounds_lon(:,:) = bounds_lon(:,:) 
    4457     
    4558    CALL init_grid_phy_lmdz(nbp,1,sum(distrib),nlayer) 
    4659    CALL init_phys_lmdz_para(nbp,1,communicator,nb_proc,distrib) 
    4760 
    48  
     61    nvertex = nb_vertex 
    4962!$OMP PARALLEL 
    5063    CALL init_dimphy(klon_omp,nbp_lev) 
     
    5265     
    5366    offset=0 
    54     airephy(1:klon_omp)=parea(offset+klon_omp_begin:offset+klon_omp_end) 
    55     rlond(1:klon_omp)=plon(offset+klon_omp_begin:offset+klon_omp_end) 
    56     rlatd(1:klon_omp)=plat(offset+klon_omp_begin:offset+klon_omp_end) 
     67    airephy(1:klon_omp)=shared_area(offset+klon_omp_begin:offset+klon_omp_end) 
     68    rlond(1:klon_omp)=shared_lon(offset+klon_omp_begin:offset+klon_omp_end) 
     69    rlatd(1:klon_omp)=shared_lat(offset+klon_omp_begin:offset+klon_omp_end) 
     70    rbounds_lon(1:klon_omp,:)=shared_bounds_lon(offset+klon_omp_begin:offset+klon_omp_end,:) 
     71    rbounds_lat(1:klon_omp,:)=shared_bounds_lat(offset+klon_omp_begin:offset+klon_omp_end,:) 
    5772 
    5873! copy over preff , ap() and bp()  
     
    6378    CALL inifis(klon_omp,nlayer,nqtot,pdayref,punjours,ptimestep, & 
    6479                rlatd,rlond,airephy,prad,pg,pr,pcpp) 
    65              
     80                 
     81    CALL initialize_xios_output         
    6682!$OMP END PARALLEL 
    6783 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/comgeomphy.F90

    r242 r253  
    11module comgeomphy 
     2   integer,save             :: nvertex=0 
    23   real,save,allocatable :: airephy(:) 
    34   real,save,allocatable :: rlatd(:) 
    45   real,save,allocatable :: rlond(:) 
    5 !$OMP THREADPRIVATE(airephy,cuphy,cvphy,rlatd,rlond) 
     6   real,save,allocatable :: rbounds_lon(:,:) 
     7   real,save,allocatable :: rbounds_lat(:,:) 
     8!$OMP THREADPRIVATE(airephy,cuphy,cvphy,rlatd,rlond,rbounds_lon,rbounds_lat) 
    69contains 
    710   
     
    1417    allocate(rlatd(klon_omp)) 
    1518    allocate(rlond(klon_omp)) 
     19    allocate(rbounds_lon(klon_omp,nvertex)) 
     20    allocate(rbounds_lat(klon_omp,nvertex)) 
    1621 
    1722  end subroutine initcomgeomphy 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/physiq.F90

    r232 r253  
    3535                            obliquit, nres, z0 
    3636 
     37      use xios_output_mod  
    3738      implicit none 
    3839 
     
    471472 
    472473 
     474 
     475      CALL update_xios_timestep 
     476 
     477 
    473478!======================================================================= 
    474479 
     
    22192224      icount=icount+1 
    22202225 
     2226!!!!!!!!!!!!!!!! section for XIOS output !!!!!!!!!!!!!!!       
     2227      CALL write_xios_field("tsurf",tsurf) 
     2228      CALL write_xios_field("ps",ps) 
     2229      CALL write_xios_field("phisinit",phisfi) 
     2230      CALL write_xios_field("aire",area) 
     2231      CALL write_xios_field("temp",zt) 
     2232      CALL write_xios_field("u",zu) 
     2233      CALL write_xios_field("v",zv) 
     2234      CALL write_xios_field("p",pplay) 
     2235      CALL write_xios_field("ISR",fluxtop_dn) 
     2236      CALL write_xios_field("ASR",fluxabs_sw) 
     2237      CALL write_xios_field("OLR",fluxtop_lw) 
     2238 
    22212239      if (lastcall) then 
    22222240 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/writediagfi.F

    r245 r253  
    115115      real phisfi_glo(ngrid) ! surface geopotential on global physics grid 
    116116#endif 
    117  
     117      
     118      RETURN 
    118119!*************************************************************** 
    119120!Sortie des variables au rythme voulu 
Note: See TracChangeset for help on using the changeset viewer.