Changeset 3702 for trunk/LMDZ.MARS


Ignore:
Timestamp:
Mar 31, 2025, 6:04:59 PM (3 months ago)
Author:
emillour
Message:

Mars PCM:
Add reindexing of columns when reading/writing (re)startfi files. This is not
necessary with the lon-lat (LMDZ.COMMON) dynamical core, but required when
using DYNAMICO (where correspondance between dynamics and physics column
indexes changes with number of computing cores).
EM

Location:
trunk/LMDZ.MARS
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/changelog.txt

    r3681 r3702  
    47794779== 12/03/2025 == JBC
    47804780Small improvements for the python script to display variables in a NetCDF file.
     4781
     4782== 31/03/2025 == EM
     4783Add reindexing of columns when reading/writing (re)startfi files. This is not
     4784necessary with the lon-lat (LMDZ.COMMON) dynamical core, but required when
     4785using DYNAMICO (where correspondance between dynamics and physics column
     4786indexes changes with number of computing cores).
     4787
  • trunk/LMDZ.MARS/libf/phymars/iostart.F90

    r3509 r3702  
    2020    INTEGER,SAVE :: idim11 ! "description_size" dimension
    2121    INTEGER,SAVE :: timeindex ! current time index (for time-dependent fields)
     22! variables above need not be OMP threadprivate, as they are used by master only
     23
    2224    INTEGER,PARAMETER :: length = 100 ! size of tab_cntrl array
    2325    INTEGER,PARAMETER :: ldscrpt = 35 ! size of dscrpt_tab_cntrl array
     
    271273  SUBROUTINE Get_field_rgen(field_name,field,field_size, &
    272274                            corners,edges,found)
    273   USE netcdf
    274   USE dimphy
    275   USE mod_grid_phy_lmdz
    276   USE mod_phys_lmdz_para
    277   IMPLICIT NONE
    278     CHARACTER(LEN=*) :: Field_name
    279     INTEGER          :: field_size
    280     REAL             :: field(klon,field_size)
     275  USE netcdf, ONLY: NF90_INQ_VARID, NF90_GET_VAR, NF90_NOERR
     276  USE dimphy, ONLY: klon ! number of columns on local grid
     277  USE geometry_mod, ONLY: ind_cell_glo
     278  USE mod_grid_phy_lmdz, ONLY: klon_glo ! number of columns on global grid
     279  USE mod_phys_lmdz_para, ONLY: is_master, bcast, scatter, gather
     280  IMPLICIT NONE
     281    CHARACTER(LEN=*),INTENT(IN) :: Field_name
     282    INTEGER,INTENT(IN) :: field_size
     283    REAL,INTENT(OUT) :: field(klon,field_size)
    281284    INTEGER,INTENT(IN) :: corners(4)
    282285    INTEGER,INTENT(IN) :: edges(4)
    283     LOGICAL,OPTIONAL :: found
    284    
    285     REAL    :: field_glo(klon_glo,field_size)
     286    LOGICAL,OPTIONAL,INTENT(OUT) :: found
     287   
     288    REAL :: field_glo(klon_glo,field_size) ! field on global grid
     289    REAL :: field_glo_tmp(klon_glo,field_size)
     290    INTEGER :: ind_cell_glo_glo(klon_glo) ! cell indexes on global grid
    286291    LOGICAL :: tmp_found
    287292    INTEGER :: varid
    288     INTEGER :: ierr
    289    
     293    INTEGER :: ierr, i
     294   
     295    ! gather columns indexes on global grid
     296    CALL gather(ind_cell_glo,ind_cell_glo_glo)
     297     
    290298    IF (is_master) THEN
    291299 
     
    293301     
    294302      IF (ierr==NF90_NOERR) THEN
    295         CALL body(field_glo)
     303        CALL body(field_glo_tmp)
    296304        tmp_found=.TRUE.
    297305      ELSE
     
    299307      ENDIF
    300308   
    301     ENDIF
     309    ENDIF ! of IF (is_master)
    302310   
    303311    CALL bcast(tmp_found)
    304312
    305313    IF (tmp_found) THEN
     314      IF (is_master) THEN
     315        ! reorder columns according to ind_cell_glo(:) indexes
     316        DO i=1,klon_glo
     317          field_glo(i,:)=field_glo_tmp(ind_cell_glo_glo(i),:)
     318        ENDDO
     319      ENDIF
    306320      CALL scatter(field_glo,field)
    307321    ENDIF
     
    326340           PRINT*, 'get_field_rgen: Failed reading <'//field_name//'>'
    327341
    328 !           IF (field_name=='CLWCON' .OR. field_name=='RNEBCON' .OR. field_name=='RATQS') THEN
    329 !              ! Essaye de lire le variable sur surface uniqument, comme fait avant
    330 !              field_glo(:)=0.
    331 !              ierr=NF90_GET_VAR(nid_start,varid,field_glo(1:klon_glo))
    332 !              IF (ierr/=NF90_NOERR) THEN
    333 !                 PRINT*, 'phyetat0: Lecture echouee aussi en 2D pour <'//field_name//'>'
    334 !                 CALL abort
    335 !              ELSE
    336 !                 PRINT*, 'phyetat0: La variable <'//field_name//'> lu sur surface seulement'!, selon ancien format, le reste mis a zero'
    337 !              END IF
    338 !           ELSE
    339               CALL abort_physic("get_field_rgen","Failed to read field",1)
    340 !           ENDIF
     342           CALL abort_physic("get_field_rgen","Failed to read field",1)
    341343         ENDIF
    342344
     
    410412
    411413  SUBROUTINE Get_var_rgen(var_name,var,var_size,found)
    412   USE netcdf
    413   USE dimphy
    414   USE mod_grid_phy_lmdz
    415   USE mod_phys_lmdz_para
    416   IMPLICIT NONE
    417     CHARACTER(LEN=*) :: var_name
    418     INTEGER          :: var_size
    419     REAL             :: var(var_size)
    420     LOGICAL,OPTIONAL :: found
     414  USE netcdf, ONLY: NF90_INQ_VARID, NF90_GET_VAR, NF90_NOERR
     415  USE mod_phys_lmdz_para, ONLY: is_master, bcast
     416  IMPLICIT NONE
     417    CHARACTER(LEN=*),INTENT(IN) :: var_name
     418    INTEGER,INTENT(IN) :: var_size
     419    REAL,INTENT(OUT) :: var(var_size)
     420    LOGICAL,OPTIONAL,INTENT(OUT) :: found
    421421   
    422422    LOGICAL :: tmp_found
     
    424424    INTEGER :: ierr
    425425   
    426     IF (is_mpi_root .AND. is_omp_root) THEN
     426    IF (is_master) THEN
    427427 
    428428      ierr=NF90_INQ_VARID(nid_start,var_name,varid)
     
    669669 
    670670  SUBROUTINE put_field_rgen(field_name,title,field,field_size,time)
    671   USE netcdf
    672   USE dimphy
     671  USE netcdf, ONLY: NF90_REDEF, NF90_ENDDEF, NF90_DEF_VAR, NF90_PUT_ATT, &
     672                    NF90_INQ_VARID, NF90_PUT_VAR, NF90_STRERROR, &
     673                    NF90_NOERR, NF90_FLOAT, NF90_DOUBLE
     674  USE dimphy, ONLY: klon, klev, klevp1
    673675  USE comsoil_h, only: nsoilmx
    674676  USE comslope_mod, ONLY: nslope
    675   USE mod_grid_phy_lmdz
    676   USE mod_phys_lmdz_para
     677  USE mod_grid_phy_lmdz, ONLY: klon_glo
     678  USE mod_phys_lmdz_para, ONLY: is_master, gather
     679  USE geometry_mod, ONLY: ind_cell_glo
     680 
    677681  IMPLICIT NONE
    678682  CHARACTER(LEN=*),INTENT(IN)    :: field_name
     
    682686  REAL,OPTIONAL,INTENT(IN)       :: time
    683687 
    684   REAL                           :: field_glo(klon_glo,field_size)
    685   REAL                           :: field_glo_reshape(klon_glo,nsoilmx,nslope,timeindex)
     688  REAL :: field_glo(klon_glo,field_size)
     689  REAL :: field_glo_tmp(klon_glo,field_size)
     690  INTEGER :: ind_cell_glo_glo(klon_glo) ! cell indexes on global grid
     691  REAL :: field_glo_reshape(klon_glo,nsoilmx,nslope,timeindex)
    686692  INTEGER                        :: ierr
    687693  INTEGER                        :: nvarid
    688694  INTEGER                        :: idim
     695  INTEGER :: i
    689696   
    690     CALL gather(field,field_glo)
    691    
    692     IF (is_master) THEN
     697    ! gather indexes on global grid
     698    CALL gather(ind_cell_glo,ind_cell_glo_glo)
     699    ! gather field on master
     700    CALL gather(field,field_glo_tmp)
     701   
     702    IF (is_master) THEN
     703      ! reorder columns
     704      DO i=1,klon_glo
     705        field_glo(ind_cell_glo_glo(i),:)=field_glo_tmp(i,:)
     706      ENDDO
    693707
    694708      IF (field_size==1) THEN
Note: See TracChangeset for help on using the changeset viewer.