Skip to content

Commit

Permalink
Merge pull request #68 from SebastienRietteMTO/merge_49T2+
Browse files Browse the repository at this point in the history
Merge PR #55
  • Loading branch information
SebastienRietteMTO authored Feb 12, 2025
2 parents 13d0518 + 64053e2 commit 37782d5
Show file tree
Hide file tree
Showing 117 changed files with 42,780 additions and 21,635 deletions.
2 changes: 1 addition & 1 deletion docs/Tools.md
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ The check\_commit\_ial script compiles, executes IAL test cases and compare the

Script options can be displayed with the -h option.

Before being usable, the AROME model must be installed following the [tools/INSTALL\_pack\_ial.md file](../tools/INSTALL_pack\_ial.md).
Before being usable, some packages must be installed following the [tools/INSTALL.md file](../tools/INSTALL.md).

### check\_commit\_mesonh.sh

Expand Down
2 changes: 1 addition & 1 deletion src/arome/aux/mode_msg.F90
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ SUBROUTINE PRINT_MSG_1LINE(KVERB, HDOMAIN, HSUBR, HMSG)

CALL PRINT_MSG_MULTI(KVERB, HDOMAIN, HSUBR, [HMSG])

ENDSUBROUTINE PRINT_MSG_1LINE
END SUBROUTINE PRINT_MSG_1LINE

