Ignore:
Timestamp:
05/09/19 01:37:55 (5 years ago)
Author:
dubos
Message:

devel : split read_dump_partition into open_local_mesh_file and read_local_mesh

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/unstructured/init_unstructured.f90

    r856 r863  
    22  USE mpipara, ONLY : is_mpi_master 
    33  USE data_unstructured_mod 
     4  USE geometry, ONLY : de 
    45  IMPLICIT NONE 
    56  SAVE 
     
    1011  INTEGER, ALLOCATABLE :: Idata_read1(:),Idata_read2(:,:),Idata_read3(:,:,:) 
    1112 
    12   PUBLIC :: read_dump_partition 
     13  CHARACTER(LEN=*),PARAMETER :: meshfile="input/mesh_information.nc" 
     14  INTEGER :: id_nc ! NetCDF id of mesh file open by open_local_mesh_file 
     15 
     16  PUBLIC :: open_local_mesh_file, read_local_mesh 
    1317 
    1418CONTAINS 
     
    9296 
    9397 
    94   SUBROUTINE read_dump_partition 
    95     use netcdf_mod 
    96     USE ioipsl 
    97     USE field_mod 
    98     USE geometry, ONLY : lon_i, lat_i, lon_e, lat_e, ep_e 
    99     IMPLICIT NONE 
    100  
    101     !!-------------Declare local variables------------------- 
    102     CHARACTER(LEN=*),PARAMETER :: f="input/mesh_information.nc" 
    103     INTEGER :: id_nc, ierr, status, descriptionLength, ij 
     98  SUBROUTINE open_local_mesh_file 
     99    USE netcdf_mod 
    104100    CHARACTER(LEN= 80) :: description 
    105     REAL(rstd), ALLOCATABLE :: angle_e(:) 
    106     REAL(rstd) :: clon, slon, clat, slat, & ! COS/SIN of lon/lat 
    107          elon(3), elat(3) ! lon/lat unit vectors 
    108     print *,"------------------ READING FILE " , f, "----------------------- " 
     101    INTEGER :: ierr, status, descriptionLength 
     102 
     103    PRINT *,"------------------ READING FILE " , meshfile, "----------------------- " 
    109104    !open and read the input file 
    110     ierr = nf90_open(f, NF90_NOWRITE, id_nc) 
     105    ierr = nf90_open(meshfile, NF90_NOWRITE, id_nc) 
    111106    if (ierr /= nf90_noerr) then 
    112107      print *, trim(nf90_strerror(ierr)) 
     
    114109    end if 
    115110 
    116     status = nf90_inquire_attribute(id_nc, nf90_global, "description", len =descriptionLength) 
     111    status = nf90_inquire_attribute(id_nc, nf90_global, "description", len=descriptionLength) 
    117112    IF(status /= 0 .or. len(description) < descriptionLength) THEN 
    118113        print *, "Not enough space to put NetCDF attribute values." 
     
    124119    print *,"Data file description :",description 
    125120 
     121    CALL read_from_gridfile(id_nc, 'integer', 'primal_deg') 
     122    primal_num = SIZE(Idata_read1) 
     123    CALL read_from_gridfile(id_nc, 'integer', 'dual_deg') 
     124    dual_num = SIZE(Idata_read1) 
     125    CALL read_from_gridfile(id_nc, 'integer', 'trisk_deg') 
     126    edge_num = SIZE(Idata_read1) 
     127  END SUBROUTINE open_local_mesh_file 
     128 
     129 
     130  SUBROUTINE read_local_mesh 
     131    USE field_mod 
     132    USE geometry, ONLY : lon_i, lat_i, lon_e, lat_e, ep_e 
     133    IMPLICIT NONE 
     134    INTEGER :: ij 
     135    REAL(rstd), ALLOCATABLE :: angle_e(:) 
     136    REAL(rstd) :: clon, slon, clat, slat, & ! COS/SIN of lon/lat 
     137         elon(3), elat(3) ! lon/lat unit vectors 
     138     
    126139    !status = nf90_get_att(id_nc, nf90_global, "primal_num", primal_num) 
    127140    !status = nf90_get_att(id_nc, nf90_global, "dual_num", dual_num) 
     
    161174    CALL read_from_gridfile(id_nc, 'float', 'le_de') 
    162175    ALLOCATE(le_de, source = Ddata_read1) 
     176    CALL read_from_gridfile(id_nc, 'float', 'le') 
     177    ALLOCATE(le, source = Ddata_read1) 
     178    CALL read_from_gridfile(id_nc, 'float', 'de') 
     179    ALLOCATE(de, source = Ddata_read1) 
    163180    CALL read_from_gridfile(id_nc, 'float', 'Riv2') 
    164181    ALLOCATE(Riv2, source = Ddata_read2) 
     
    204221     
    205222    DEALLOCATE(angle_e) 
    206   END SUBROUTINE read_dump_partition 
    207  
    208   SUBROUTINE init_grid_type 
    209     USE grid_param, ONLY : grid_type, grid_unst, grid_ico    
    210     USE getin_mod, ONLY : getin 
    211     CHARACTER(len=255) :: grid_type_var 
    212     grid_type_var='icosahedral' 
    213     CALL getin("grid_type",grid_type_var) 
    214     SELECT CASE(grid_type_var) 
    215     CASE('unstructured') 
    216        grid_type = grid_unst 
    217 !       is_omp_level_master=.TRUE. 
    218 !       omp_level_size=1 
    219        CALL read_dump_partition 
    220        IF (is_mpi_master) PRINT *,'Using unstructured grid type' 
    221     CASE DEFAULT 
    222        grid_type = grid_ico 
    223        IF (is_mpi_master) PRINT *,'Using default grid type' 
    224     END SELECT   
    225   END SUBROUTINE init_grid_type 
     223  END SUBROUTINE read_local_mesh 
    226224 
    227225END MODULE init_unstructured_mod 
Note: See TracChangeset for help on using the changeset viewer.