Ignore:
Timestamp:
06/04/19 18:30:08 (5 years ago)
Author:
dubos
Message:

devel : store cell bounds once, use them for XIOS later

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/sphere/compute_geometry.f90

    r863 r880  
    11MODULE compute_geometry_mod 
    22  USE geometry 
     3  USE dimensions 
     4 
     5  USE domain_mod, ONLY : t_domain, t_cellset, & 
     6       domain, ndomain, assigned_domain, & 
     7       domain_glo, ndomain_glo, domloc_glo_ind, swap_needed 
     8  USE omp_para, ONLY : is_omp_level_master, is_master 
     9  USE transfert_mod, ONLY : req_i0, req_i1, t_message, transfert_request, transfert_message, init_message 
     10 
     11  USE spherical_geom_mod, ONLY : xyz2lonlat, circumcenter, & 
     12       compute_centroid, centroid, & 
     13       surf_triangle, dist_cart, div_arc_bis, & 
     14       schmidt_transform 
     15  USE vector, ONLY : norm, cross_product2 
     16 
    317  IMPLICIT NONE 
    418  PRIVATE 
     
    1024 
    1125  SUBROUTINE update_circumcenters  
    12     USE domain_mod 
    13     USE dimensions 
    14     USE spherical_geom_mod 
    15     USE vector 
    16     USE transfert_mod 
    17     USE omp_para 
    18  
    19     IMPLICIT NONE 
     26 
    2027    REAL(rstd) :: x1(3),x2(3) 
    2128    REAL(rstd) :: vect(3,6) 
     
    3643     
    3744    DO ind=1,ndomain 
    38       IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE 
     45 
    3946      CALL swap_dimensions(ind) 
    4047      CALL swap_geometry(ind) 
     
    5562 
    5663  SUBROUTINE remap_schmidt_loc 
    57     USE spherical_geom_mod 
    5864    USE getin_mod 
    59     USE omp_para 
    60     USE domain_mod 
    61     USE dimensions 
    62     IMPLICIT NONE 
    6365    INTEGER :: ind,i,j,n 
    6466    REAL(rstd) :: schmidt_factor, schmidt_lon, schmidt_lat 
     
    9193 
    9294  SUBROUTINE optimize_geometry 
    93   USE metric 
    94   USE spherical_geom_mod 
    95   USE domain_mod 
    96   USE dimensions 
    97   USE transfert_mod 
    98   USE vector 
    9995  USE getin_mod 
    100   USE omp_para 
    101   IMPLICIT NONE 
    10296    INTEGER :: nb_it=0 
    10397    TYPE(t_domain),POINTER :: d 
     
    193187    ! copy position of generators and vertices back into domain(:)%xyz/vertex 
    194188    ! so that XIOS/create_header_gen gets the right values 
    195     USE omp_para 
    196     USE dimensions 
    197     USE domain_mod  
    198     USE transfert_mpi_mod 
     189    USE transfert_mpi_mod, ONLY : gather_field, bcast_field 
    199190 
    200191    INTEGER :: ind,i,j,k,n 
     
    253244  SUBROUTINE set_geometry 
    254245  USE metric 
    255   USE vector 
    256   USE spherical_geom_mod 
    257   USE domain_mod 
    258   USE dimensions 
    259   USE transfert_mod 
    260   USE getin_mod 
    261   USE omp_para 
    262   IMPLICIT NONE 
    263246 
    264247    REAL(rstd) :: surf(6) 
     
    279262    CALL remap_schmidt_loc 
    280263    CALL update_circumcenters 
    281     ! copy position of generators and vertices back into domain(:)%xyz/vertex 
    282     ! so that XIOS gets the right values 
    283     CALL update_domain 
    284264 
    285265    DO ind=1,ndomain 
     
    527507  
    528508  END SUBROUTINE set_geometry 
    529    
     509 
    530510  SUBROUTINE compute_wee(n,pos,w) 
    531   IMPLICIT NONE 
    532511    INTEGER,INTENT(IN) :: n 
    533512    INTEGER,INTENT(IN) :: pos 
     
    555534   END SUBROUTINE compute_wee 
    556535             
    557  
    558536   
    559537  SUBROUTINE compute_geometry 
    560538    USE grid_param 
    561     USE domain_mod, ONLY : swap_needed 
    562539    USE init_unstructured_mod, ONLY : read_local_mesh 
    563     IMPLICIT NONE 
    564  
     540    USE set_bounds_mod, ONLY : set_bounds 
    565541    CALL allocate_geometry 
    566542 
     
    568544    CASE(grid_ico) 
    569545       CALL set_geometry 
     546       ! copy position of generators and vertices back into domain_glo(:)%xyz/vertex 
     547       ! so that write_field gets the right values 
     548       CALL update_domain 
     549       CALL set_bounds(domain_glo, .TRUE.) 
     550       CALL set_bounds(domain, .FALSE.) 
    570551    CASE(grid_unst) 
    571552       swap_needed=.FALSE. 
Note: See TracChangeset for help on using the changeset viewer.