SUBROUTINE PRINT_MSG_MULTI_CMNHMSG(KVERB, HDOMAIN, HSUBR)
INTEGER, INTENT(IN) :: KVERB !Verbosity level
Expand Down
11 changes: 8 additions & 3 deletions src/arome/conv/convect_chem_transport.F90
Original file line number Diff line number Diff line change
Expand Up @@ -95,6 +95,7 @@ SUBROUTINE CONVECT_CHEM_TRANSPORT( CVPEXT, D, NSV, KCH, PCH1, PCH1C, &
INTEGER :: JI ! horizontal loop index
INTEGER :: JK, JKP ! vertical loop index
INTEGER :: JN ! chemical tracer loop index
INTEGER :: JCH
INTEGER :: JSTEP ! fractional time loop index
INTEGER :: JKLD, JKLP, JKMIN, JKMAX, JKMAX2 ! loop index for levels
!
Expand Down Expand Up @@ -212,7 +213,9 @@ SUBROUTINE CONVECT_CHEM_TRANSPORT( CVPEXT, D, NSV, KCH, PCH1, PCH1C, &
!* 4. Final closure (environmental) computations
! ------------------------------------------
!
PCH1C(D%NIB:D%NIE,IKB:IKE,1:KCH) = PCH1(D%NIB:D%NIE,IKB:IKE,1:KCH) ! initialize adjusted envir. values
DO JCH = 1, KCH
PCH1C(:,IKB:IKE,JCH) = PCH1(:,IKB:IKE,JCH) ! initialize adjusted envir. values
ENDDO
!
DO JK = IKB, IKE
DO JI=D%NIB,D%NIE
Expand All @@ -233,8 +236,10 @@ SUBROUTINE CONVECT_CHEM_TRANSPORT( CVPEXT, D, NSV, KCH, PCH1, PCH1C, &
ENDDO
ENDDO
!
ZCH1MFIN(D%NIB:D%NIE,1:D%NKT,1:KCH) = 0.
ZCH1MFOUT(D%NIB:D%NIE,1:D%NKT,1:KCH) = 0.
DO JCH = 1, KCH
ZCH1MFIN(:,1:D%NKT,JCH) = 0.
ZCH1MFOUT(:,1:D%NKT,JCH) = 0.
ENDDO
!
DO JSTEP = 1, KFTSTEPS ! Enter the fractional time step loop
!
Expand Down
26 changes: 19 additions & 7 deletions src/arome/conv/convect_closure.F90
Original file line number Diff line number Diff line change
Expand Up @@ -146,6 +146,7 @@ SUBROUTINE CONVECT_CLOSURE( KLON, KLEV, &
REAL, DIMENSION(KLON,KLEV), INTENT(INOUT):: PDTEVRF! downdraft evaporation rate
REAL, DIMENSION(KLON,KLEV), INTENT(OUT) :: PPRLFLX! liquid precip flux
REAL, DIMENSION(KLON,KLEV), INTENT(OUT) :: PPRSFLX! solid precip flux

!
!* 0.2 Declarations of local variables :
!
Expand All @@ -156,6 +157,7 @@ SUBROUTINE CONVECT_CLOSURE( KLON, KLEV, &
INTEGER :: JITER ! iteration loop index
INTEGER :: JSTEP ! fractional time loop index
REAL :: ZCPORD, ZRDOCP ! C_pd / R_d, R_d / C_pd
REAL :: ZEPS
!
REAL, DIMENSION(KLON,KLEV) :: ZTHLC ! convectively adjusted
! grid scale enthalpy
Expand Down Expand Up @@ -203,14 +205,15 @@ SUBROUTINE CONVECT_CLOSURE( KLON, KLEV, &
LOGICAL, DIMENSION(KLON) :: GWORK1, GWORK3! work arrays
LOGICAL, DIMENSION(KLON,KLEV) :: GWORK4 ! work array
!
REAL(KIND=JPHOOK) :: ZHOOK_HANDLE
!
#include "convect_closure_thrvlcl.h"
!-------------------------------------------------------------------------------
!
!* 0.2 Initialize local variables
! ----------------------------
!
!
REAL(KIND=JPHOOK) :: ZHOOK_HANDLE
IF (LHOOK) CALL DR_HOOK('CONVECT_CLOSURE',0,ZHOOK_HANDLE)
PSPR(:) = 0.
ZTIMC(:,:) = 0.
Expand All @@ -225,6 +228,7 @@ SUBROUTINE CONVECT_CLOSURE( KLON, KLEV, &
GWORK4(:,:) = .FALSE.
ILCL(:) = KLCL(:)
!
ZEPS = XRD / XRV
ZCPORD = XCPD / XRD
ZRDOCP = XRD / XCPD
!
Expand Down Expand Up @@ -545,10 +549,11 @@ SUBROUTINE CONVECT_CLOSURE( KLON, KLEV, &
! that in routine TRIGGER_FUNCT
! ---------------------------------------------
!
CALL CONVECT_CLOSURE_THRVLCL( KLON, KLEV, &
PPRES, PTHC, PRWC, PZ, GWORK1, &
ZTHLCL, ZRVLCL, ZZLCL, ZTLCL, ZTELCL, &
ILCL, KDPL, KPBL )
CALL ABOR1('FIXME: THE INTERFACE IS WRONG')
!CALL CONVECT_CLOSURE_THRVLCL( KLON, KLEV, &
!PPRES, PTHC, PRWC, PZ, GWORK1, &
!ZTHLCL, ZRVLCL, ZZLCL, ZTLCL, ZTELCL, &
!ILCL, KDPL, KPBL )
!
!
ZTLCL(:) = MAX( 230., MIN( 335., ZTLCL(:) ) ) ! set some overflow bounds
Expand All @@ -565,7 +570,9 @@ SUBROUTINE CONVECT_CLOSURE( KLON, KLEV, &
ZPI(:) = MAX( 0.95, MIN( 1.5, ZPI(:) ) )
ZWORK1(:) = XP00 / ZPI(:) ** ZCPORD ! pressure at LCL
!
CALL CONVECT_SATMIXRATIO( KLON, ZWORK1, ZTELCL, ZWORK3, ZLV, ZLS, ZCPH )
DO JI = 1, IIE
CALL CONVECT_SATMIXRATIO( ZWORK1(JI), ZTELCL(JI), ZEPS, ZWORK3(JI), ZLV(JI), ZLS(JI), ZCPH(JI) )
END DO
ZWORK3(:) = MIN( .1, MAX( 0., ZWORK3(:) ) )
!
! compute theta_e updraft undilute
Expand Down Expand Up @@ -593,7 +600,9 @@ SUBROUTINE CONVECT_CLOSURE( KLON, KLEV, &
ZWORK2(JI) = PTHC(JI,JK) / ZPI(JI)
END DO
!
CALL CONVECT_SATMIXRATIO( KLON, PPRES(:,JK), ZWORK2, ZWORK3, ZLV, ZLS, ZCPH )
DO JI = 1, IIE
CALL CONVECT_SATMIXRATIO( PPRES(JI,JK), ZWORK2(JI), ZEPS, ZWORK3(JI), ZLV(JI), ZLS(JI), ZCPH(JI) )
END DO
!
!
DO JI = 1, IIE
Expand Down Expand Up @@ -659,4 +668,7 @@ SUBROUTINE CONVECT_CLOSURE( KLON, KLEV, &
!
!
IF (LHOOK) CALL DR_HOOK('CONVECT_CLOSURE',1,ZHOOK_HANDLE)
CONTAINS
INCLUDE "convect_satmixratio.h"
!
END SUBROUTINE CONVECT_CLOSURE
14 changes: 7 additions & 7 deletions src/arome/conv/convect_closure_adjust_shal.F90
Original file line number Diff line number Diff line change
Expand Up @@ -93,13 +93,13 @@ SUBROUTINE CONVECT_CLOSURE_ADJUST_SHAL( CVPEXT, D, PADJ, &
! specified degree of stabilization
! ----------------------------------------------------
!
DO JK = IKB + 1, IKE
DO JI = D%NIB, D%NIE
PUMF(JI,JK) = PZUMF(JI,JK) * PADJ(JI)
PUER(JI,JK) = PZUER(JI,JK) * PADJ(JI)
PUDR(JI,JK) = PZUDR(JI,JK) * PADJ(JI)
ENDDO
END DO
DO JK = IKB + 1, IKE
DO JI = D%NIB, D%NIE
PUMF(JI,JK) = PZUMF(JI,JK) * PADJ(JI)
PUER(JI,JK) = PZUER(JI,JK) * PADJ(JI)
PUDR(JI,JK) = PZUDR(JI,JK) * PADJ(JI)
ENDDO
END DO
!
IF (LHOOK) CALL DR_HOOK('CONVECT_CLOSURE_ADJUST_SHAL',1,ZHOOK_HANDLE)
END SUBROUTINE CONVECT_CLOSURE_ADJUST_SHAL
Loading

0 comments on commit 37782d5

Please sign in to comment.