| 1 | MODULE etat0_mod |
|---|
| 2 | USE icosa |
|---|
| 3 | PRIVATE |
|---|
| 4 | |
|---|
| 5 | CHARACTER(len=255),SAVE :: etat0_type |
|---|
| 6 | !$OMP THREADPRIVATE(etat0_type) |
|---|
| 7 | |
|---|
| 8 | REAL(rstd) :: etat0_temp |
|---|
| 9 | |
|---|
| 10 | PUBLIC :: etat0, init_etat0, etat0_type |
|---|
| 11 | |
|---|
| 12 | CONTAINS |
|---|
| 13 | |
|---|
| 14 | SUBROUTINE Init_etat0 |
|---|
| 15 | USE etat0_database_mod |
|---|
| 16 | IMPLICIT NONE |
|---|
| 17 | |
|---|
| 18 | CALL getin("etat0",etat0_type) |
|---|
| 19 | |
|---|
| 20 | SELECT CASE (TRIM(etat0_type)) |
|---|
| 21 | CASE ('isothermal') |
|---|
| 22 | CASE ('temperature_profile') |
|---|
| 23 | CASE ('jablonowsky06') |
|---|
| 24 | CASE ('dcmip5') |
|---|
| 25 | CASE ('williamson91.6') |
|---|
| 26 | CASE ('start_file') |
|---|
| 27 | CASE ('database') |
|---|
| 28 | CALL init_etat0_database |
|---|
| 29 | CASE ('academic') |
|---|
| 30 | CASE ('held_suarez') |
|---|
| 31 | CASE ('venus') |
|---|
| 32 | CASE ('dcmip1') |
|---|
| 33 | CASE ('dcmip2_mountain','dcmip2_schaer_noshear','dcmip2_schaer_shear') |
|---|
| 34 | CASE ('dcmip3') |
|---|
| 35 | CASE ('dcmip4') |
|---|
| 36 | CASE DEFAULT |
|---|
| 37 | PRINT*, 'Bad selector for variable etat0 <',etat0_type, & |
|---|
| 38 | '> options are <jablonowsky06>, <academic>, <dcmip[1-4]> ' |
|---|
| 39 | STOP |
|---|
| 40 | END SELECT |
|---|
| 41 | |
|---|
| 42 | END SUBROUTINE Init_etat0 |
|---|
| 43 | |
|---|
| 44 | SUBROUTINE etat0(f_ps,f_mass,f_phis,f_theta_rhodz,f_u, f_q) |
|---|
| 45 | USE mpipara, ONLY : is_mpi_root |
|---|
| 46 | USE disvert_mod |
|---|
| 47 | ! New interface |
|---|
| 48 | USE etat0_dcmip5_mod, ONLY : getin_etat0_dcmip5=>getin_etat0 |
|---|
| 49 | USE etat0_williamson_mod, ONLY : getin_etat0_williamson=>getin_etat0 |
|---|
| 50 | USE etat0_temperature_mod, ONLY: getin_etat0_temperature=>getin_etat0 |
|---|
| 51 | ! Old interface |
|---|
| 52 | USE etat0_academic_mod, ONLY : etat0_academic=>etat0 |
|---|
| 53 | USE etat0_dcmip1_mod, ONLY : etat0_dcmip1=>etat0 |
|---|
| 54 | USE etat0_dcmip2_mod, ONLY : etat0_dcmip2=>etat0 |
|---|
| 55 | USE etat0_dcmip3_mod, ONLY : etat0_dcmip3=>etat0 |
|---|
| 56 | USE etat0_dcmip4_mod, ONLY : etat0_dcmip4=>etat0 |
|---|
| 57 | USE etat0_heldsz_mod, ONLY : etat0_heldsz=>etat0 |
|---|
| 58 | USE etat0_venus_mod, ONLY : etat0_venus=>etat0 |
|---|
| 59 | USE etat0_start_file_mod, ONLY : etat0_start_file=>etat0 |
|---|
| 60 | USE etat0_database_mod, ONLY : etat0_database=>etat0 |
|---|
| 61 | |
|---|
| 62 | IMPLICIT NONE |
|---|
| 63 | TYPE(t_field),POINTER :: f_ps(:) |
|---|
| 64 | TYPE(t_field),POINTER :: f_mass(:) |
|---|
| 65 | TYPE(t_field),POINTER :: f_phis(:) |
|---|
| 66 | TYPE(t_field),POINTER :: f_theta_rhodz(:) |
|---|
| 67 | TYPE(t_field),POINTER :: f_u(:) |
|---|
| 68 | TYPE(t_field),POINTER :: f_q(:) |
|---|
| 69 | |
|---|
| 70 | REAL(rstd),POINTER :: ps(:), mass(:,:) |
|---|
| 71 | LOGICAL :: init_mass |
|---|
| 72 | INTEGER :: ind,i,j,ij,l |
|---|
| 73 | |
|---|
| 74 | ! most etat0 routines set ps and not mass |
|---|
| 75 | ! in that case and if caldyn_eta == eta_lag |
|---|
| 76 | ! the initial distribution of mass is taken to be the same |
|---|
| 77 | ! as what the mass coordinate would dictate |
|---|
| 78 | ! however if etat0_XXX defines mass then the flag init_mass must be set to .FALSE. |
|---|
| 79 | ! otherwise mass will be overwritten |
|---|
| 80 | init_mass = (caldyn_eta == eta_lag) |
|---|
| 81 | |
|---|
| 82 | etat0_type='jablonowsky06' |
|---|
| 83 | CALL getin("etat0",etat0_type) |
|---|
| 84 | |
|---|
| 85 | SELECT CASE (TRIM(etat0_type)) |
|---|
| 86 | !------------------- New interface --------------------- |
|---|
| 87 | CASE ('isothermal') |
|---|
| 88 | CALL getin_etat0_isothermal |
|---|
| 89 | CALL etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_q) |
|---|
| 90 | CASE ('temperature_profile') |
|---|
| 91 | CALL getin_etat0_temperature |
|---|
| 92 | CALL etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_q) |
|---|
| 93 | CASE ('jablonowsky06') |
|---|
| 94 | CALL etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_q) |
|---|
| 95 | CASE ('dcmip5') |
|---|
| 96 | CALL getin_etat0_dcmip5 |
|---|
| 97 | CALL etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_q) |
|---|
| 98 | CASE ('williamson91.6') |
|---|
| 99 | init_mass=.FALSE. |
|---|
| 100 | CALL getin_etat0_williamson |
|---|
| 101 | CALL etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_q) |
|---|
| 102 | !------------------- Old interface -------------------- |
|---|
| 103 | CASE ('start_file') |
|---|
| 104 | CALL etat0_start_file(f_ps,f_phis,f_theta_rhodz,f_u, f_q) |
|---|
| 105 | CASE ('database') |
|---|
| 106 | CALL etat0_database(f_ps,f_phis,f_theta_rhodz,f_u, f_q) |
|---|
| 107 | CASE ('academic') |
|---|
| 108 | CALL etat0_academic(f_ps,f_phis,f_theta_rhodz,f_u, f_q) |
|---|
| 109 | CASE ('held_suarez') |
|---|
| 110 | PRINT *,"Held & Suarez (1994) test case" |
|---|
| 111 | CALL etat0_heldsz(f_ps,f_phis,f_theta_rhodz,f_u, f_q) |
|---|
| 112 | CASE ('venus') |
|---|
| 113 | CALL etat0_venus(f_ps, f_phis, f_theta_rhodz, f_u, f_q) |
|---|
| 114 | PRINT *, "Venus (Lebonnois et al., 2012) test case" |
|---|
| 115 | CASE ('dcmip1') |
|---|
| 116 | CALL etat0_dcmip1(f_ps,f_phis,f_theta_rhodz,f_u, f_q) |
|---|
| 117 | CASE ('dcmip2_mountain','dcmip2_schaer_noshear','dcmip2_schaer_shear') |
|---|
| 118 | CALL etat0_dcmip2(f_ps,f_phis,f_theta_rhodz,f_u, f_q) |
|---|
| 119 | CASE ('dcmip3') |
|---|
| 120 | CALL etat0_dcmip3(f_ps,f_phis,f_theta_rhodz,f_u, f_q) |
|---|
| 121 | CASE ('dcmip4') |
|---|
| 122 | IF(nqtot<2) THEN |
|---|
| 123 | IF (is_mpi_root) THEN |
|---|
| 124 | PRINT *, "nqtot must be at least 2 for test case DCMIP4" |
|---|
| 125 | END IF |
|---|
| 126 | STOP |
|---|
| 127 | END IF |
|---|
| 128 | CALL etat0_dcmip4(f_ps,f_phis,f_theta_rhodz,f_u, f_q) |
|---|
| 129 | CASE DEFAULT |
|---|
| 130 | PRINT*, 'Bad selector for variable etat0 <',etat0_type, & |
|---|
| 131 | '> options are <jablonowsky06>, <academic>, <dcmip[1-4]> ' |
|---|
| 132 | STOP |
|---|
| 133 | END SELECT |
|---|
| 134 | |
|---|
| 135 | IF(init_mass) THEN ! initialize mass distribution using ps |
|---|
| 136 | ! !$OMP BARRIER |
|---|
| 137 | DO ind=1,ndomain |
|---|
| 138 | IF (.NOT. assigned_domain(ind)) CYCLE |
|---|
| 139 | CALL swap_dimensions(ind) |
|---|
| 140 | CALL swap_geometry(ind) |
|---|
| 141 | mass=f_mass(ind); ps=f_ps(ind) |
|---|
| 142 | CALL compute_rhodz(.TRUE., ps, mass) |
|---|
| 143 | END DO |
|---|
| 144 | END IF |
|---|
| 145 | |
|---|
| 146 | END SUBROUTINE etat0 |
|---|
| 147 | |
|---|
| 148 | SUBROUTINE etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_q) |
|---|
| 149 | USE theta2theta_rhodz_mod |
|---|
| 150 | IMPLICIT NONE |
|---|
| 151 | TYPE(t_field),POINTER :: f_ps(:) |
|---|
| 152 | TYPE(t_field),POINTER :: f_mass(:) |
|---|
| 153 | TYPE(t_field),POINTER :: f_phis(:) |
|---|
| 154 | TYPE(t_field),POINTER :: f_theta_rhodz(:) |
|---|
| 155 | TYPE(t_field),POINTER :: f_u(:) |
|---|
| 156 | TYPE(t_field),POINTER :: f_q(:) |
|---|
| 157 | |
|---|
| 158 | TYPE(t_field),POINTER,SAVE :: f_temp(:) |
|---|
| 159 | REAL(rstd),POINTER :: ps(:) |
|---|
| 160 | REAL(rstd),POINTER :: mass(:,:) |
|---|
| 161 | REAL(rstd),POINTER :: phis(:) |
|---|
| 162 | REAL(rstd),POINTER :: theta_rhodz(:,:) |
|---|
| 163 | REAL(rstd),POINTER :: temp(:,:) |
|---|
| 164 | REAL(rstd),POINTER :: u(:,:) |
|---|
| 165 | REAL(rstd),POINTER :: q(:,:,:) |
|---|
| 166 | INTEGER :: ind |
|---|
| 167 | |
|---|
| 168 | CALL allocate_field(f_temp,field_t,type_real,llm,name='temp') |
|---|
| 169 | |
|---|
| 170 | DO ind=1,ndomain |
|---|
| 171 | IF (.NOT. assigned_domain(ind)) CYCLE |
|---|
| 172 | CALL swap_dimensions(ind) |
|---|
| 173 | CALL swap_geometry(ind) |
|---|
| 174 | ps=f_ps(ind) |
|---|
| 175 | mass=f_mass(ind) |
|---|
| 176 | phis=f_phis(ind) |
|---|
| 177 | theta_rhodz=f_theta_rhodz(ind) |
|---|
| 178 | temp=f_temp(ind) |
|---|
| 179 | u=f_u(ind) |
|---|
| 180 | q=f_q(ind) |
|---|
| 181 | |
|---|
| 182 | IF( TRIM(etat0_type)=='williamson91.6' ) THEN |
|---|
| 183 | CALL compute_etat0_collocated(ps,mass, phis, theta_rhodz, u, q) |
|---|
| 184 | ELSE |
|---|
| 185 | CALL compute_etat0_collocated(ps,mass, phis, temp, u, q) |
|---|
| 186 | ENDIF |
|---|
| 187 | ENDDO |
|---|
| 188 | |
|---|
| 189 | IF( TRIM(etat0_type)/='williamson91.6' ) CALL temperature2theta_rhodz(f_ps,f_temp,f_theta_rhodz) |
|---|
| 190 | |
|---|
| 191 | CALL deallocate_field(f_temp) |
|---|
| 192 | |
|---|
| 193 | END SUBROUTINE etat0_collocated |
|---|
| 194 | |
|---|
| 195 | SUBROUTINE compute_etat0_collocated(ps,mass, phis, temp_i, u, q) |
|---|
| 196 | USE wind_mod |
|---|
| 197 | USE etat0_jablonowsky06_mod, ONLY : compute_jablonowsky06 => compute_etat0 |
|---|
| 198 | USE etat0_dcmip5_mod, ONLY : compute_dcmip5 => compute_etat0 |
|---|
| 199 | USE etat0_williamson_mod, ONLY : compute_w91_6 => compute_etat0 |
|---|
| 200 | USE etat0_temperature_mod, ONLY: compute_etat0_temperature => compute_etat0 |
|---|
| 201 | IMPLICIT NONE |
|---|
| 202 | REAL(rstd),INTENT(INOUT) :: ps(iim*jjm) |
|---|
| 203 | REAL(rstd),INTENT(INOUT) :: mass(iim*jjm,llm) |
|---|
| 204 | REAL(rstd),INTENT(OUT) :: phis(iim*jjm) |
|---|
| 205 | REAL(rstd),INTENT(OUT) :: temp_i(iim*jjm,llm) |
|---|
| 206 | REAL(rstd),INTENT(OUT) :: u(3*iim*jjm,llm) |
|---|
| 207 | REAL(rstd),INTENT(OUT) :: q(iim*jjm,llm,nqtot) |
|---|
| 208 | |
|---|
| 209 | REAL(rstd) :: ulon_i(iim*jjm,llm) |
|---|
| 210 | REAL(rstd) :: ulat_i(iim*jjm,llm) |
|---|
| 211 | |
|---|
| 212 | REAL(rstd) :: ps_e(3*iim*jjm) |
|---|
| 213 | REAL(rstd) :: mass_e(3*iim*jjm,llm) |
|---|
| 214 | REAL(rstd) :: phis_e(3*iim*jjm) |
|---|
| 215 | REAL(rstd) :: temp_e(3*iim*jjm,llm) |
|---|
| 216 | REAL(rstd) :: ulon_e(3*iim*jjm,llm) |
|---|
| 217 | REAL(rstd) :: ulat_e(3*iim*jjm,llm) |
|---|
| 218 | REAL(rstd) :: q_e(3*iim*jjm,llm,nqtot) |
|---|
| 219 | |
|---|
| 220 | INTEGER :: l,i,j,ij |
|---|
| 221 | |
|---|
| 222 | SELECT CASE (TRIM(etat0_type)) |
|---|
| 223 | CASE ('isothermal') |
|---|
| 224 | CALL compute_etat0_isothermal(iim*jjm, phis, ps, temp_i, ulon_i, ulat_i, q) |
|---|
| 225 | CALL compute_etat0_isothermal(3*iim*jjm, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e) |
|---|
| 226 | CASE ('temperature_profile') |
|---|
| 227 | CALL compute_etat0_temperature(iim*jjm, phis, ps, temp_i, ulon_i, ulat_i, q) |
|---|
| 228 | CALL compute_etat0_temperature(3*iim*jjm, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e) |
|---|
| 229 | CASE('jablonowsky06') |
|---|
| 230 | CALL compute_jablonowsky06(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i) |
|---|
| 231 | CALL compute_jablonowsky06(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e) |
|---|
| 232 | CASE('dcmip5') |
|---|
| 233 | CALL compute_dcmip5(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i, q) |
|---|
| 234 | CALL compute_dcmip5(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e) |
|---|
| 235 | CASE('williamson91.6') |
|---|
| 236 | CALL compute_w91_6(iim*jjm,lon_i,lat_i, phis, mass(:,1), temp_i(:,1), ulon_i(:,1), ulat_i(:,1)) |
|---|
| 237 | CALL compute_w91_6(3*iim*jjm,lon_e,lat_e, phis_e, mass_e(:,1), temp_e(:,1), ulon_e(:,1), ulat_e(:,1)) |
|---|
| 238 | END SELECT |
|---|
| 239 | |
|---|
| 240 | CALL compute_wind_perp_from_lonlat_compound(ulon_e, ulat_e, u) |
|---|
| 241 | |
|---|
| 242 | END SUBROUTINE compute_etat0_collocated |
|---|
| 243 | |
|---|
| 244 | !----------------------------- Resting isothermal state -------------------------------- |
|---|
| 245 | |
|---|
| 246 | SUBROUTINE getin_etat0_isothermal |
|---|
| 247 | etat0_temp=300 |
|---|
| 248 | CALL getin("etat0_isothermal_temp",etat0_temp) |
|---|
| 249 | END SUBROUTINE getin_etat0_isothermal |
|---|
| 250 | |
|---|
| 251 | SUBROUTINE compute_etat0_isothermal(ngrid, phis, ps, temp, ulon, ulat, q) |
|---|
| 252 | IMPLICIT NONE |
|---|
| 253 | INTEGER, INTENT(IN) :: ngrid |
|---|
| 254 | REAL(rstd),INTENT(OUT) :: phis(ngrid) |
|---|
| 255 | REAL(rstd),INTENT(OUT) :: ps(ngrid) |
|---|
| 256 | REAL(rstd),INTENT(OUT) :: temp(ngrid,llm) |
|---|
| 257 | REAL(rstd),INTENT(OUT) :: ulon(ngrid,llm) |
|---|
| 258 | REAL(rstd),INTENT(OUT) :: ulat(ngrid,llm) |
|---|
| 259 | REAL(rstd),INTENT(OUT) :: q(ngrid,llm,nqtot) |
|---|
| 260 | phis(:)=0 |
|---|
| 261 | ps(:)=preff |
|---|
| 262 | temp(:,:)=etat0_temp |
|---|
| 263 | ulon(:,:)=0 |
|---|
| 264 | ulat(:,:)=0 |
|---|
| 265 | q(:,:,:)=0 |
|---|
| 266 | END SUBROUTINE compute_etat0_isothermal |
|---|
| 267 | |
|---|
| 268 | END MODULE etat0_mod |
|---|