Changeset 3436


Ignore:
Timestamp:
Jan 22, 2019, 5:26:21 PM (5 years ago)
Author:
Ehouarn Millour
Message:

Additional modifications wrt previous commit to enable working without XIOS.
EM+LF

Location:
LMDZ6/trunk/libf/phylmd
Files:
5 edited

Legend:

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

    r3435 r3436  
    1010 
    1111  SUBROUTINE init_etat0_limit_unstruct
     12#ifdef CPP_XIOS
    1213  USE xios
    1314  USE mod_phys_lmdz_para
     
    4647      ENDIF 
    4748
     49#endif
    4850  END SUBROUTINE init_etat0_limit_unstruct
    4951 
    5052  SUBROUTINE create_etat0_limit_unstruct
     53#ifdef CPP_XIOS
    5154  USE mod_grid_phy_lmdz
    5255  USE create_etat0_unstruct_mod
     
    9396      ENDIF
    9497       
     98#endif
    9599  END SUBROUTINE create_etat0_limit_unstruct
    96100 
  • LMDZ6/trunk/libf/phylmd/readaerosol.F90

    r3435 r3436  
    178178  USE mod_phys_lmdz_para
    179179  USE mod_grid_phy_lmdz, ONLY: grid_type, unstructured
     180#ifdef CPP_XIOS
    180181  USE xios
     182#endif
    181183  IMPLICIT NONE
    182184  INTEGER, INTENT(IN) :: flag_aerosol
     185#ifdef CPP_XIOS
    183186  REAL,ALLOCATABLE :: lat_src(:)
    184187  REAL,ALLOCATABLE :: lon_src(:)
     
    238241   
    239242  ENDIF   
    240 
     243#endif
    241244  END SUBROUTINE init_aero_fromfile
    242245
     
    269272    USE iophy, ONLY : io_lon, io_lat
    270273    USE print_control_mod, ONLY: lunout
     274#ifdef CPP_XIOS
    271275    USE xios
    272 
     276#endif
    273277    IMPLICIT NONE
    274278     
     
    682686
    683687    IF (grid_type==unstructured) THEN
     688#ifdef CPP_XIOS
    684689      IF (is_omp_master) THEN
    685690        CALL xios_send_field(TRIM(varname)//"_in",varyear)
     
    697702      CALL scatter_omp(psurf_interp,psurf_out)
    698703      first=.FALSE.
     704#endif
    699705    ELSE
    700706      ! Scatter global field to local domain at local process
  • LMDZ6/trunk/libf/phylmd/readaerosolstrato.F90

    r3435 r3436  
    1515    USE aero_mod
    1616    USE dimphy
     17#ifdef CPP_XIOS
    1718    USE xios
    18 
     19#endif
    1920    implicit none
    2021
     
    143144
    144145    IF (grid_type==unstructured) THEN
     146#ifdef CPP_XIOS
    145147      IF (is_omp_master) THEN
    146148        CALL xios_send_field("taustrat_in",tauaerstrat_mois)
     
    151153      ENDIF
    152154      CALL scatter_omp(tau_aer_strat_mpi,tau_aer_strat)
     155#endif
    153156    ELSE 
    154157!--scatter on all proc
  • LMDZ6/trunk/libf/phylmd/readaerosolstrato_m.F90

    r3435 r3436  
    2424
    2525  SUBROUTINE init_readaerosolstrato1
     26#ifdef CPP_XIOS
    2627  USE netcdf
    2728  USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, &
     
    2930  USE mod_phys_lmdz_para
    3031  USE xios
    31   USE YOERAD, ONLY : NLW
     32!  USE YOERAD, ONLY : NLW
    3233  IMPLICIT NONE
    3334  REAL, POINTER:: latitude(:)
     
    6263    ENDIF
    6364   
     65#endif
    6466  END SUBROUTINE init_readaerosolstrato1
    6567 
    6668  SUBROUTINE init_readaerosolstrato2
     69#ifdef CPP_XIOS
    6770  USE netcdf
    6871  USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_dimid, &
     
    7073  USE mod_phys_lmdz_para
    7174  USE xios
    72   USE YOERAD, ONLY : NLW
     75!  USE YOERAD, ONLY : NLW
    7376  IMPLICIT NONE
    7477  REAL, POINTER:: latitude(:)
     
    128131
    129132    ENDIF
    130    
     133#endif   
    131134  END SUBROUTINE init_readaerosolstrato2
    132135 
  • LMDZ6/trunk/libf/phylmd/regr_horiz_time_climoz_m.F90

    r3435 r3436  
    6666  USE regular_lonlat_mod, ONLY: boundslon_reg, boundslat_reg, south, west, east
    6767  USE slopes_m,           ONLY: slopes
     68#ifdef CPP_XIOS
    6869  USE xios
     70#endif
    6971  USE mod_phys_lmdz_para, ONLY: is_mpi_root, is_master, is_omp_master, gather, gather_mpi, bcast_mpi, klon_mpi
    7072  USE geometry_mod, ONLY : latitude_deg, ind_cell_glo
     
    377379    !=============================================================================
    378380     IF (grid_type==unstructured) THEN
     381#ifdef CPP_XIOS
    379382       nlat_ou=klon_mpi
    380383       
     
    389392       CALL xios_send_field("tro3_in",o3_in3bis(:,:,:,:,:))
    390393       CALL xios_recv_field("tro3_out",o3_regr_lonlat(1,:,:,:,:))
    391 
     394#endif
    392395     ELSE
    393396         
     
    423426     nlat_ou=nbp_lat
    424427     IF (grid_type==unstructured) THEN
     428#ifdef CPP_XIOS
    425429       CALL xios_send_field('o3_out',o3_out3)
    426430       ndims=3
    427431       ALLOCATE(o3_out3_glo(nlat_ou, nlev_in, ntim_ou, read_climoz))
    428432       CALL gather_mpi(o3_out3(1,:,:,:,:), o3_out3_glo)
     433#endif
    429434     ENDIF
    430435
     
    467472   
    468473     IF (grid_type==unstructured) THEN
     474#ifdef CPP_XIOS
    469475       nlat_ou=klon_mpi
    470476
     
    480486       IF(.NOT.lprev) o3_regr_lat(:,:, 0, :) = o3_regr_lat(:,:,12,:)
    481487       IF(.NOT.lnext) o3_regr_lat(:,:,13, :) = o3_regr_lat(:,:, 1,:)
    482        
     488#endif       
    483489     
    484490     ELSE
Note: See TracChangeset for help on using the changeset viewer.