source: codes/icosagcm/devel/src/initial/etat0_temperature.f90 @ 595

Last change on this file since 595 was 531, checked in by dubos, 7 years ago

devel : tyding up sources

File size: 2.2 KB
Line 
1MODULE etat0_temperature_mod
2  USE prec
3  USE icosa, ONLY: llm,nqtot
4  IMPLICIT NONE
5  PRIVATE
6
7  REAL(rstd), SAVE, ALLOCATABLE :: t_profile(:)
8!$OMP THREADPRIVATE(t_profile)
9
10  PUBLIC :: getin_etat0, compute_etat0
11
12CONTAINS
13 
14  SUBROUTINE getin_etat0
15    USE getin_mod, ONLY: getin
16    USE mpipara, ONLY: is_mpi_root
17    USE omp_para, ONLY: omp_in_parallel
18    USE transfert_omp_mod, ONLY: bcast_omp
19    USE free_unit_mod, ONLY : free_unit
20    INTEGER :: unit,ok
21    INTEGER :: l
22    CHARACTER(len=255) :: temperature_file
23 
24    temperature_file="profile.in" ! default file name
25    ! but users may want to use some other file name
26    CALL getin("temperature_profile_file",temperature_file)
27   
28    ALLOCATE(t_profile(llm))
29 
30 
31 !$OMP MASTER
32    unit=free_unit()
33    OPEN(unit,file=temperature_file,status="old",action="read",iostat=ok)
34    IF (ok/=0) THEN
35      WRITE(*,*) "getin_etat0 error: input file ",trim(temperature_file)," not found!"
36      CALL ABORT
37    ENDIF
38    ! read in t_profile() line by line, starting from first atmospheric
39    ! layer, up to model top
40    DO l=1,llm
41      READ(unit,fmt=*,iostat=ok) t_profile(l)
42      IF (ok/=0) THEN
43        WRITE(*,*) "getin_etat0 error: failed reading t_profile(l) for l=",l
44        CALL ABORT
45      ENDIF
46    ENDDO
47   
48    CLOSE(unit)
49    IF (is_mpi_root) THEN
50      WRITE(*,*) "Using input temperature profile from file ",trim(temperature_file),":"
51      DO l=1,llm
52         WRITE(*,*) "  TEMP(l=",l,")=",t_profile(l)
53      ENDDO
54    ENDIF
55!$OMP END MASTER
56
57    IF (omp_in_parallel()) THEN
58      CALL bcast_omp(t_profile)
59    ENDIF
60   
61  END SUBROUTINE getin_etat0
62
63  SUBROUTINE compute_etat0(ngrid, phis, ps, temp, ulon, ulat, q)
64    USE earth_const, ONLY: preff
65    INTEGER, INTENT(IN)    :: ngrid
66    REAL(rstd),INTENT(OUT) :: phis(ngrid)
67    REAL(rstd),INTENT(OUT) :: ps(ngrid)
68    REAL(rstd),INTENT(OUT) :: temp(ngrid,llm)
69    REAL(rstd),INTENT(OUT) :: ulon(ngrid,llm)
70    REAL(rstd),INTENT(OUT) :: ulat(ngrid,llm)
71    REAL(rstd),INTENT(OUT) :: q(ngrid,llm,nqtot)
72    INTEGER :: l
73    phis(:)=0
74    ps(:)=preff
75    DO l=1,llm
76      temp(:,l)=t_profile(l)
77    ENDDO
78    ulon(:,:)=0
79    ulat(:,:)=0
80    q(:,:,:)=0
81
82  END SUBROUTINE compute_etat0
83
84END MODULE etat0_temperature_mod
Note: See TracBrowser for help on using the repository browser.