source: codes/icosagcm/devel/src/initial/etat0_isothermal.f90 @ 847

Last change on this file since 847 was 847, checked in by dubos, 5 years ago

devel : split etat0 into etat0, etat0_collocated and etat0_isothermal

File size: 984 bytes
Line 
1MODULE etat0_isothermal_mod
2  USE icosa, ONLY : rstd, getin, llm, nqtot, preff
3  IMPLICIT NONE         
4  PRIVATE
5  SAVE
6 
7  REAL(rstd) :: etat0_temp
8!$OMP THREADPRIVATE(etat0_temp)
9 
10  PUBLIC :: getin_etat0, compute_etat0
11 
12CONTAINS
13 
14!----------------------------- Resting isothermal state --------------------------------
15
16  SUBROUTINE getin_etat0
17    etat0_temp=300
18    CALL getin("etat0_isothermal_temp",etat0_temp)
19  END SUBROUTINE getin_etat0
20
21  SUBROUTINE compute_etat0(ngrid, phis, ps, temp, ulon, ulat, q)
22    INTEGER, INTENT(IN)    :: ngrid
23    REAL(rstd),INTENT(OUT) :: phis(ngrid)
24    REAL(rstd),INTENT(OUT) :: ps(ngrid)
25    REAL(rstd),INTENT(OUT) :: temp(ngrid,llm)
26    REAL(rstd),INTENT(OUT) :: ulon(ngrid,llm)
27    REAL(rstd),INTENT(OUT) :: ulat(ngrid,llm)
28    REAL(rstd),INTENT(OUT) :: q(ngrid,llm,nqtot)
29    phis(:)=0
30    ps(:)=preff
31    temp(:,:)=etat0_temp
32    ulon(:,:)=0
33    ulat(:,:)=0
34    q(:,:,:)=0
35  END SUBROUTINE compute_etat0
36
37END MODULE etat0_isothermal_mod
Note: See TracBrowser for help on using the repository browser.