source: LMDZ4/trunk/libf/phylmd/iophy.F90 @ 911

Last change on this file since 911 was 879, checked in by Laurent Fairhead, 17 years ago

Suite de la bascule vers une physique avec thermiques, nouvelle convection, poche froide ...
LF

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 4.6 KB
Line 
1!
2! $Header$
3!
4module iophy
5 
6  REAL,private,allocatable,dimension(:,:),save :: tmp_tab2d
7  REAL,private,allocatable,dimension(:,:,:),save :: tmp_tab3d
8  INTEGER,private,allocatable,dimension(:),save :: ndex2d
9  INTEGER,private,allocatable,dimension(:),save :: ndex3d
10  REAL,private,allocatable,dimension(:),save :: io_lat
11  REAL,private,allocatable,dimension(:),save :: io_lon
12  INTEGER, save :: phys_domain_id
13 
14  INTERFACE histwrite_phy
15    MODULE PROCEDURE histwrite2d_phy,histwrite3d_phy
16  END INTERFACE
17
18contains
19
20  subroutine init_iophy(lat,lon)
21  USE dimphy
22  USE mod_phys_lmdz_para
23  use ioipsl
24  implicit none
25  include 'dimensions.h'   
26    real,dimension(iim),intent(in) :: lon
27    real,dimension(jjm+1-1/iim),intent(in) :: lat
28
29    INTEGER,DIMENSION(2) :: ddid
30    INTEGER,DIMENSION(2) :: dsg
31    INTEGER,DIMENSION(2) :: dsl
32    INTEGER,DIMENSION(2) :: dpf
33    INTEGER,DIMENSION(2) :: dpl
34    INTEGER,DIMENSION(2) :: dhs
35    INTEGER,DIMENSION(2) :: dhe
36
37!$OMP MASTER 
38    allocate(io_lat(jjm+1-1/iim))
39    io_lat(:)=lat(:)
40    allocate(io_lon(iim))
41    io_lon(:)=lon(:)
42    allocate(tmp_tab2d(iim,jj_nb))
43    allocate(tmp_tab3d(iim,jj_nb,klev))
44    allocate(ndex2d(iim*jj_nb))
45    allocate(ndex3d(iim*jj_nb*klev))
46    ndex2d(:)=0
47    ndex3d(:)=0
48   
49    ddid=(/ 1,2 /)
50    dsg=(/ iim, jjm+1-1/iim /)
51    dsl=(/ iim, jj_nb /)
52    dpf=(/ 1,jj_begin /)
53    dpl=(/ iim, jj_end /)
54    dhs=(/ ii_begin-1,0 /)
55    if (mpi_rank==mpi_size-1) then
56      dhe=(/0,0/)
57    else
58      dhe=(/ iim-ii_end,0 /) 
59    endif
60   
61    call flio_dom_set(mpi_size,mpi_rank,ddid,dsg,dsl,dpf,dpl,dhs,dhe, &
62                      'APPLE',phys_domain_id)
63
64!$OMP END MASTER
65     
66  end subroutine init_iophy
67 
68  subroutine histbeg_phy(name,itau0,zjulian,dtime,nhori,nid_day)
69  USE dimphy
70  USE mod_phys_lmdz_para
71  use ioipsl
72  use write_field
73  implicit none
74  include 'dimensions.h'
75   
76    character*(*), intent(IN) :: name
77    integer, intent(in) :: itau0
78    real,intent(in) :: zjulian
79    real,intent(in) :: dtime
80    integer,intent(out) :: nhori
81    integer,intent(out) :: nid_day
82
83!$OMP MASTER   
84    if (is_sequential) then
85      call histbeg(name,iim,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
86                   1,iim,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day)
87    else
88      call histbeg(name,iim,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
89                   1,iim,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day,phys_domain_id)
90    endif
91!$OMP END MASTER
92 
93  end subroutine histbeg_phy
94 
95  subroutine histwrite2d_phy(nid,name,itau,field)
96  USE dimphy
97  USE mod_phys_lmdz_para
98  USE ioipsl
99  implicit none
100  include 'dimensions.h'
101   
102    integer,intent(in) :: nid
103    character*(*), intent(IN) :: name
104    integer, intent(in) :: itau
105    real,dimension(klon),intent(in) :: field
106   
107    REAL,dimension(klon_mpi) :: buffer_omp
108   
109    CALL Gather_omp(field,buffer_omp)   
110!$OMP MASTER
111    CALL grid1Dto2D_mpi(buffer_omp,tmp_tab2d)
112    CALL histwrite(nid,name,itau,tmp_tab2d,iim*jj_nb,ndex2d)
113!$OMP END MASTER   
114  end subroutine histwrite2d_phy
115 
116  subroutine histwrite3d_phy(nid,name,itau,field)
117  USE dimphy
118  USE mod_phys_lmdz_para
119
120  use ioipsl
121  implicit none
122  include 'dimensions.h'
123   
124    integer,intent(in) :: nid
125    character*(*), intent(IN) :: name
126    integer, intent(in) :: itau
127    real,dimension(klon,klev),intent(in) :: field
128
129    REAL,dimension(klon_mpi,klev) :: buffer_omp
130   
131    CALL Gather_omp(field,buffer_omp)
132!$OMP MASTER
133    CALL grid1Dto2D_mpi(buffer_omp,tmp_tab3d)
134    CALL histwrite(nid,name,itau,tmp_tab3d,iim*jj_nb*klev,ndex3d)
135!$OMP END MASTER   
136  end subroutine histwrite3d_phy
137 
138 
139!  subroutine phy2dyn(field_phy,field_dyn,nlev)
140!  USE dimphy_old
141!  implicit none
142!  include 'dimensions.h'
143
144!    real,dimension(klon_mpi,nlev),intent(in) :: field_phy
145!    real,dimension(iim,jjphy_nb,nlev),intent(out) :: field_dyn
146!    integer,intent(in) :: nlev
147!   
148!    integer :: next
149!    integer :: j,l
150!   
151!      do l=1,nlev
152!               
153!       if (jjphy_begin==jjphy_end) then
154!         field_dyn(:,1,l)=0.
155!         field_dyn(iiphy_begin:iiphy_end,1,l)=field_phy(1:klon_mpi,l)
156!       else
157!       
158!        if (jjphy_begin==1) then
159!           field_dyn(:,1,l)=field_phy(1,l)
160!           next=2
161!        else
162!          field_dyn(:,1,l)=0.
163!          next=iim-iiphy_begin+2
164!          field_dyn(iiphy_begin:iim,1,l)=field_phy(1:next-1,l)   
165!        endif
166!       
167!         do j=2,jjphy_nb-1
168!           field_dyn(:,j,l)=field_phy(next:next+iim-1,l)
169!           next=next+iim
170!         enddo
171!         
172!         if (jjphy_end==jjm+1-1/iim) then
173!             field_dyn(:,jjphy_nb,l)=field_phy(klon_mpi,l)
174!         else
175!          field_dyn(:,jjphy_nb,l)=0.
176!          field_dyn(1:iiphy_end,jjphy_nb,l)=field_phy(next:next+iiphy_end-1,l)   
177!         endif
178!         
179!       endif
180!     
181!     enddo
182!       
183!    end subroutine phy2dyn         
184 
185         
186end module iophy
Note: See TracBrowser for help on using the repository browser.