source: codes/icosagcm/trunk/src/etat0_dcmip2.f90 @ 344

Last change on this file since 344 was 344, checked in by dubos, 9 years ago

Cleanup DCMIP 1&2

File size: 2.5 KB
Line 
1MODULE etat0_dcmip2_mod
2
3! test cases DCMIP 2012, category 2 : Orographic gravity waves
4
5  USE icosa
6  PRIVATE
7
8  INTEGER, SAVE :: testcase
9  INTEGER, PARAMETER :: mountain=0, schaer_noshear=1, schaer_shear=2
10
11  PUBLIC getin_etat0, compute_etat0
12
13CONTAINS
14
15  SUBROUTINE getin_etat0
16    CHARACTER(len=255) :: etat0_type
17    etat0_type='jablonowsky06'
18    CALL getin("etat0",etat0_type)
19    SELECT CASE (TRIM(etat0_type))
20    CASE('dcmip2_mountain')
21       testcase = mountain
22    CASE('dcmip2_schaer_noshear')
23       testcase = schaer_noshear
24    CASE('dcmip2_schaer_shear')
25       testcase = schaer_shear
26    CASE DEFAULT
27       PRINT *, 'This should not happen : etat0_type =', TRIM(etat0_type), ' in etat0_dcmip2.f90/etat0'
28       STOP
29    END SELECT
30    PRINT *, 'Orographic gravity-wave test case :', TRIM(etat0_type)
31  END SUBROUTINE getin_etat0
32
33  SUBROUTINE compute_etat0(ngrid,lon,lat, phis, ps, Temp, ulon, ulat)
34    USE disvert_mod
35    IMPLICIT NONE
36    INTEGER, INTENT(IN)    :: ngrid
37    REAL(rstd),INTENT(IN)  :: lon(ngrid)
38    REAL(rstd),INTENT(IN)  :: lat(ngrid)
39    REAL(rstd),INTENT(OUT) :: ps(ngrid)
40    REAL(rstd),INTENT(OUT) :: phis(ngrid)
41    REAL(rstd),INTENT(OUT) :: Temp(ngrid,llm)
42    REAL(rstd),INTENT(OUT) :: ulon(ngrid,llm)
43    REAL(rstd),INTENT(OUT) :: ulat(ngrid,llm)
44    INTEGER :: l,ij
45    REAL(rstd) :: hyam, hybm
46
47    ! Hexagons : ps,phis,temp
48    DO l=1,llm
49       ! The surface pressure is not set yet so we provide the hybrid coefficients
50       hyam = .5*(ap(l)+ap(l+1))/preff
51       hybm = .5*(bp(l)+bp(l+1))
52       DO ij=1,ngrid
53          CALL comp_all(hyam,hybm,lon(ij),lat(ij), &
54               ps(ij),phis(ij), Temp(ij,l),ulon(ij,l), ulat(ij,l) )
55       END DO
56    END DO
57  END SUBROUTINE compute_etat0
58
59  SUBROUTINE comp_all(hyam,hybm,lon,lat, psj,phisj,tempj, ulonj,ulatj)
60    USE dcmip_initial_conditions_test_1_2_3
61    REAL(rstd), INTENT(IN) :: hyam, hybm, lon, lat
62    REAL(rstd), INTENT(OUT) :: psj,phisj,tempj,ulonj,ulatj
63    REAL :: dummy
64    dummy=0.
65    SELECT CASE (testcase)
66    CASE(mountain)
67       CALL test2_steady_state_mountain(lon,lat,dummy,dummy,0,.TRUE.,hyam,hybm, &
68            ulonj,ulatj,dummy,tempj,phisj,psj,dummy,dummy)
69    CASE(schaer_noshear)
70       CALL test2_schaer_mountain(lon,lat,dummy,dummy,0,.TRUE.,hyam,hybm,0,&
71            ulonj,ulatj,dummy,tempj,phisj,psj,dummy,dummy)
72    CASE(schaer_shear)
73       CALL test2_schaer_mountain(lon,lat,dummy,dummy,0,.TRUE.,hyam,hybm,1, &
74            ulonj,ulatj,dummy,tempj,phisj,psj,dummy,dummy)
75    END SELECT
76  END SUBROUTINE comp_all
77
78END MODULE etat0_dcmip2_mod
Note: See TracBrowser for help on using the repository browser.