Skip to content
Snippets Groups Projects
Commit 15b3dbe1 authored by Gaelle DELAUTIER's avatar Gaelle DELAUTIER
Browse files

Gaelle 25/11/2016 : bug OASIS

parent 0389fc0e
No related branches found
No related tags found
No related merge requests found
...@@ -258,14 +258,15 @@ END MODULE MODI_INI_MODEL_n ...@@ -258,14 +258,15 @@ END MODULE MODI_INI_MODEL_n
!! June 2011 (P.Aumond) Drag of the vegetation !! June 2011 (P.Aumond) Drag of the vegetation
!! + Mean fields !! + Mean fields
!! July 2013 (Bosseur & Filippi) Adds Forefire !! July 2013 (Bosseur & Filippi) Adds Forefire
!! P. Tulet Nov 2014 accumulated moles of aqueous species that fall at the surface !! P. Tulet Nov 2014 accumulated moles of aqueous species that fall at the surface
!! JAn. 2015 (F. Brosse) bug in allocate XACPRAQ !! JAn. 2015 (F. Brosse) bug in allocate XACPRAQ
!! Dec 2014 (C.Lac) : For reproducibility START/RESTA !! Dec 2014 (C.Lac) : For reproducibility START/RESTA
!! J.Escobar : 15/09/2015 : WENO5 & JPHEXT <> 1 !! J.Escobar : 15/09/2015 : WENO5 & JPHEXT <> 1
!! V. Masson Feb 2015 replaces, for aerosols, cover fractions by sea, town, bare soil fractions !! V. Masson Feb 2015 replaces, for aerosols, cover fractions by sea, town, bare soil fractions
!! J.Escobar : 19/04/2016 : Pb IOZ/NETCDF , missing OPARALLELIO=.FALSE. for PGD files !! J.Escobar : 19/04/2016 : Pb IOZ/NETCDF , missing OPARALLELIO=.FALSE. for PGD files
!! Jun. 2016 (G.Delautier) phasage surfex 8 !! J.Escobar : 01/06/2016 : correct check limit of NRIM versus local subdomain size IDIM
!! Modification 01/2016 (JP Pinty) Add LIMA !! 06/2016 (G.Delautier) phasage surfex 8
!! Modification 01/2016 (JP Pinty) Add LIMA
!! Aug. 2016 (J.Pianezze) Add SFX_OASIS_READ_NAM function from SurfEx !! Aug. 2016 (J.Pianezze) Add SFX_OASIS_READ_NAM function from SurfEx
!! M.Leriche 2016 Chemistry !! M.Leriche 2016 Chemistry
!! 10/2016 M.Mazoyer New KHKO output fields !! 10/2016 M.Mazoyer New KHKO output fields
...@@ -504,6 +505,8 @@ REAL, DIMENSION(:,:,:), POINTER :: DPTR_XZZ ...@@ -504,6 +505,8 @@ REAL, DIMENSION(:,:,:), POINTER :: DPTR_XZZ
REAL, DIMENSION(:,:,:), POINTER :: DPTR_XLSUM,DPTR_XLSVM,DPTR_XLSWM,DPTR_XLSTHM,DPTR_XLSRVM REAL, DIMENSION(:,:,:), POINTER :: DPTR_XLSUM,DPTR_XLSVM,DPTR_XLSWM,DPTR_XLSTHM,DPTR_XLSRVM
REAL, DIMENSION(:,:,:), POINTER :: DPTR_XLSUS,DPTR_XLSVS,DPTR_XLSWS,DPTR_XLSTHS,DPTR_XLSRVS REAL, DIMENSION(:,:,:), POINTER :: DPTR_XLSUS,DPTR_XLSVS,DPTR_XLSWS,DPTR_XLSTHS,DPTR_XLSRVS
! !
INTEGER :: IIB,IJB,IIE,IJE,IDIMX,IDIMY
!
!------------------------------------------------------------------------------- !-------------------------------------------------------------------------------
! !
!* 0. PROLOGUE !* 0. PROLOGUE
...@@ -617,6 +620,10 @@ IJU_ll=NJMAX_ll + 2 * JPHEXT ...@@ -617,6 +620,10 @@ IJU_ll=NJMAX_ll + 2 * JPHEXT
! spawning,... ! spawning,...
CALL GET_DIM_PHYS_ll('B',NIMAX,NJMAX) CALL GET_DIM_PHYS_ll('B',NIMAX,NJMAX)
! !
CALL GET_INDICE_ll( IIB,IJB,IIE,IJE)
IDIMX = IIE - IIB + 1
IDIMY = IJE - IJB + 1
!
NRR=0 NRR=0
NRRL=0 NRRL=0
NRRI=0 NRRI=0
...@@ -1024,11 +1031,11 @@ ELSE ! 3D case ...@@ -1024,11 +1031,11 @@ ELSE ! 3D case
! check if local domain not to small for NRIMX NRIMY ! check if local domain not to small for NRIMX NRIMY
! !
IF ( CLBCX(1) /= 'CYCL' ) THEN IF ( CLBCX(1) /= 'CYCL' ) THEN
IF ( NRIMX+2*JPHEXT .GE. IIU ) THEN IF ( NRIMX .GT. IDIMX ) THEN
WRITE(*,'(A,I8,A/A,2I8,/A)') "Processor=", IP-1, & WRITE(*,'(A,I8,A/A,2I8,/A)') "Processor=", IP-1, &
" :: INI_MODEL_n ERROR: ( NRIMX+2*JPHEXT >= IIU ) ", & " :: INI_MODEL_n ERROR: ( NRIMX > IDIMX ) ", &
" Local domain to small for relaxation NRIMX+2*JPHEXT,IIU ", & " Local domain to small for relaxation NRIMX,IDIMX ", &
NRIMX+2*JPHEXT,IIU ,& NRIMX,IDIMX ,&
" change relaxation parameters or number of processors " " change relaxation parameters or number of processors "
!callabortstop !callabortstop
CALL ABORT CALL ABORT
...@@ -1036,11 +1043,11 @@ ELSE ! 3D case ...@@ -1036,11 +1043,11 @@ ELSE ! 3D case
END IF END IF
END IF END IF
IF ( CLBCY(1) /= 'CYCL' ) THEN IF ( CLBCY(1) /= 'CYCL' ) THEN
IF ( NRIMY+2*JPHEXT .GE. IJU ) THEN IF ( NRIMY .GT. IDIMY ) THEN
WRITE(*,'(A,I8,A/A,2I8,/A)') "Processor=", IP-1, & WRITE(*,'(A,I8,A/A,2I8,/A)') "Processor=", IP-1, &
" :: INI_MODEL_n ERROR: ( NRIMY+2*JPHEXT >= IJU ) ", & " :: INI_MODEL_n ERROR: ( NRIMY > IDIMY ) ", &
" Local domain to small for relaxation NRIMY+2*JPHEXT,IJU ", & " Local domain to small for relaxation NRIMY,IDIMY ", &
NRIMY+2*JPHEXT,IJU ,& NRIMY,IDIMY ,&
" change relaxation parameters or number of processors " " change relaxation parameters or number of processors "
!callabortstop !callabortstop
CALL ABORT CALL ABORT
......
...@@ -51,6 +51,7 @@ SUBROUTINE MNH_OASIS_DEFINE(HPROGRAM,IP) ...@@ -51,6 +51,7 @@ SUBROUTINE MNH_OASIS_DEFINE(HPROGRAM,IP)
!! MODIFICATIONS !! MODIFICATIONS
!! ------------- !! -------------
!! Original 09/2014 !! Original 09/2014
!! 11/2016 Correction WENO5
!------------------------------------------------------------------------------- !-------------------------------------------------------------------------------
! !
!* 0. DECLARATIONS !* 0. DECLARATIONS
...@@ -63,6 +64,9 @@ USE MOD_OASIS ...@@ -63,6 +64,9 @@ USE MOD_OASIS
USE MODD_MNH_SURFEX_n USE MODD_MNH_SURFEX_n
#endif #endif
! !
USE MODD_CONF, ONLY : NVERB
USE MODD_PARAMETERS, ONLY : JPHEXT
!
USE MODE_ll USE MODE_ll
! !
IMPLICIT NONE IMPLICIT NONE
...@@ -121,7 +125,16 @@ JI=2 ...@@ -121,7 +125,16 @@ JI=2
INPTS=0 INPTS=0
DO JSEG=1,ISEGMENT DO JSEG=1,ISEGMENT
JI=JI+1 JI=JI+1
IPARAL(JI) = (IIOR - 1) + NIMAX_ll*(IJOR -1) + NIMAX_ll*(JSEG-1) IF (LWEST_ll() .AND. LSOUTH_ll()) THEN
IPARAL(JI) = (IIOR - JPHEXT) + NIMAX_ll*(IJOR - JPHEXT) + NIMAX_ll*(JSEG - 1)
ELSE IF (LWEST_ll() .AND. .NOT. LSOUTH_ll()) THEN
IPARAL(JI) = (IIOR - JPHEXT) + NIMAX_ll*(IJOR + NHALO - 2*JPHEXT) + NIMAX_ll*(JSEG - 1)
ELSE IF (LSOUTH_ll() .AND. .NOT. LWEST_ll()) THEN
IPARAL(JI) = (IIOR + NHALO - 2*JPHEXT) + NIMAX_ll*(IJOR - JPHEXT) + NIMAX_ll*(JSEG - 1)
ELSE IF (.NOT. LSOUTH_ll() .AND. .NOT. LWEST_ll()) THEN
IPARAL(JI) = (IIOR + NHALO - 2*JPHEXT) + NIMAX_ll*(IJOR + NHALO - 2*JPHEXT) + NIMAX_ll*(JSEG - 1)
END IF
JI=JI+1 JI=JI+1
IPARAL(JI) = NIMAX IPARAL(JI) = NIMAX
ENDDO ENDDO
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment