UPP  11.0.0
 All Data Structures Files Functions Variables Pages
CALLCL.f
Go to the documentation of this file.
1 
31 !-----------------------------------------------------------------------
40 !-----------------------------------------------------------------------
41  SUBROUTINE callcl(P1D,T1D,Q1D,PLCL,ZLCL)
42 
43 !
44 !
45  use vrbls3d, only: alpint, zint
46  use vrbls2d, only: fis
47  use masks, only: lmh
48  use params_mod, only: eps, oneps, d01, h1m12, gi, d00
49  use ctlblk_mod, only: jsta, jend, spval, jsta_m, jend_m, im, &
50  ista, iend, ista_m, iend_m
51 !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
52  implicit none
53 !
54  real,PARAMETER :: d35=3.5, d4805=4.805, h2840=2840.
55  real,PARAMETER :: h55=55., d2845=0.2845, d28=0.28
56 !
57 ! DECLARE VARIABLES.
58 !
59  REAL,dimension(ista:iend,jsta:jend), intent(in) :: p1d,t1d,q1d
60  REAL,dimension(ista:iend,jsta:jend), intent(inout) :: plcl,zlcl
61  REAL tlcl(ista:iend,jsta:jend)
62  integer i,j,l,llmh
63  real dlplcl,zsfc,dz,dalp,alplcl,rmx,evp,arg,rkapa
64 !
65 !**********************************************************************
66 ! START CALLCL HERE.
67 !
68 ! LOAD OUTPUT ARRAYS WITH SPECIAL VALUE.
69 !
70 !$omp parallel do private(i,j)
71  DO j=jsta,jend
72  DO i=ista,iend
73  plcl(i,j) = spval
74  tlcl(i,j) = spval
75  zlcl(i,j) = spval
76  ENDDO
77  ENDDO
78 !
79 ! COMPUTE PRESSURE, TEMPERATURE AND AGL HEIGHT AT LCL.
80 !
81 ! Bo Cui 10/30/2019, remove "GOTO" statement
82 
83  DO 30 j=jsta_m,jend_m
84  DO 30 i=ista_m,iend_m
85  IF(p1d(i,j)<spval.and.q1d(i,j)<spval)THEN
86  evp = p1d(i,j)*q1d(i,j)/(eps+oneps*q1d(i,j))
87  rmx = eps*evp/(p1d(i,j)-evp)
88  rkapa = 1.0 / (d2845*(1.0-d28*rmx))
89  arg = max(h1m12,evp*d01)
90  tlcl(i,j) = h55 + h2840 / (d35*log(t1d(i,j))-log(arg)-d4805)
91  plcl(i,j) = p1d(i,j)*(tlcl(i,j)/t1d(i,j))**rkapa
92  alplcl = log(plcl(i,j))
93  llmh = nint(lmh(i,j))
94  zsfc = fis(i,j)*gi
95 !
96  DO 20 l=llmh,1,-1
97  IF(alpint(i,j,l) < alplcl)THEN
98  dlplcl = alplcl - alpint(i,j,l+1)
99  dalp = alpint(i,j,l) - alpint(i,j,l+1)
100  dz = zint(i,j,l) - zint(i,j,l+1)
101  zlcl(i,j) = max(d00, zint(i,j,l+1) + dz*dlplcl/dalp - zsfc)
102  EXIT
103  ENDIF
104  20 CONTINUE
105  ENDIF
106  30 CONTINUE
107 !
108 ! END OF ROUTINE.
109 !
110  RETURN
111  END
Definition: MASKS_mod.f:1
subroutine callcl(P1D, T1D, Q1D, PLCL, ZLCL)
Subroutine that computes the lifting condensation level (LCL) height (above ground level) and pressur...
Definition: CALLCL.f:41