| 1 | MODULE etat0_dcmip2_mod |
|---|
| 2 | |
|---|
| 3 | ! test cases DCMIP 2012, category 2 : Orographic gravity waves |
|---|
| 4 | |
|---|
| 5 | USE genmod |
|---|
| 6 | |
|---|
| 7 | PRIVATE |
|---|
| 8 | |
|---|
| 9 | PUBLIC etat0 |
|---|
| 10 | |
|---|
| 11 | CONTAINS |
|---|
| 12 | |
|---|
| 13 | |
|---|
| 14 | SUBROUTINE etat0(f_ps,f_phis,f_theta_rhodz,f_u, f_q) |
|---|
| 15 | USE icosa |
|---|
| 16 | USE theta2theta_rhodz_mod |
|---|
| 17 | IMPLICIT NONE |
|---|
| 18 | TYPE(t_field),POINTER :: f_ps(:) |
|---|
| 19 | TYPE(t_field),POINTER :: f_phis(:) |
|---|
| 20 | TYPE(t_field),POINTER :: f_theta_rhodz(:) |
|---|
| 21 | TYPE(t_field),POINTER :: f_u(:) |
|---|
| 22 | TYPE(t_field),POINTER :: f_q(:) |
|---|
| 23 | |
|---|
| 24 | TYPE(t_field),POINTER,SAVE :: f_temp(:) |
|---|
| 25 | REAL(rstd),POINTER :: ps(:) |
|---|
| 26 | REAL(rstd),POINTER :: phis(:) |
|---|
| 27 | REAL(rstd),POINTER :: u(:,:) |
|---|
| 28 | REAL(rstd),POINTER :: Temp(:,:) |
|---|
| 29 | REAL(rstd),POINTER :: q(:,:,:) |
|---|
| 30 | |
|---|
| 31 | INTEGER :: ind, icase |
|---|
| 32 | CHARACTER(len=255) :: etat0_type |
|---|
| 33 | etat0_type='jablonowsky06' |
|---|
| 34 | CALL getin("etat0",etat0_type) |
|---|
| 35 | |
|---|
| 36 | SELECT CASE (TRIM(etat0_type)) |
|---|
| 37 | CASE('dcmip2_mountain') |
|---|
| 38 | icase=0 |
|---|
| 39 | CASE('dcmip2_schaer_noshear') |
|---|
| 40 | icase=1 |
|---|
| 41 | CASE('dcmip2_schaer_shear') |
|---|
| 42 | icase=2 |
|---|
| 43 | CASE DEFAULT |
|---|
| 44 | PRINT *, 'This should not happen : etat0_type =', TRIM(etat0_type), ' in etat0_dcmip2.f90/etat0' |
|---|
| 45 | STOP |
|---|
| 46 | END SELECT |
|---|
| 47 | PRINT *, 'Orographic gravity-wave test case :', TRIM(etat0_type) |
|---|
| 48 | |
|---|
| 49 | CALL allocate_field(f_temp,field_t,type_real,llm,name='temp') |
|---|
| 50 | |
|---|
| 51 | DO ind=1,ndomain |
|---|
| 52 | IF (.NOT. assigned_domain(ind)) CYCLE |
|---|
| 53 | CALL swap_dimensions(ind) |
|---|
| 54 | CALL swap_geometry(ind) |
|---|
| 55 | |
|---|
| 56 | ps=f_ps(ind) |
|---|
| 57 | phis=f_phis(ind) |
|---|
| 58 | u=f_u(ind) |
|---|
| 59 | q=f_q(ind) |
|---|
| 60 | temp=f_temp(ind) |
|---|
| 61 | CALL compute_etat0_DCMIP2(icase,ps,phis,u,Temp,q) |
|---|
| 62 | ENDDO |
|---|
| 63 | |
|---|
| 64 | CALL temperature2theta_rhodz(f_ps,f_temp,f_theta_rhodz) |
|---|
| 65 | |
|---|
| 66 | CALL deallocate_field(f_temp) |
|---|
| 67 | |
|---|
| 68 | END SUBROUTINE etat0 |
|---|
| 69 | |
|---|
| 70 | SUBROUTINE compute_etat0_DCMIP2(icase, ps, phis, u, temp,q) |
|---|
| 71 | USE icosa |
|---|
| 72 | USE disvert_mod, ONLY : ap,bp |
|---|
| 73 | USE pression_mod |
|---|
| 74 | USE theta2theta_rhodz_mod |
|---|
| 75 | USE wind_mod |
|---|
| 76 | IMPLICIT NONE |
|---|
| 77 | INTEGER, INTENT(IN) :: icase |
|---|
| 78 | REAL(rstd), INTENT(OUT) :: ps(iim*jjm) |
|---|
| 79 | REAL(rstd), INTENT(OUT) :: phis(iim*jjm) |
|---|
| 80 | REAL(rstd), INTENT(OUT) :: u(3*iim*jjm,llm) |
|---|
| 81 | REAL(rstd), INTENT(OUT) :: temp(iim*jjm,llm) |
|---|
| 82 | REAL(rstd), INTENT(OUT) :: q(iim*jjm,llm) |
|---|
| 83 | REAL(rstd) :: ulon(3*iim*jjm,llm), ulat(3*iim*jjm,llm) |
|---|
| 84 | |
|---|
| 85 | INTEGER :: i,j,l,ij |
|---|
| 86 | REAL(rstd) :: hyam, hybm, pp, dummy1, dummy2, dummy3 |
|---|
| 87 | |
|---|
| 88 | ! Hexagons : ps,phis,temp |
|---|
| 89 | DO l=1,llm |
|---|
| 90 | ! The surface pressure is not set yet so we provide the hybrid coefficients |
|---|
| 91 | hyam = .5*(ap(l)+ap(l+1))/preff |
|---|
| 92 | hybm = .5*(bp(l)+bp(l+1)) |
|---|
| 93 | DO j=jj_begin,jj_end |
|---|
| 94 | DO i=ii_begin,ii_end |
|---|
| 95 | ij=(j-1)*iim+i |
|---|
| 96 | CALL comp_all(lon_i(ij),lat_i(ij), ps(ij),phis(ij),temp(ij,l), dummy1,dummy2) |
|---|
| 97 | END DO |
|---|
| 98 | END DO |
|---|
| 99 | END DO |
|---|
| 100 | |
|---|
| 101 | ! Edges : ulon,ulat |
|---|
| 102 | DO l=1,llm |
|---|
| 103 | ! The surface pressure is not set yet so we provide the hybrid coefficients |
|---|
| 104 | hyam = .5*(ap(l)+ap(l+1))/preff |
|---|
| 105 | hybm = .5*(bp(l)+bp(l+1)) |
|---|
| 106 | DO j=jj_begin,jj_end |
|---|
| 107 | DO i=ii_begin,ii_end |
|---|
| 108 | ij=(j-1)*iim+i |
|---|
| 109 | CALL comp_all(lon_e(ij+u_right), lat_e(ij+u_right), & |
|---|
| 110 | dummy1,dummy2,dummy3, ulon(ij+u_right,l),ulat(ij+u_right,l)) |
|---|
| 111 | CALL comp_all(lon_e(ij+u_lup), lat_e(ij+u_lup), & |
|---|
| 112 | dummy1,dummy2,dummy3, ulon(ij+u_lup,l),ulat(ij+u_lup,l)) |
|---|
| 113 | CALL comp_all(lon_e(ij+u_ldown), lat_e(ij+u_ldown), & |
|---|
| 114 | dummy1,dummy2,dummy3, ulon(ij+u_ldown,l),ulat(ij+u_ldown,l)) |
|---|
| 115 | END DO |
|---|
| 116 | END DO |
|---|
| 117 | END DO |
|---|
| 118 | CALL compute_wind_perp_from_lonlat_compound(ulon,ulat,u) |
|---|
| 119 | |
|---|
| 120 | q=1. |
|---|
| 121 | |
|---|
| 122 | CONTAINS |
|---|
| 123 | |
|---|
| 124 | SUBROUTINE comp_all(lon,lat, psj,phisj,tempj, ulonj,ulatj) |
|---|
| 125 | USE dcmip_initial_conditions_test_1_2_3 |
|---|
| 126 | REAL(rstd), INTENT(IN) :: lon, lat |
|---|
| 127 | REAL(rstd), INTENT(OUT) :: psj,phisj,tempj,ulonj,ulatj |
|---|
| 128 | REAL :: dummy |
|---|
| 129 | dummy=0. |
|---|
| 130 | SELECT CASE (icase) |
|---|
| 131 | CASE(0) |
|---|
| 132 | CALL test2_steady_state_mountain(lon,lat,dummy,dummy,0,.TRUE.,hyam,hybm, & |
|---|
| 133 | ulonj,ulatj,dummy,tempj,phisj,psj,dummy,dummy) |
|---|
| 134 | CASE(1) |
|---|
| 135 | CALL test2_schaer_mountain(lon,lat,dummy,dummy,0,.TRUE.,hyam,hybm,0,& |
|---|
| 136 | ulonj,ulatj,dummy,tempj,phisj,psj,dummy,dummy) |
|---|
| 137 | CASE(2) |
|---|
| 138 | CALL test2_schaer_mountain(lon,lat,dummy,dummy,0,.TRUE.,hyam,hybm,1, & |
|---|
| 139 | ulonj,ulatj,dummy,tempj,phisj,psj,dummy,dummy) |
|---|
| 140 | END SELECT |
|---|
| 141 | END SUBROUTINE comp_all |
|---|
| 142 | |
|---|
| 143 | END SUBROUTINE compute_etat0_DCMIP2 |
|---|
| 144 | |
|---|
| 145 | |
|---|
| 146 | END MODULE etat0_dcmip2_mod |
|---|