source: codes/icosagcm/devel/src/initial/etat0_dcmip2016_supercell.f90 @ 732

Last change on this file since 732 was 732, checked in by dubos, 6 years ago

devel : more cleanup and reorganization in dynamics/

File size: 1.9 KB
Line 
1MODULE etat0_dcmip2016_supercell_mod
2  USE icosa
3  USE caldyn_vars_mod
4  IMPLICIT NONE
5  PRIVATE
6 
7  PUBLIC getin_etat0, compute_etat0
8
9CONTAINS
10
11  SUBROUTINE getin_etat0
12    USE mpipara, ONLY : is_mpi_root
13    USE tracer_mod
14    USE dcmip2016_supercell_mod, ONLY : supercell_init, supercell_test
15    IF(nqtot<5) THEN
16       IF (is_mpi_root)  THEN
17          PRINT *, "nqtot must be at least 5 for test case dcmip2016_supercell"
18       END IF
19       STOP
20    END IF
21
22    CALL supercell_init
23   
24  END SUBROUTINE getin_etat0
25
26  SUBROUTINE compute_etat0(ngrid,lon,lat, phis,ps,temp,ulon,ulat,q)
27    USE icosa
28    USE disvert_mod
29    USE omp_para
30    USE dcmip2016_supercell_mod, ONLY : supercell_init, supercell_test, supercell_z
31    USE terminator, ONLY: initial_value_Terminator
32    INTEGER, INTENT(IN) :: ngrid
33    REAL(rstd),INTENT(IN) :: lon(ngrid)
34    REAL(rstd),INTENT(IN) :: lat(ngrid)
35    REAL(rstd),INTENT(OUT) :: phis(ngrid)
36    REAL(rstd),INTENT(OUT) :: ps(ngrid)
37    REAL(rstd),INTENT(OUT) :: temp(ngrid,llm)
38    REAL(rstd),INTENT(OUT) :: ulon(ngrid,llm)
39    REAL(rstd),INTENT(OUT) :: ulat(ngrid,llm)
40    REAL(rstd),INTENT(OUT) :: q(ngrid,llm,nqtot)
41   
42    INTEGER :: l,ij
43    INTEGER,PARAMETER :: perturbation = 1
44   
45    REAL(rstd) :: p,z, thetav,rho
46 
47    phis(:)=0
48    DO ij=1,ngrid
49       z=0.
50       CALL supercell_z(lon(ij), lat(ij), z, ps(ij), thetav, rho, q(ij,1,1), perturbation)
51       DO l=ll_begin,ll_end
52         p=0.5*(ap(l)+ap(l+1) + (bp(l)+bp(l+1)) * ps(ij))
53         CALL supercell_test(lon(ij),lat(ij),p,z,0,ulon(ij,l),ulat(ij,l),temp(ij,l),thetav, ps(ij),rho, q(ij,l,1),perturbation) 
54       
55        IF (physics_thermo==thermo_fake_moist) temp(ij,l)=Temp(ij,l)*(1+0.608*q(ij,l,1))
56        q(ij,l,2)=0.
57        q(ij,l,3)=0.
58        CALL initial_value_Terminator(lat(ij),lon(ij),q(ij,l,4),q(ij,l,5))
59
60       END DO
61    END DO
62 
63   
64  END SUBROUTINE compute_etat0
65 
66END MODULE etat0_dcmip2016_supercell_mod
Note: See TracBrowser for help on using the repository browser.