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

Adding xios output functionnalities

YM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/branches/SATURN_DYNAMICO/ICOSAGCM/src/physics_lmdz_generic.f90

    r246 r254  
    4343  USE mpipara 
    4444  USE disvert_mod 
     45  USE xios_mod 
    4546   
    4647  IMPLICIT NONE 
     
    5152  REAL(rstd),ALLOCATABLE :: lonfi(:) 
    5253  REAL(rstd),ALLOCATABLE :: airefi(:) 
     54  REAL(rstd),ALLOCATABLE :: bounds_latfi(:,:) 
     55  REAL(rstd),ALLOCATABLE :: bounds_lonfi(:,:) 
    5356 
    5457    start_day=0 
     
    9497    ALLOCATE(lonfi(nbp_phys)) 
    9598    ALLOCATE(airefi(nbp_phys)) 
     99    ALLOCATE(bounds_latfi(nbp_phys,6)) 
     100    ALLOCATE(bounds_lonfi(nbp_phys,6)) 
    96101     
    97102    pos=0 
     
    104109          pos=pos+1 
    105110          CALL xyz2lonlat(xyz_i(ij,:),lonfi(pos),latfi(pos)) 
     111          CALL xyz2lonlat(xyz_v(ij+z_rup,:), bounds_lonfi(pos,1), bounds_latfi(pos,1)) 
     112          CALL xyz2lonlat(xyz_v(ij+z_up,:), bounds_lonfi(pos,2), bounds_latfi(pos,2)) 
     113          CALL xyz2lonlat(xyz_v(ij+z_lup,:), bounds_lonfi(pos,3), bounds_latfi(pos,3)) 
     114          CALL xyz2lonlat(xyz_v(ij+z_ldown,:), bounds_lonfi(pos,4), bounds_latfi(pos,4)) 
     115          CALL xyz2lonlat(xyz_v(ij+z_down,:), bounds_lonfi(pos,5), bounds_latfi(pos,5)) 
     116          CALL xyz2lonlat(xyz_v(ij+z_rdown,:), bounds_lonfi(pos,6), bounds_latfi(pos,6)) 
    106117          airefi(pos)=Ai(ij)   
    107118        ENDDO 
     
    112123    CALL initialize_unstructured_physics(nbp_phys,llm, comm_icosa, mpi_size,distrib,            & 
    113124                                         day_length,start_day,itau_physics*dt,                  & 
    114                                          latfi,lonfi,airefi,radius,g, gas_constant/mu, cpp,     & 
     125                                         6,latfi,lonfi,airefi,bounds_lonfi,bounds_latfi,         & 
     126                                         radius,g, gas_constant/mu, cpp,                        & 
    115127                                         preff, ap, bp)                                          
    116128     
    117      
     129    CALL xios_set_context     
    118130     
    119131!    CALL init_phys_lmdz(128,97,llm, comm_icosa, mpi_size, distrib) 
     
    135147  USE transfert_mod 
    136148  USE mpipara 
     149  USE xios_mod 
    137150  IMPLICIT NONE 
    138151    INTEGER,INTENT(IN)    :: it 
     
    305318 
    306319!$OMP BARRIER 
     320    CALL xios_set_context     
    307321      
    308322  CONTAINS 
Note: See TracChangeset for help on using the changeset viewer.