source: codes/icosagcm/trunk/src/etat0_temperature.f90 @ 352

Last change on this file since 352 was 328, checked in by ymipsl, 9 years ago

Add missing files...
Merge recent developments from saturn branch onto trunk.

  • lmdz generic physics interface
  • performance improvment on mix mpi/openmp
  • asynchrone and overlaping communication
  • best domain distribution between process and threads
  • ....

This version is compatible with the actual saturn version and the both branches are considered merged on dynamico component.

YM

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 
27 !$OMP MASTER
28    unit=free_unit()
29    OPEN(unit,file=temperature_file,status="old",action="read",iostat=ok)
30    IF (ok/=0) THEN
31      WRITE(*,*) "getin_etat0 error: input file ",trim(temperature_file)," not found!"
32      CALL ABORT
33    ENDIF
34    ! read in t_profile() line by line, starting from first atmospheric
35    ! layer, up to model top
36    DO l=1,llm
37      READ(unit,fmt=*,iostat=ok) t_profile(l)
38      IF (ok/=0) THEN
39        WRITE(*,*) "getin_etat0 error: failed reading t_profile(l) for l=",l
40        CALL ABORT
41      ENDIF
42    ENDDO
43   
44    CLOSE(unit)
45    IF (is_mpi_root) THEN
46      WRITE(*,*) "Using input temperature profile from file ",trim(temperature_file),":"
47      DO l=1,llm
48         WRITE(*,*) "  TEMP(l=",l,")=",t_profile(l)
49      ENDDO
50    ENDIF
51!$OMP END MASTER
52
53    IF (omp_in_parallel()) THEN
54      CALL bcast_omp(t_profile)
55    ENDIF
56   
57  END SUBROUTINE getin_etat0
58
59  SUBROUTINE compute_etat0(ngrid, phis, ps, temp, ulon, ulat, q)
60    USE earth_const, ONLY: preff
61    IMPLICIT NONE 
62    INTEGER, INTENT(IN)    :: ngrid
63    REAL(rstd),INTENT(OUT) :: phis(ngrid)
64    REAL(rstd),INTENT(OUT) :: ps(ngrid)
65    REAL(rstd),INTENT(OUT) :: temp(ngrid,llm)
66    REAL(rstd),INTENT(OUT) :: ulon(ngrid,llm)
67    REAL(rstd),INTENT(OUT) :: ulat(ngrid,llm)
68    REAL(rstd),INTENT(OUT) :: q(ngrid,llm,nqtot)
69    INTEGER :: l
70    phis(:)=0
71    ps(:)=preff
72    DO l=1,llm
73      temp(:,l)=t_profile(l)
74    ENDDO
75    ulon(:,:)=0
76    ulat(:,:)=0
77    q(:,:,:)=0
78
79  END SUBROUTINE compute_etat0
80
81END MODULE etat0_temperature_mod
Note: See TracBrowser for help on using the repository browser.