source: codes/icosagcm/branches/SATURN_DYNAMICO/ICOSAGCM/src/etat0_temperature.f90 @ 268

Last change on this file since 268 was 268, checked in by millour, 10 years ago

Add possibility to initialize atmospheric temperatures with a profile read from a text file (one value per line, starting from first atmospheric level, up to the top of the atmosphere).
EM

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