Skip to content

Commit 2249aef

Browse files
Add changes to the rebased branch
1 parent de282b4 commit 2249aef

File tree

1 file changed

+14
-29
lines changed

1 file changed

+14
-29
lines changed

model/src/w3oacpmd.F90

+14-29
Original file line numberDiff line numberDiff line change
@@ -368,6 +368,7 @@ SUBROUTINE CPL_OASIS_DEFINE(NDSO,RCV_STR,SND_STR)
368368
!/ (R. Baraille & J. Pianezze)
369369
!/ April-2016 : Add comments (J. Pianezze) ( version 5.07 )
370370
!/ 08-Jun-2018 : use INIT_GET_ISEA ( version 6.04 )
371+
!/ Feb-2025 : OASIS points partition (J.M. Castillo) ( version X.XX )
371372
!/
372373
! 1. Purpose :
373374
!
@@ -419,58 +420,41 @@ SUBROUTINE CPL_OASIS_DEFINE(NDSO,RCV_STR,SND_STR)
419420
!/ ------------------------------------------------------------------- /
420421
!/ Local parameters
421422
!/
422-
INTEGER :: IB_I,I
423+
INTEGER :: IB_I
423424
INTEGER :: IL_PART_ID ! PartitionID
424425
INTEGER, ALLOCATABLE, DIMENSION(:) :: ILA_PARAL ! Description of the local partition in the global index space
425426
INTEGER, DIMENSION(4) :: ILA_SHAPE ! Vector giving the min & max index for each dim of the fields
426427
INTEGER, DIMENSION(2) :: ILA_VAR_NODIMS ! rank of fields & number of bundles (1 with OASIS3-MCT)
427428
INTEGER :: ISEA, JSEA, IX, IY
428-
INTEGER :: NHXW, NHXE, NHYS, NHYN ! size of the halo at the western, eastern, southern, northern boundaries
429-
LOGICAL :: LL_MPI_FILE ! to check if there an mpi.txt file for domain decompasition
430429
!/
431430
!/ ------------------------------------------------------------------- /
432431
!/ Executable part
433432
!/
434433
!
434+
ALLOCATE(ILA_PARAL(2+NSEAL))
435+
!
436+
! * Define the partition : OASIS POINTS partition
437+
ILA_PARAL(1) = 4
438+
!
439+
! * total number of segments of the global domain
440+
ILA_PARAL(2) = NSEAL
441+
!
435442
IF (GTYPE .EQ. RLGTYPE .OR. GTYPE .EQ. CLGTYPE) THEN
436443
!
437444
! 1.1. regular and curvilinear grids
438445
! ----------------------------------
439-
NHXW = 1 ; NHXE = NX ; NHYS = 1 ; NHYN = NY
440-
NHXW = NHXW - 1
441-
NHXE = NX - NHXE
442-
NHYS = NHYS - 1
443-
NHYN = NY - NHYN
444-
!
445-
ALLOCATE(ILA_PARAL(2+NSEAL*2))
446-
!
447-
! * Define the partition : OASIS ORANGE partition
448-
ILA_PARAL(1) = 3
449-
!
450-
! * total number of segments of the global domain
451-
ILA_PARAL(2) = NSEAL
452-
!
453446
DO JSEA=1, NSEAL
454447
CALL INIT_GET_ISEA(ISEA,JSEA)
455448

456449
IX = MAPSF(ISEA,1)
457450
IY = MAPSF(ISEA,2)
458-
ILA_PARAL(JSEA*2+1) = (IY - NHYN -1)*(NX - NHXE - NHXW) + (IX - NHXW - 1)
459-
ILA_PARAL(JSEA*2+2) = 1
451+
ILA_PARAL(JSEA+2) = (IY - 1)*NX + IX
460452
END DO
461453
#ifdef W3_SMC
462454
ELSE IF( GTYPE .EQ. SMCTYPE ) THEN
463455
!
464456
! 1.2. SMC grids
465457
! ----------------------------------
466-
ALLOCATE(ILA_PARAL(2+NSEAL))
467-
!
468-
! * Define the partition : OASIS POINTS partition
469-
ILA_PARAL(1) = 4
470-
!
471-
! * total number of segments of the global domain
472-
ILA_PARAL(2) = NSEAL
473-
!
474458
DO JSEA=1, NSEAL
475459
ILA_PARAL(JSEA+2) = IAPROC + (JSEA-1)*NAPROC
476460
ENDDO
@@ -484,8 +468,7 @@ SUBROUTINE CPL_OASIS_DEFINE(NDSO,RCV_STR,SND_STR)
484468
STOP
485469
!
486470
DO JSEA=1,NSEAL
487-
ILA_PARAL(JSEA*2+1) = (IAPROC-1) + (JSEA-1)*NAPROC
488-
ILA_PARAL(JSEA*2+2) = 1
471+
ILA_PARAL(JSEA+2) = IAPROC + (JSEA-1)*NAPROC
489472
END DO
490473
!
491474
ENDIF
@@ -497,6 +480,8 @@ SUBROUTINE CPL_OASIS_DEFINE(NDSO,RCV_STR,SND_STR)
497480
CALL OASIS_ABORT(IL_COMPID, 'CPL_OASIS_DEFINE', 'Problem during oasis_def_partition')
498481
ENDIF
499482
!
483+
DEALLOCATE(ILA_PARAL)
484+
!
500485
! 3. Coupling fields declaration
501486
! ----------------------------------
502487
ILA_SHAPE(:) = (/1, NSEAL, 1, 1 /)

0 commit comments

Comments
 (0)