| 1 | !! Diagnostics: Sea Level Pressure |
|---|
| 2 | |
|---|
| 3 | MODULE module_calc_slp |
|---|
| 4 | |
|---|
| 5 | CONTAINS |
|---|
| 6 | SUBROUTINE calc_slp(SCR, cname, cdesc, cunits) |
|---|
| 7 | |
|---|
| 8 | USE constants_module |
|---|
| 9 | USE module_model_basics |
|---|
| 10 | |
|---|
| 11 | !Arguments |
|---|
| 12 | real, pointer, dimension(:,:,:) :: SCR |
|---|
| 13 | character (len=128) :: cname, cdesc, cunits |
|---|
| 14 | |
|---|
| 15 | !Local |
|---|
| 16 | real, dimension(west_east_dim,south_north_dim,bottom_top_dim) :: temp, p_tmp, z |
|---|
| 17 | integer, dimension(west_east_dim,south_north_dim) :: level |
|---|
| 18 | real, dimension(west_east_dim,south_north_dim) :: slp |
|---|
| 19 | real, dimension(west_east_dim,south_north_dim) :: t_surf, t_sea_level |
|---|
| 20 | |
|---|
| 21 | real, parameter :: TC=273.16+17.5 |
|---|
| 22 | real, parameter :: PCONST = 10000. |
|---|
| 23 | logical, parameter :: traditional_comp = .TRUE. |
|---|
| 24 | |
|---|
| 25 | integer :: i, j, k |
|---|
| 26 | integer :: klo, khi |
|---|
| 27 | real :: plo, phi, tlo, thi, zlo, zhi |
|---|
| 28 | real :: p_at_pconst, t_at_pconst, z_at_pconst |
|---|
| 29 | real :: z_half_lowest |
|---|
| 30 | logical :: l1, l2, l3, found |
|---|
| 31 | |
|---|
| 32 | |
|---|
| 33 | |
|---|
| 34 | p_tmp = PRES ! Pressure in Pa |
|---|
| 35 | z = (PH+PHB)/G |
|---|
| 36 | temp = TK ! Temp in K |
|---|
| 37 | |
|---|
| 38 | |
|---|
| 39 | ! Find least zeta level that is PCONST Pa above the surface. We later use this |
|---|
| 40 | ! level to extrapolate a surface pressure and temperature, which is supposed |
|---|
| 41 | ! to reduce the effect of the diurnal heating cycle in the pressure field. |
|---|
| 42 | |
|---|
| 43 | DO j = 1 , south_north_dim |
|---|
| 44 | DO i = 1 , west_east_dim |
|---|
| 45 | |
|---|
| 46 | level(i,j) = -1 |
|---|
| 47 | k = 1 |
|---|
| 48 | found = .FALSE. |
|---|
| 49 | DO WHILE( (.not. found) .and. (k.le.bottom_top_dim) ) |
|---|
| 50 | IF ( p_tmp(i,j,k) .LT. p_tmp(i,j,1)-PCONST ) THEN |
|---|
| 51 | level(i,j) = k |
|---|
| 52 | found = .TRUE. |
|---|
| 53 | END IF |
|---|
| 54 | k = k+1 |
|---|
| 55 | END DO |
|---|
| 56 | |
|---|
| 57 | IF ( level(i,j) .EQ. -1 ) THEN |
|---|
| 58 | PRINT '(A,I4,A)','Troubles finding level ', & |
|---|
| 59 | NINT(PCONST)/100,' above ground.' |
|---|
| 60 | PRINT '(A,I4,A,I4,A)', & |
|---|
| 61 | 'Problems first occur at (',i,',',j,')' |
|---|
| 62 | PRINT '(A,F6.1,A)', & |
|---|
| 63 | 'Surface pressure = ',p_tmp(i,j,1)/100,' hPa.' |
|---|
| 64 | STOP 'Error_in_finding_100_hPa_up' |
|---|
| 65 | END IF |
|---|
| 66 | |
|---|
| 67 | END DO |
|---|
| 68 | END DO |
|---|
| 69 | |
|---|
| 70 | |
|---|
| 71 | ! Get temperature PCONST Pa above surface. Use this to extrapolate |
|---|
| 72 | ! the temperature at the surface and down to sea level. |
|---|
| 73 | |
|---|
| 74 | DO j = 1 , south_north_dim |
|---|
| 75 | DO i = 1 , west_east_dim |
|---|
| 76 | |
|---|
| 77 | klo = MAX ( level(i,j) - 1 , 1 ) |
|---|
| 78 | khi = MIN ( klo + 1 , bottom_top_dim - 1 ) |
|---|
| 79 | |
|---|
| 80 | IF ( klo .EQ. khi ) THEN |
|---|
| 81 | PRINT '(A)','Trapping levels are weird.' |
|---|
| 82 | PRINT '(A,I3,A,I3,A)','klo = ',klo,', khi = ',khi, & |
|---|
| 83 | ': and they should not be equal.' |
|---|
| 84 | STOP 'Error_trapping_levels' |
|---|
| 85 | END IF |
|---|
| 86 | |
|---|
| 87 | plo = p_tmp(i,j,klo) |
|---|
| 88 | phi = p_tmp(i,j,khi) |
|---|
| 89 | tlo = temp(i,j,klo)*(1. + 0.608 * qv(i,j,klo) ) |
|---|
| 90 | thi = temp(i,j,khi)*(1. + 0.608 * qv(i,j,khi) ) |
|---|
| 91 | zlo = z(i,j,klo) |
|---|
| 92 | zhi = z(i,j,khi) |
|---|
| 93 | |
|---|
| 94 | p_at_pconst = p_tmp(i,j,1) - pconst |
|---|
| 95 | t_at_pconst = thi-(thi-tlo)*LOG(p_at_pconst/phi)*LOG(plo/phi) |
|---|
| 96 | z_at_pconst = zhi-(zhi-zlo)*LOG(p_at_pconst/phi)*LOG(plo/phi) |
|---|
| 97 | |
|---|
| 98 | t_surf(i,j) = t_at_pconst*(p_tmp(i,j,1)/p_at_pconst)**(GAMMA*Rd/G) |
|---|
| 99 | t_sea_level(i,j) = t_at_pconst+GAMMA*z_at_pconst |
|---|
| 100 | |
|---|
| 101 | END DO |
|---|
| 102 | END DO |
|---|
| 103 | |
|---|
| 104 | |
|---|
| 105 | ! If we follow a traditional computation, there is a correction to the sea level |
|---|
| 106 | ! temperature if both the surface and sea level temperatures are *too* hot. |
|---|
| 107 | |
|---|
| 108 | IF ( traditional_comp ) THEN |
|---|
| 109 | DO j = 1 , south_north_dim |
|---|
| 110 | DO i = 1 , west_east_dim |
|---|
| 111 | l1 = t_sea_level(i,j) .LT. TC |
|---|
| 112 | l2 = t_surf (i,j) .LE. TC |
|---|
| 113 | l3 = .NOT. l1 |
|---|
| 114 | IF ( l2 .AND. l3 ) THEN |
|---|
| 115 | t_sea_level(i,j) = TC |
|---|
| 116 | ELSE |
|---|
| 117 | t_sea_level(i,j) = TC - 0.005*(t_surf(i,j)-TC)**2 |
|---|
| 118 | END IF |
|---|
| 119 | END DO |
|---|
| 120 | END DO |
|---|
| 121 | END IF |
|---|
| 122 | |
|---|
| 123 | |
|---|
| 124 | ! The grand finale |
|---|
| 125 | |
|---|
| 126 | DO j = 1 , south_north_dim |
|---|
| 127 | DO i = 1 , west_east_dim |
|---|
| 128 | z_half_lowest=z(i,j,1) |
|---|
| 129 | slp(i,j) = p_tmp(i,j,1) * & |
|---|
| 130 | EXP((2.*G*z_half_lowest)/ & |
|---|
| 131 | (Rd*(t_sea_level(i,j)+t_surf(i,j)))) |
|---|
| 132 | slp(i,j) = slp(i,j)*0.01 |
|---|
| 133 | |
|---|
| 134 | END DO |
|---|
| 135 | END DO |
|---|
| 136 | |
|---|
| 137 | |
|---|
| 138 | SCR(:,:,1) = slp(:,:) |
|---|
| 139 | cname = "slp" |
|---|
| 140 | cdesc = "Sea Levelp Pressure" |
|---|
| 141 | cunits = "hPa" |
|---|
| 142 | |
|---|
| 143 | END SUBROUTINE calc_slp |
|---|
| 144 | |
|---|
| 145 | END MODULE module_calc_slp |
|---|
| 146 | |
|---|