UPP  001
 All Data Structures Files Functions Pages
WETFRZLVL.f
Go to the documentation of this file.
1 
5 
30  SUBROUTINE wetfrzlvl(TWET,ZWET)
31 
32 !
33 !
34  use vrbls3d, only: pint, zint, t
35  use vrbls2d, only: fis, thz0, ths
36  use masks, only: lmh, sm
37  use params_mod, only: gi, p1000, capa, tfrz, d0065, d50
38  use ctlblk_mod, only: jsta, jend, im, jsta_2l, jend_2u, lm, spval
39 !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
40  implicit none
41 !
42 ! DECLARE VARIABLES.
43 !
44  REAL,intent(in) :: twet(im,jsta_2l:jend_2u,lm)
45  REAL,intent(out) :: zwet(im,jsta:jend)
46 !
47  integer i,j,llmh,l
48  real htsfc,thsfc,psfc,tsfc,delz,delt,zl,zu
49 !*********************************************************************
50 ! START FRZLVL.
51 !
52 ! LOOP OVER HORIZONTAL GRID.
53 !
54 !!$omp parallel do
55 !!$omp& private(delt,delz,htsfc,l,llmh
56 !!$omp& tsfc,zl,zu)
57  DO j=jsta,jend
58  DO i=1,im
59  IF(fis(i,j)==spval)THEN
60  zwet(i,j)=spval
61  cycle
62  ENDIF
63  htsfc = fis(i,j)*gi
64  llmh = nint(lmh(i,j))
65  zwet(i,j) = htsfc
66 !
67 ! CHECK IF FREEZING LEVEL IS AT THE GROUND.
68 ! IF YES, ESTIMATE UNDERGROUND FREEZING LEVEL USING 6.5C/KM LAPSE RATE
69 ! AND ASSUME RH TO BE EQUAL TO RH AT SFC
70 !
71  thsfc = (sm(i,j)*thz0(i,j)+(1.-sm(i,j))*ths(i,j))
72  psfc = pint(i,j,llmh+1)
73  tsfc = thsfc*(psfc/p1000)**capa
74 
75  IF (tsfc<=tfrz) THEN
76 ! ZWET(I,J) = HTSFC
77  zwet(i,j) = htsfc+(tsfc-tfrz)/d0065
78  cycle
79  ENDIF
80 !
81 ! OTHERWISE, LOCATE THE FREEZING LEVEL ALOFT.
82 !
83  loopl:DO l = llmh,1,-1
84  IF (twet(i,j,l)<=tfrz) THEN
85  IF (l<llmh-1) THEN
86  delz = d50*(zint(i,j,l)-zint(i,j,l+2))
87  zl = d50*(zint(i,j,l+1)+zint(i,j,l+2))
88  delt = twet(i,j,l)-twet(i,j,l+1)
89  zwet(i,j) = zl + (tfrz-twet(i,j,l+1))/delt*delz
90  ELSE
91  zu = d50*(zint(i,j,l)+zint(i,j,l+1))
92  zl = htsfc
93  delz = zu-zl
94  tsfc = sm(i,j)*thz0(i,j)+(1.-sm(i,j))*ths(i,j) &
95  *(pint(i,j,nint(lmh(i,j))+1)/p1000)**capa
96  delt = t(i,j,l)-tsfc
97  IF(delt /= 0.)THEN
98  zwet(i,j) = zl + (tfrz-tsfc)/delt*delz
99  ELSE
100  zwet(i,j) = htsfc+(tsfc-twet(i,j,l))/d0065
101  END IF
102  IF (zwet(i,j) > zu) THEN
103  zwet(i,j)=zu
104  ENDIF
105  IF ((-1*zwet(i,j)) > zu) THEN
106  zwet(i,j)=zu
107  endif
108  ENDIF
109  EXIT loopl
110  ENDIF
111  ENDDO loopl
112 
113  ENDDO !end I
114  ENDDO !end J
115 !
116 ! END OF ROUTINE.
117 !
118  RETURN
119  END
Definition: MASKS_mod.f:1