source: LMDZ6/trunk/libf/phylmd/iophy.F90 @ 3438

Last change on this file since 3438 was 3435, checked in by Laurent Fairhead, 6 years ago

"Historic" :-) commit merging the physics branch used for DYNAMICO with the LMDZ trunk.
The same physics branch can now be used seamlessly with the traditional lon-lat LMDZ
dynamical core and DYNAMICO.
Testing consisted in running a lon-lat LMDZ bucket simulation with the NPv6.1 physics package
with the original trunk sources and the merged sources. Tests were succesful in the sense that
numeric continuity was preserved in the restart files from both simulation. Further tests
included running both versions of the physics codes for one year in a LMDZOR setting in which
the restart files also came out identical.

Caution:

  • as the physics package now manages unstructured grids, grid information needs to be transmitted

to the surface scheme ORCHIDEE. This means that the interface defined in surf_land_orchidee_mod.F90
is only compatible with ORCHIDEE version orchidee2.1 and later versions. If previous versions of
ORCHIDEE need to be used, the CPP key ORCHIDEE_NOUNSTRUCT needs to be set at compilation time.
This is done automatically if makelmdz/makelmdz_fcm are called with the veget orchidee2.0 switch

  • due to a limitation in XIOS, the time at which limit conditions will be read in by DYNAMICO will be

delayed by one physic timestep with respect to the time it is read in by the lon-lat model. This is caused
by the line

IF (MOD(itime-1, lmt_pas) == 0 .OR. (jour_lu /= jour .AND. grid_type /= unstructured)) THEN ! time to read

in limit_read_mod.F90

Work still needed on COSP integration and XML files for DYNAMICO

EM, YM, LF

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 51.1 KB
RevLine 
[879]1!
[1897]2! $Id: iophy.F90 3435 2019-01-22 15:21:59Z fairhead $
[879]3!
[1807]4MODULE iophy
5
[1797]6! abd  REAL,private,allocatable,DIMENSION(:),save :: io_lat
7! abd  REAL,private,allocatable,DIMENSION(:),save :: io_lon
[1791]8  REAL,ALLOCATABLE,DIMENSION(:),SAVE :: io_lat
9  REAL,ALLOCATABLE,DIMENSION(:),SAVE :: io_lon
10  INTEGER, SAVE :: phys_domain_id
11  INTEGER, SAVE :: npstn
12  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: nptabij
13  INTEGER, SAVE :: itau_iophy
[3238]14  LOGICAL :: check_dim = .false.
[1791]15
16!$OMP THREADPRIVATE(itau_iophy)
[1852]17
18#ifdef CPP_XIOS
[629]19  INTERFACE histwrite_phy
[2645]20    MODULE PROCEDURE histwrite2d_phy,histwrite3d_phy,histwrite2d_phy_old,histwrite3d_phy_old,histwrite2d_xios,histwrite3d_xios,histwrite0d_xios
[1852]21  END INTERFACE
22#else
23  INTERFACE histwrite_phy
[1791]24    MODULE PROCEDURE histwrite2d_phy,histwrite3d_phy,histwrite2d_phy_old,histwrite3d_phy_old
[1001]25  END INTERFACE
[1852]26#endif
[629]27
[1539]28  INTERFACE histbeg_phy_all
[1825]29    MODULE PROCEDURE histbeg_phy,histbeg_phyxios,histbeg_phy_points
[1539]30  END INTERFACE
[1001]31
[1539]32
[1797]33CONTAINS
[629]34
[1797]35! ug Routine pour définir itau_iophy depuis phys_output_write_mod:
36  SUBROUTINE set_itau_iophy(ito)
[3266]37    IMPLICIT NONE
38    INTEGER, INTENT(IN) :: ito
39    itau_iophy = ito
[1797]40  END SUBROUTINE
41
42  SUBROUTINE init_iophy_new(rlat,rlon)
[3266]43
44    USE dimphy, ONLY: klon
45    USE mod_phys_lmdz_para, ONLY: gather, bcast, &
46                                  jj_nb, jj_begin, jj_end, ii_begin, ii_end, &
47                                  mpi_size, mpi_rank, klon_mpi, &
[2429]48                                is_sequential, is_south_pole_dyn
[3435]49  USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, klon_glo, grid_type, unstructured
50  USE print_control_mod, ONLY: prt_level,lunout
[1897]51#ifdef CPP_IOIPSL
[3266]52    USE ioipsl, ONLY: flio_dom_set
[1897]53#endif
54#ifdef CPP_XIOS
[3435]55  use wxios, ONLY: wxios_domain_param, wxios_domain_param_unstructured, wxios_context_init
[1897]56#endif
[3266]57    IMPLICIT NONE
[1797]58    REAL,DIMENSION(klon),INTENT(IN) :: rlon
59    REAL,DIMENSION(klon),INTENT(IN) :: rlat
[1001]60
[1797]61    REAL,DIMENSION(klon_glo)        :: rlat_glo
62    REAL,DIMENSION(klon_glo)        :: rlon_glo
[1001]63   
64    INTEGER,DIMENSION(2) :: ddid
65    INTEGER,DIMENSION(2) :: dsg
66    INTEGER,DIMENSION(2) :: dsl
67    INTEGER,DIMENSION(2) :: dpf
68    INTEGER,DIMENSION(2) :: dpl
69    INTEGER,DIMENSION(2) :: dhs
70    INTEGER,DIMENSION(2) :: dhe
71    INTEGER :: i   
[1852]72    INTEGER :: data_ibegin, data_iend
[1001]73
[3435]74#ifdef CPP_XIOS
75      CALL wxios_context_init
76#endif
[1001]77   
[3435]78
79    IF (grid_type==unstructured) THEN
80   
81#ifdef CPP_XIOS
82      CALL wxios_domain_param_unstructured("dom_glo")
83#endif
84
85    ELSE
86
87      CALL gather(rlat,rlat_glo)
88      CALL bcast(rlat_glo)
89      CALL gather(rlon,rlon_glo)
90      CALL bcast(rlon_glo)
91   
[1001]92!$OMP MASTER 
[2350]93    ALLOCATE(io_lat(nbp_lat))
94    IF (klon_glo == 1) THEN
95      io_lat(1)=rlat_glo(1)
96    ELSE
97      io_lat(1)=rlat_glo(1)
98      io_lat(nbp_lat)=rlat_glo(klon_glo)
[2344]99      DO i=2,nbp_lat-1
100        io_lat(i)=rlat_glo(2+(i-2)*nbp_lon)
[1001]101      ENDDO
102    ENDIF
103
[2344]104    ALLOCATE(io_lon(nbp_lon))
105    IF (klon_glo == 1) THEN
106      io_lon(1)=rlon_glo(1)
107    ELSE
108      io_lon(1:nbp_lon)=rlon_glo(2:nbp_lon+1)
109    ENDIF
110
[1852]111!! (I) dtnb   : total number of domains
112!! (I) dnb    : domain number
113!! (I) did(:) : distributed dimensions identifiers
114!!              (up to 5 dimensions are supported)
115!! (I) dsg(:) : total number of points for each dimension
116!! (I) dsl(:) : local number of points for each dimension
117!! (I) dpf(:) : position of first local point for each dimension
118!! (I) dpl(:) : position of last local point for each dimension
119!! (I) dhs(:) : start halo size for each dimension
120!! (I) dhe(:) : end halo size for each dimension
121!! (C) cdnm   : Model domain definition name.
122!!              The names actually supported are :
123!!              "BOX", "APPLE", "ORANGE".
124!!              These names are case insensitive.
[1001]125
126    ddid=(/ 1,2 /)
[2344]127    dsg=(/ nbp_lon, nbp_lat /)
128    dsl=(/ nbp_lon, jj_nb /)
[1001]129    dpf=(/ 1,jj_begin /)
[2344]130    dpl=(/ nbp_lon, jj_end /)
[1001]131    dhs=(/ ii_begin-1,0 /)
[1797]132    IF (mpi_rank==mpi_size-1) THEN
[1001]133      dhe=(/0,0/)
[1797]134    ELSE
[2344]135      dhe=(/ nbp_lon-ii_end,0 /) 
[1797]136    ENDIF
[1852]137
[2097]138#ifndef CPP_IOIPSL_NO_OUTPUT   
[1797]139    CALL flio_dom_set(mpi_size,mpi_rank,ddid,dsg,dsl,dpf,dpl,dhs,dhe, &
[1001]140                      'APPLE',phys_domain_id)
[1852]141#endif
[1825]142#ifdef CPP_XIOS
[3435]143      ! Set values for the mask:
144      IF (mpi_rank == 0) THEN
145          data_ibegin = 0
146      ELSE
147          data_ibegin = ii_begin - 1
148      END IF
[1852]149
[3435]150      IF (mpi_rank == mpi_size-1) THEN
151          data_iend = nbp_lon
152      ELSE
153          data_iend = ii_end + 1
154      END IF
[1852]155
[3435]156      IF (prt_level>=10) THEN
157        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," iibegin=",ii_begin , " ii_end=",ii_end," jjbegin=",jj_begin," jj_nb=",jj_nb," jj_end=",jj_end
158        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," nbp_lon=",nbp_lon," nbp_lat=",nbp_lat
159        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
160        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," data_ibegin=",data_ibegin," data_iend=",data_iend
161        write(lunout,*) "init_iophy_new: mpirank=",mpi_rank," is_south_pole_dyn=",is_south_pole_dyn
162      ENDIF
[1852]163
[3435]164      ! Initialize the XIOS domain coreesponding to this process:
[1825]165#endif
[1001]166!$OMP END MASTER
[3435]167
168#ifdef CPP_XIOS   
169        CALL wxios_domain_param("dom_glo")
170#endif
[1001]171     
[3435]172    ENDIF
173     
[1797]174  END SUBROUTINE init_iophy_new
[1001]175
[3266]176
[1797]177  SUBROUTINE init_iophy(lat,lon)
[3266]178
179    USE mod_phys_lmdz_para, ONLY: jj_begin, jj_end, ii_begin, ii_end, jj_nb, &
180                                  mpi_size, mpi_rank
181    USE ioipsl, ONLY: flio_dom_set
182    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
183
184    IMPLICIT NONE
185
[2344]186    REAL,DIMENSION(nbp_lon),INTENT(IN) :: lon
187    REAL,DIMENSION(nbp_lat),INTENT(IN) :: lat
[766]188
189    INTEGER,DIMENSION(2) :: ddid
190    INTEGER,DIMENSION(2) :: dsg
191    INTEGER,DIMENSION(2) :: dsl
192    INTEGER,DIMENSION(2) :: dpf
193    INTEGER,DIMENSION(2) :: dpl
194    INTEGER,DIMENSION(2) :: dhs
195    INTEGER,DIMENSION(2) :: dhe
196
197!$OMP MASTER 
[2854]198    ALLOCATE(io_lat(nbp_lat))
[629]199    io_lat(:)=lat(:)
[2854]200    ALLOCATE(io_lon(nbp_lon))
[629]201    io_lon(:)=lon(:)
[1331]202   
[766]203    ddid=(/ 1,2 /)
[2344]204    dsg=(/ nbp_lon, nbp_lat /)
205    dsl=(/ nbp_lon, jj_nb /)
[776]206    dpf=(/ 1,jj_begin /)
[2344]207    dpl=(/ nbp_lon, jj_end /)
[776]208    dhs=(/ ii_begin-1,0 /)
[2854]209    IF (mpi_rank==mpi_size-1) THEN
[766]210      dhe=(/0,0/)
[2854]211    ELSE
[2344]212      dhe=(/ nbp_lon-ii_end,0 /) 
[2854]213    ENDIF
[766]214   
[2097]215#ifndef CPP_IOIPSL_NO_OUTPUT
[776]216    call flio_dom_set(mpi_size,mpi_rank,ddid,dsg,dsl,dpf,dpl,dhs,dhe, &
[766]217                      'APPLE',phys_domain_id)
[1852]218#endif
[766]219!$OMP END MASTER
220     
[2854]221  END SUBROUTINE init_iophy
[1825]222
223 SUBROUTINE histbeg_phyxios(name,itau0,zjulian,dtime,ffreq,lev,nhori,nid_day)
[1897]224!  USE dimphy
[2854]225  USE mod_phys_lmdz_para, ONLY: is_sequential, is_using_mpi, is_mpi_root, &
[1897]226                                jj_begin, jj_end, jj_nb
[2344]227  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
[2854]228  USE ioipsl, ONLY: histbeg
[1897]229#ifdef CPP_XIOS
[2854]230  USE wxios, ONLY: wxios_add_file
[1897]231#endif
[1825]232  IMPLICIT NONE
[3266]233  INCLUDE 'clesphys.h'
[1825]234   
[3266]235  CHARACTER*(*), INTENT(IN) :: name
236  INTEGER, INTENT(IN) :: itau0
237  REAL,INTENT(IN) :: zjulian
238  REAL,INTENT(IN) :: dtime
239  CHARACTER(LEN=*), INTENT(IN) :: ffreq
240  INTEGER,INTENT(IN) :: lev
241  INTEGER,INTENT(OUT) :: nhori
242  INTEGER,INTENT(OUT) :: nid_day
[1825]243
244!$OMP MASTER   
[3266]245  IF (is_sequential) THEN
246    CALL histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
247                 1,nbp_lon,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day)
248  ELSE
249    CALL histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
250                 1,nbp_lon,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day,phys_domain_id)
251  ENDIF
[1825]252
253#ifdef CPP_XIOS
[3266]254  ! ug OMP en chantier...
255  IF((.NOT. is_using_mpi) .OR. is_mpi_root) THEN
256      ! ug Création du fichier
257    IF (.not. ok_all_xml) THEN
258      CALL wxios_add_file(name, ffreq, lev)
[2854]259    ENDIF
[3266]260  ENDIF
[1825]261#endif
262!$OMP END MASTER
[629]263 
[1825]264  END SUBROUTINE histbeg_phyxios
265 
[1797]266  SUBROUTINE histbeg_phy(name,itau0,zjulian,dtime,nhori,nid_day)
[1897]267
[2854]268  USE mod_phys_lmdz_para, ONLY: jj_begin, jj_end, jj_nb, is_sequential
[2344]269  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
[2854]270  USE ioipsl, ONLY: histbeg
[1897]271
[1797]272  IMPLICIT NONE
[629]273   
[2854]274    CHARACTER*(*), INTENT(IN) :: name
275    INTEGER, INTENT(IN) :: itau0
[1797]276    REAL,INTENT(IN) :: zjulian
277    REAL,INTENT(IN) :: dtime
[2854]278    INTEGER,INTENT(OUT) :: nhori
279    INTEGER,INTENT(OUT) :: nid_day
[766]280
281!$OMP MASTER   
[2097]282#ifndef CPP_IOIPSL_NO_OUTPUT
[2854]283    IF (is_sequential) THEN
[3266]284      CALL histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
[2344]285                   1,nbp_lon,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day)
[2854]286    ELSE
[3266]287      CALL histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), &
[2344]288                   1,nbp_lon,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day,phys_domain_id)
[2854]289    ENDIF
[1852]290#endif
[766]291!$OMP END MASTER
[629]292 
[1797]293  END SUBROUTINE histbeg_phy
[1539]294
[1825]295
[1797]296  SUBROUTINE histbeg_phy_points(rlon,rlat,pim,tabij,ipt,jpt, &
[1539]297             plon,plat,plon_bounds,plat_bounds, &
298             nname,itau0,zjulian,dtime,nnhori,nnid_day)
[2854]299  USE dimphy, ONLY: klon
300  USE mod_phys_lmdz_para, ONLY: gather, bcast, &
[1897]301                                is_sequential, klon_mpi_begin, klon_mpi_end, &
302                                mpi_rank
[3435]303  USE mod_grid_phy_lmdz, ONLY: klon_glo, nbp_lon, nbp_lat, grid1dTo2d_glo
[2854]304  USE ioipsl, ONLY: histbeg
[1897]305
[1797]306  IMPLICIT NONE
[1539]307
[1797]308    REAL,DIMENSION(klon),INTENT(IN) :: rlon
309    REAL,DIMENSION(klon),INTENT(IN) :: rlat
[2854]310    INTEGER, INTENT(IN) :: itau0
[1797]311    REAL,INTENT(IN) :: zjulian
312    REAL,INTENT(IN) :: dtime
[2854]313    INTEGER, INTENT(IN) :: pim
314    INTEGER, intent(out) :: nnhori
315    CHARACTER(len=20), INTENT(IN) :: nname
316    INTEGER, INTENT(OUT) :: nnid_day
317    INTEGER :: i
[1797]318    REAL,DIMENSION(klon_glo)        :: rlat_glo
319    REAL,DIMENSION(klon_glo)        :: rlon_glo
320    INTEGER, DIMENSION(pim), INTENT(IN)  :: tabij
321    REAL,DIMENSION(pim), INTENT(IN) :: plat, plon
322    INTEGER,DIMENSION(pim), INTENT(IN) :: ipt, jpt
323    REAL,DIMENSION(pim,2), intent(out) :: plat_bounds, plon_bounds
[1539]324
325    INTEGER, SAVE :: tabprocbeg, tabprocend
326!$OMP THREADPRIVATE(tabprocbeg, tabprocend)
327    INTEGER :: ip
328    INTEGER, PARAMETER :: nip=1
329    INTEGER :: npproc
[1797]330    REAL, allocatable, DIMENSION(:) :: npplat, npplon
331    REAL, allocatable, DIMENSION(:,:) :: npplat_bounds, npplon_bounds
[2344]332    REAL, DIMENSION(nbp_lon,nbp_lat) :: zx_lon, zx_lat
[1539]333
334    CALL gather(rlat,rlat_glo)
335    CALL bcast(rlat_glo)
336    CALL gather(rlon,rlon_glo)
337    CALL bcast(rlon_glo)
338
339!$OMP MASTER
340    DO i=1,pim
341
342!    print*,'CFMIP_iophy i tabij lon lat',i,tabij(i),plon(i),plat(i)
343
344     plon_bounds(i,1)=rlon_glo(tabij(i)-1)
345     plon_bounds(i,2)=rlon_glo(tabij(i)+1)
[2854]346     IF (plon_bounds(i,2).LE.0..AND.plon_bounds(i,1).GE.0.) THEN
347      IF (rlon_glo(tabij(i)).GE.0.) THEN
[1539]348       plon_bounds(i,2)=-1*plon_bounds(i,2)
[2854]349      ENDIF
350     ENDIF
351     IF (plon_bounds(i,2).GE.0..AND.plon_bounds(i,1).LE.0.) THEN
352      IF (rlon_glo(tabij(i)).LE.0.) THEN
[1539]353       plon_bounds(i,2)=-1*plon_bounds(i,2)
[2854]354      ENDIF
355     ENDIF
[1539]356!
[2344]357     IF ( tabij(i).LE.nbp_lon) THEN
[1539]358      plat_bounds(i,1)=rlat_glo(tabij(i))
359     ELSE
[2344]360      plat_bounds(i,1)=rlat_glo(tabij(i)-nbp_lon)
[1539]361     ENDIF
[2344]362     plat_bounds(i,2)=rlat_glo(tabij(i)+nbp_lon)
[1539]363!
364!    print*,'CFMIP_iophy point i lon lon_bds',i,plon_bounds(i,1),rlon_glo(tabij(i)),plon_bounds(i,2)
365!    print*,'CFMIP_iophy point i lat lat_bds',i,plat_bounds(i,1),rlat_glo(tabij(i)),plat_bounds(i,2)
366!
367    ENDDO
368    if (is_sequential) then
369
370     npstn=pim
371     IF(.NOT. ALLOCATED(nptabij)) THEN
372      ALLOCATE(nptabij(pim))
373     ENDIF
374     DO i=1,pim
375      nptabij(i)=tabij(i)
376     ENDDO
377
[3435]378       CALL grid1dTo2d_glo(rlon_glo,zx_lon)
[2854]379       IF ((nbp_lon*nbp_lat).GT.1) THEN
[2344]380       DO i = 1, nbp_lon
[1539]381         zx_lon(i,1) = rlon_glo(i+1)
[2344]382         zx_lon(i,nbp_lat) = rlon_glo(i+1)
[1539]383       ENDDO
[2854]384       ENDIF
[3435]385       CALL grid1dTo2d_glo(rlat_glo,zx_lat)
[1539]386
387    DO i=1,pim
388!    print*,'CFMIP_iophy i tabij lon lat',i,tabij(i),plon(i),plat(i)
389
390     plon_bounds(i,1)=zx_lon(ipt(i)-1,jpt(i))
391     plon_bounds(i,2)=zx_lon(ipt(i)+1,jpt(i))
392
[2854]393     IF (ipt(i).EQ.1) THEN
[2344]394      plon_bounds(i,1)=zx_lon(nbp_lon,jpt(i))
[1539]395      plon_bounds(i,2)=360.+zx_lon(ipt(i)+1,jpt(i))
[2854]396     ENDIF
[1539]397 
[2854]398     IF (ipt(i).EQ.nbp_lon) THEN
[1539]399      plon_bounds(i,2)=360.+zx_lon(1,jpt(i))
[2854]400     ENDIF
[1539]401
402     plat_bounds(i,1)=zx_lat(ipt(i),jpt(i)-1)
403     plat_bounds(i,2)=zx_lat(ipt(i),jpt(i)+1)
404
[2854]405     IF (jpt(i).EQ.1) THEN
[1539]406      plat_bounds(i,1)=zx_lat(ipt(i),1)+0.001
407      plat_bounds(i,2)=zx_lat(ipt(i),1)-0.001
[2854]408     ENDIF
[1539]409 
[2854]410     IF (jpt(i).EQ.nbp_lat) THEN
[2344]411      plat_bounds(i,1)=zx_lat(ipt(i),nbp_lat)+0.001
412      plat_bounds(i,2)=zx_lat(ipt(i),nbp_lat)-0.001
[2854]413     ENDIF
[1539]414!
415!    print*,'CFMIP_iophy point i lon lon_bds',i,plon_bounds(i,1),rlon(tabij(i)),plon_bounds(i,2)
416!    print*,'CFMIP_iophy point i lat lat_bds',i,plat_bounds(i,1),rlat(tabij(i)),plat_bounds(i,2)
417!
418    ENDDO
[1897]419
[2097]420#ifndef CPP_IOIPSL_NO_OUTPUT
[3266]421     CALL histbeg(nname,pim,plon,plon_bounds, &
[1539]422                           plat,plat_bounds, &
423                           itau0, zjulian, dtime, nnhori, nnid_day)
[1852]424#endif
[2854]425    ELSE
[1539]426     npproc=0
427     DO ip=1, pim
428      tabprocbeg=klon_mpi_begin
429      tabprocend=klon_mpi_end
430      IF(tabij(ip).GE.tabprocbeg.AND.tabij(ip).LE.tabprocend) THEN
431       npproc=npproc+1
432       npstn=npproc
433      ENDIF
434     ENDDO
435!    print*,'CFMIP_iophy mpi_rank npstn',mpi_rank,npstn
436     IF(.NOT. ALLOCATED(nptabij)) THEN
437      ALLOCATE(nptabij(npstn))
438      ALLOCATE(npplon(npstn), npplat(npstn))
439      ALLOCATE(npplon_bounds(npstn,2), npplat_bounds(npstn,2))
440     ENDIF
441     npproc=0
442     DO ip=1, pim
443      IF(tabij(ip).GE.tabprocbeg.AND.tabij(ip).LE.tabprocend) THEN
444       npproc=npproc+1
445       nptabij(npproc)=tabij(ip)
446!      print*,'mpi_rank npproc ip plon plat tabij=',mpi_rank,npproc,ip, &
447!      plon(ip),plat(ip),tabij(ip)
448       npplon(npproc)=plon(ip)
449       npplat(npproc)=plat(ip)
450       npplon_bounds(npproc,1)=plon_bounds(ip,1)
451       npplon_bounds(npproc,2)=plon_bounds(ip,2)
452       npplat_bounds(npproc,1)=plat_bounds(ip,1)
453       npplat_bounds(npproc,2)=plat_bounds(ip,2)
454!!!
455!!! print qui sert a reordonner les points stations selon l'ordre CFMIP
456!!! ne pas enlever
457        print*,'iophy_mpi rank ip lon lat',mpi_rank,ip,plon(ip),plat(ip)
458!!!
459      ENDIF
460     ENDDO
[2097]461#ifndef CPP_IOIPSL_NO_OUTPUT
[3266]462     CALL histbeg(nname,npstn,npplon,npplon_bounds, &
[1539]463                            npplat,npplat_bounds, &
464                            itau0,zjulian,dtime,nnhori,nnid_day,phys_domain_id)
[1852]465#endif
[2854]466    ENDIF
[1539]467!$OMP END MASTER
468
[2854]469  END SUBROUTINE histbeg_phy_points
[1807]470
471
472  SUBROUTINE histdef2d_old (iff,lpoint,flag_var,nomvar,titrevar,unitvar)
473
[2854]474    USE ioipsl, ONLY: histdef
[3238]475    USE mod_phys_lmdz_para, ONLY: jj_nb, is_master
[2854]476    USE phys_output_var_mod, ONLY: type_ecri, zoutm, zdtime_moy, lev_files, &
[2989]477                                   nid_files, nhorim, swaero_diag, dryaod_diag, nfiles, &
478                                   ok_4xCO2atm
[2344]479    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
[2854]480    USE aero_mod, ONLY : naero_tot, name_aero_tau
[3238]481    USE print_control_mod, ONLY: prt_level,lunout
[2854]482
[1807]483    IMPLICIT NONE
484
485    INCLUDE "clesphys.h"
486
487    INTEGER                          :: iff
[2854]488    INTEGER                          :: naero
[1807]489    LOGICAL                          :: lpoint
490    INTEGER, DIMENSION(nfiles)       :: flag_var
[2854]491    CHARACTER(LEN=20)                :: nomvar
[1807]492    CHARACTER(LEN=*)                 :: titrevar
493    CHARACTER(LEN=*)                 :: unitvar
494
495    REAL zstophym
496
497    IF (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') THEN
498       zstophym=zoutm(iff)
499    ELSE
500       zstophym=zdtime_moy
501    ENDIF
[3238]502    IF (check_dim .AND. is_master) WRITE(lunout,*)'histdef2d_old for ', nomvar
[1807]503    ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def
504    CALL conf_physoutputs(nomvar,flag_var)
505
506    IF(.NOT.lpoint) THEN 
507       IF ( flag_var(iff)<=lev_files(iff) ) THEN
508          CALL histdef (nid_files(iff),nomvar,titrevar,unitvar, &
[2344]509               nbp_lon,jj_nb,nhorim(iff), 1,1,1, -99, 32, &
[1807]510               type_ecri(iff), zstophym,zoutm(iff))               
511       ENDIF
512    ELSE
513       IF ( flag_var(iff)<=lev_files(iff) ) THEN
514          CALL histdef (nid_files(iff),nomvar,titrevar,unitvar, &
515               npstn,1,nhorim(iff), 1,1,1, -99, 32, &
516               type_ecri(iff), zstophym,zoutm(iff))               
517       ENDIF
518    ENDIF
519
520    ! Set swaero_diag=true if at least one of the concerned variables are defined
[2854]521    IF (nomvar=='topswad' .OR. nomvar=='topswad0' .OR. nomvar=='solswad' .OR. nomvar=='solswad0' .OR. &
522        nomvar=='toplwad' .OR. nomvar=='toplwad0' .OR. nomvar=='sollwad' .OR. nomvar=='sollwad0' .OR. &
523        nomvar=='topswai' .OR. nomvar=='solswai' ) THEN
524       IF  ( flag_var(iff)<=lev_files(iff) ) swaero_diag=.TRUE.
525    ENDIF
[1807]526
[2854]527    ! Set dryaod_diag=true if at least one of the concerned variables are defined
[2856]528    IF (nomvar=='dryod550aer') THEN
529      IF  ( flag_var(iff)<=lev_files(iff) ) dryaod_diag=.TRUE.
530    ENDIF
[2854]531    DO naero = 1, naero_tot-1
532      IF (nomvar=='dryod550_'//name_aero_tau(naero)) THEN
533        IF  ( flag_var(iff)<=lev_files(iff) ) dryaod_diag=.TRUE.
534      ENDIF
535    ENDDO
[1807]536
[2989]537    ! Set ok_4xCO2atm=true if at least one of the concerned variables are
538    ! defined
539    IF (nomvar=='rsut4co2'.OR.nomvar=='rlut4co2'.OR.nomvar=='rsutcs4co2' &
540        .OR. nomvar=='rlutcs4co2'.OR.nomvar=='rsu4co2'.OR.nomvar=='rsucs4co2' &
541        .OR.nomvar=='rsu4co2'.OR.nomvar=='rsucs4co2'.OR.nomvar=='rsd4co2'.OR. &
542        nomvar=='rsdcs4co2'.OR.nomvar=='rlu4co2'.OR.nomvar=='rlucs4co2'.OR.&
543        nomvar=='rld4co2'.OR.nomvar=='rldcs4co2') THEN
544        IF ( flag_var(iff)<=lev_files(iff) ) ok_4xCO2atm=.TRUE.
545    ENDIF
[2854]546  END SUBROUTINE histdef2d_old
[1807]547
548  SUBROUTINE histdef3d_old (iff,lpoint,flag_var,nomvar,titrevar,unitvar)
549
[2854]550    USE ioipsl, ONLY: histdef
551    USE dimphy, ONLY: klev
[3238]552    USE mod_phys_lmdz_para, ONLY: jj_nb, is_master
[2854]553    USE phys_output_var_mod, ONLY: type_ecri, zoutm, lev_files, nid_files, &
[1897]554                                   nhorim, zdtime_moy, levmin, levmax, &
555                                   nvertm, nfiles
[2344]556    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
[3238]557    USE print_control_mod, ONLY: prt_level,lunout
[1807]558    IMPLICIT NONE
559
560    INCLUDE "clesphys.h"
561
562    INTEGER                          :: iff
563    LOGICAL                          :: lpoint
564    INTEGER, DIMENSION(nfiles)       :: flag_var
565    CHARACTER(LEN=20)                 :: nomvar
566    CHARACTER(LEN=*)                 :: titrevar
567    CHARACTER(LEN=*)                 :: unitvar
568
569    REAL zstophym
570
571    ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def
572    CALL conf_physoutputs(nomvar,flag_var)
573
[3238]574    IF (check_dim .AND. is_master) WRITE(lunout,*)'histdef3d_old for ', nomvar
575
[1807]576    IF (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') THEN
577       zstophym=zoutm(iff)
578    ELSE
579       zstophym=zdtime_moy
580    ENDIF
581
582    IF(.NOT.lpoint) THEN
583       IF ( flag_var(iff)<=lev_files(iff) ) THEN
584          CALL histdef (nid_files(iff), nomvar, titrevar, unitvar, &
[2344]585               nbp_lon, jj_nb, nhorim(iff), klev, levmin(iff), &
[1807]586               levmax(iff)-levmin(iff)+1, nvertm(iff), 32, type_ecri(iff), &
587               zstophym, zoutm(iff))
588       ENDIF
589    ELSE
590       IF ( flag_var(iff)<=lev_files(iff) ) THEN
591          CALL histdef (nid_files(iff), nomvar, titrevar, unitvar, &
592               npstn,1,nhorim(iff), klev, levmin(iff), &
593               levmax(iff)-levmin(iff)+1, nvertm(iff), 32, &
594               type_ecri(iff), zstophym,zoutm(iff))
595       ENDIF
596    ENDIF
597  END SUBROUTINE histdef3d_old
598
599  SUBROUTINE histdef2d (iff,var)
600
[2854]601    USE ioipsl, ONLY: histdef
[3238]602    USE mod_phys_lmdz_para, ONLY: jj_nb, is_master
[2854]603    USE phys_output_var_mod, ONLY: ctrl_out, type_ecri_files, zoutm, zdtime_moy, &
[1897]604                                   clef_stations, phys_out_filenames, lev_files, &
[3082]605                                   nid_files, nhorim, swaerofree_diag, swaero_diag, dryaod_diag,&
[2989]606                                   ok_4xCO2atm
[2319]607    USE print_control_mod, ONLY: prt_level,lunout
[2344]608    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
[2854]609    USE aero_mod, ONLY : naero_tot, name_aero_tau
[1897]610#ifdef CPP_XIOS
[2854]611    USE wxios, ONLY: wxios_add_field_to_file
[1897]612#endif
[3238]613    USE print_control_mod, ONLY: prt_level,lunout
[1807]614    IMPLICIT NONE
615
616    INCLUDE "clesphys.h"
617
618    INTEGER                          :: iff
[2854]619    INTEGER                          :: naero
[1807]620    TYPE(ctrl_out)                   :: var
621
622    REAL zstophym
623    CHARACTER(LEN=20) :: typeecrit
624
[3238]625    IF (check_dim .AND. is_master) WRITE(lunout,*)'histdef2d for ', var%name
626
[1807]627    ! ug On récupère le type écrit de la structure:
628    !       Assez moche, à refaire si meilleure méthode...
629    IF (INDEX(var%type_ecrit(iff), "once") > 0) THEN
630       typeecrit = 'once'
631    ELSE IF(INDEX(var%type_ecrit(iff), "t_min") > 0) THEN
632       typeecrit = 't_min(X)'
633    ELSE IF(INDEX(var%type_ecrit(iff), "t_max") > 0) THEN
634       typeecrit = 't_max(X)'
635    ELSE IF(INDEX(var%type_ecrit(iff), "inst") > 0) THEN
636       typeecrit = 'inst(X)'
637    ELSE
638       typeecrit = type_ecri_files(iff)
639    ENDIF
640
641    IF (typeecrit=='inst(X)'.OR.typeecrit=='once') THEN
642       zstophym=zoutm(iff)
643    ELSE
644       zstophym=zdtime_moy
645    ENDIF
646
647    ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def
648    CALL conf_physoutputs(var%name, var%flag)
649
650    IF(.NOT.clef_stations(iff)) THEN 
[1852]651
[1825]652#ifdef CPP_XIOS
[2114]653      IF (.not. ok_all_xml) THEN
654        IF ( var%flag(iff)<=lev_files(iff) ) THEN
655          CALL wxios_add_field_to_file(var%name, 2, iff, phys_out_filenames(iff), &
656          var%description, var%unit, var%flag(iff), typeecrit)
657          IF (prt_level >= 10) THEN
658            WRITE(lunout,*) 'histdef2d: call wxios_add_field_to_file var%name iff: ', &
659                            trim(var%name),iff
660          ENDIF
[2001]661        ENDIF
662      ENDIF
[1825]663#endif
[2097]664#ifndef CPP_IOIPSL_NO_OUTPUT
[1825]665
[1807]666       IF ( var%flag(iff)<=lev_files(iff) ) THEN
667          CALL histdef (nid_files(iff), var%name, var%description, var%unit, &
[2344]668               nbp_lon,jj_nb,nhorim(iff), 1,1,1, -99, 32, &
[1807]669               typeecrit, zstophym,zoutm(iff))               
670       ENDIF
671    ELSE
672       IF ( var%flag(iff)<=lev_files(iff)) THEN
673          CALL histdef (nid_files(iff), var%name, var%description, var%unit, &
674               npstn,1,nhorim(iff), 1,1,1, -99, 32, &
675               typeecrit, zstophym,zoutm(iff))               
676       ENDIF
[1852]677#endif
[1807]678    ENDIF
679
[2854]680    ! Set swaero_diag=true if at least one of the concerned variables are defined
[2529]681    !--OB 30/05/2016 use wider set of variables
682    IF ( var%name=='topswad' .OR. var%name=='topswad0' .OR. var%name=='solswad' .OR. var%name=='solswad0' .OR. &
683         var%name=='topswai' .OR. var%name=='solswai'  .OR. ( iflag_rrtm==1 .AND. (                            &
684         var%name=='toplwad' .OR. var%name=='toplwad0' .OR. var%name=='sollwad' .OR. var%name=='sollwad0' .OR. &
685         var%name=='toplwai' .OR. var%name=='sollwai'  ) ) ) THEN
[2854]686       IF  ( var%flag(iff)<=lev_files(iff) ) swaero_diag=.TRUE.
687    ENDIF
688
[3082]689    ! Set swaerofree_diag=true if at least one of the concerned variables are defined
[3106]690    IF (var%name=='SWupTOAcleanclr' .OR. var%name=='SWupSFCcleanclr' .OR. var%name=='SWdnSFCcleanclr' .OR. &
[3107]691        var%name=='LWupTOAcleanclr' .OR. var%name=='LWdnSFCcleanclr' ) THEN
[3082]692       IF  ( var%flag(iff)<=lev_files(iff) ) swaerofree_diag=.TRUE.
693    ENDIF
694
[2854]695    ! set dryaod_dry=true if at least one of the concerned variables are defined
696    IF (var%name=='dryod550aer') THEN
697      IF  ( var%flag(iff)<=lev_files(iff) ) dryaod_diag=.TRUE.
698    ENDIF
699    !
700    DO naero = 1, naero_tot-1
701      IF (var%name=='dryod550_'//name_aero_tau(naero)) THEN
702        IF  ( var%flag(iff)<=lev_files(iff) ) dryaod_diag=.TRUE.
703      ENDIF
704    ENDDO
[2989]705    ! Set ok_4xCO2atm=true if at least one of the concerned variables are
706    ! defined
707    IF (var%name=='rsut4co2'.OR.var%name=='rlut4co2'.OR.var%name=='rsutcs4co2' &
708        .OR. var%name=='rlutcs4co2'.OR.var%name=='rsu4co2'.OR.var%name=='rsucs4co2' &
709        .OR.var%name=='rsu4co2'.OR.var%name=='rsucs4co2'.OR.var%name=='rsd4co2'.OR. &
710        var%name=='rsdcs4co2'.OR.var%name=='rlu4co2'.OR.var%name=='rlucs4co2'.OR.&
711        var%name=='rld4co2'.OR.var%name=='rldcs4co2') THEN
712        IF ( var%flag(iff)<=lev_files(iff) ) ok_4xCO2atm=.TRUE.
713    ENDIF
[1807]714  END SUBROUTINE histdef2d
[2001]715
[1807]716  SUBROUTINE histdef3d (iff,var)
717
[2854]718    USE ioipsl, ONLY: histdef
719    USE dimphy, ONLY: klev
[3238]720    USE mod_phys_lmdz_para, ONLY: jj_nb, is_master
[2854]721    USE phys_output_var_mod, ONLY: ctrl_out, type_ecri_files, zoutm, zdtime_moy, &
[1897]722                                   clef_stations, phys_out_filenames, lev_files, &
[3266]723                                   nid_files, nhorim, swaerofree_diag, levmin, &
[1897]724                                   levmax, nvertm
[2311]725    USE print_control_mod, ONLY: prt_level,lunout
[2344]726    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
[1897]727#ifdef CPP_XIOS
[2854]728    USE wxios, ONLY: wxios_add_field_to_file
[1897]729#endif
[3238]730    USE print_control_mod, ONLY: prt_level,lunout
[1807]731    IMPLICIT NONE
732
733    INCLUDE "clesphys.h"
734
735    INTEGER                          :: iff
736    TYPE(ctrl_out)                   :: var
737
738    REAL zstophym
739    CHARACTER(LEN=20) :: typeecrit
740
[3238]741    IF (check_dim .AND. is_master) WRITE(lunout,*)'histdef3d for ', var%name
742
[1807]743    ! ug On récupère le type écrit de la structure:
744    !       Assez moche, à refaire si meilleure méthode...
745    IF (INDEX(var%type_ecrit(iff), "once") > 0) THEN
746       typeecrit = 'once'
747    ELSE IF(INDEX(var%type_ecrit(iff), "t_min") > 0) THEN
748       typeecrit = 't_min(X)'
749    ELSE IF(INDEX(var%type_ecrit(iff), "t_max") > 0) THEN
750       typeecrit = 't_max(X)'
751    ELSE IF(INDEX(var%type_ecrit(iff), "inst") > 0) THEN
752       typeecrit = 'inst(X)'
753    ELSE
754       typeecrit = type_ecri_files(iff)
755    ENDIF
756
757    ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def
758    CALL conf_physoutputs(var%name,var%flag)
759
760    IF (typeecrit=='inst(X)'.OR.typeecrit=='once') THEN
761       zstophym=zoutm(iff)
762    ELSE
763       zstophym=zdtime_moy
764    ENDIF
765
766    IF(.NOT.clef_stations(iff)) THEN
[1852]767
[1825]768#ifdef CPP_XIOS
[2114]769       IF (.not. ok_all_xml) THEN
770         IF ( var%flag(iff)<=lev_files(iff) ) THEN
771         CALL wxios_add_field_to_file(var%name, 3, iff, phys_out_filenames(iff), &
772         var%description, var%unit, var%flag(iff), typeecrit)
773           IF (prt_level >= 10) THEN
774             WRITE(lunout,*) 'histdef3d: call wxios_add_field_to_file var%name iff: ', &
775                             trim(var%name),iff
776           ENDIF
777         ENDIF
778       ENDIF
[1825]779#endif
[2097]780#ifndef CPP_IOIPSL_NO_OUTPUT
[1825]781
[1807]782       IF ( var%flag(iff)<=lev_files(iff) ) THEN
783          CALL histdef (nid_files(iff), var%name, var%description, var%unit, &
[2344]784               nbp_lon, jj_nb, nhorim(iff), klev, levmin(iff), &
[1807]785               levmax(iff)-levmin(iff)+1, nvertm(iff), 32, typeecrit, &
786               zstophym, zoutm(iff))
787       ENDIF
788    ELSE
789       IF ( var%flag(iff)<=lev_files(iff)) THEN
790          CALL histdef (nid_files(iff), var%name, var%description, var%unit, &
791               npstn,1,nhorim(iff), klev, levmin(iff), &
792               levmax(iff)-levmin(iff)+1, nvertm(iff), 32, &
793               typeecrit, zstophym,zoutm(iff))
794       ENDIF
[1852]795#endif
[1807]796    ENDIF
[3082]797
798    ! Set swaerofree_diag=true if at least one of the concerned variables are defined
799    IF (var%name=='rsucsaf' .OR. var%name=='rsdcsaf') THEN
800       IF  ( var%flag(iff)<=lev_files(iff) ) swaerofree_diag=.TRUE.
801    ENDIF
802
[1807]803  END SUBROUTINE histdef3d
804
805  SUBROUTINE conf_physoutputs(nam_var,flag_var)
806!!! Lecture des noms et niveau de sortie des variables dans output.def
807    !   en utilisant les routines getin de IOIPSL 
[2854]808    USE ioipsl, ONLY: getin
809    USE phys_output_var_mod, ONLY: nfiles
[2311]810    USE print_control_mod, ONLY: prt_level,lunout
[1807]811    IMPLICIT NONE
812
813    CHARACTER(LEN=20)                :: nam_var
814    INTEGER, DIMENSION(nfiles)      :: flag_var
815
816    IF(prt_level>10) WRITE(lunout,*)'Avant getin: nam_var flag_var ',nam_var,flag_var(:)
817    CALL getin('flag_'//nam_var,flag_var)
818    CALL getin('name_'//nam_var,nam_var)
819    IF(prt_level>10) WRITE(lunout,*)'Apres getin: nam_var flag_var ',nam_var,flag_var(:)
820
821  END SUBROUTINE conf_physoutputs
822
[1539]823 
[1791]824  SUBROUTINE histwrite2d_phy_old(nid,lpoint,name,itau,field)
[3266]825
826    USE dimphy, ONLY: klon
827    USE mod_phys_lmdz_para, ONLY: Gather_omp, grid1Dto2D_mpi, &
828                                  is_sequential, klon_mpi_begin, klon_mpi_end, &
829                                  jj_nb, klon_mpi, is_master
830    USE ioipsl, ONLY: histwrite
831    USE print_control_mod, ONLY: prt_level,lunout
832    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
833
834    IMPLICIT NONE
[629]835   
[2854]836    INTEGER,INTENT(IN) :: nid
837    LOGICAL,INTENT(IN) :: lpoint
838    CHARACTER*(*), INTENT(IN) :: name
839    INTEGER, INTENT(IN) :: itau
[1797]840    REAL,DIMENSION(:),INTENT(IN) :: field
841    REAL,DIMENSION(klon_mpi) :: buffer_omp
842    INTEGER, allocatable, DIMENSION(:) :: index2d
[2344]843    REAL :: Field2d(nbp_lon,jj_nb)
[1331]844
[2854]845    INTEGER :: ip
846    REAL,ALLOCATABLE,DIMENSION(:) :: fieldok
[1539]847
[2311]848    IF (size(field)/=klon) CALL abort_physic('iophy::histwrite2d','Field first DIMENSION not equal to klon',1)
[3238]849    IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite2d_phy_old for ', name
850
[776]851    CALL Gather_omp(field,buffer_omp)   
[766]852!$OMP MASTER
[1331]853    CALL grid1Dto2D_mpi(buffer_omp,Field2d)
[3266]854    IF (.NOT.lpoint) THEN
[2344]855     ALLOCATE(index2d(nbp_lon*jj_nb))
856     ALLOCATE(fieldok(nbp_lon*jj_nb))
[1897]857     IF (prt_level >= 10) write(lunout,*)'Sending ',name,' to IOIPSL'
[2344]858     CALL histwrite(nid,name,itau,Field2d,nbp_lon*jj_nb,index2d)
[1897]859     IF (prt_level >= 10) write(lunout,*)'Finished sending ',name,' to IOIPSL'
[2854]860    ELSE
[1539]861     ALLOCATE(fieldok(npstn))
862     ALLOCATE(index2d(npstn))
863
[2854]864     IF (is_sequential) THEN
[1539]865!     klon_mpi_begin=1
866!     klon_mpi_end=klon
867      DO ip=1, npstn
868       fieldok(ip)=buffer_omp(nptabij(ip))
869      ENDDO
[2854]870     ELSE
[1539]871      DO ip=1, npstn
872!     print*,'histwrite2d is_sequential npstn ip name nptabij',npstn,ip,name,nptabij(ip)
873       IF(nptabij(ip).GE.klon_mpi_begin.AND. &
874          nptabij(ip).LE.klon_mpi_end) THEN
875         fieldok(ip)=buffer_omp(nptabij(ip)-klon_mpi_begin+1)
876       ENDIF
877      ENDDO
[2854]878     ENDIF
[1897]879     IF (prt_level >= 10) write(lunout,*)'Sending ',name,' to IOIPSL'
[1539]880     CALL histwrite(nid,name,itau,fieldok,npstn,index2d)
[1897]881     IF (prt_level >= 10) write(lunout,*)'Finished sending ',name,' to IOIPSL'
[1539]882!
[2854]883    ENDIF
884    DEALLOCATE(index2d)
885    DEALLOCATE(fieldok)
[1791]886!$OMP END MASTER   
[1331]887
[1791]888 
[2854]889  END SUBROUTINE histwrite2d_phy_old
[1791]890
[1797]891  SUBROUTINE histwrite3d_phy_old(nid,lpoint,name,itau,field)
[3266]892
893    USE dimphy, ONLY: klon
894    USE mod_phys_lmdz_para, ONLY: Gather_omp, grid1Dto2D_mpi, &
895                                  is_sequential, klon_mpi_begin, klon_mpi_end, &
896                                  jj_nb, klon_mpi, is_master
897    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
898    USE ioipsl, ONLY: histwrite
899    USE print_control_mod, ONLY: prt_level,lunout
900
901    IMPLICIT NONE
[629]902   
[2854]903    INTEGER,INTENT(IN) :: nid
904    LOGICAL,INTENT(IN) :: lpoint
905    CHARACTER*(*), INTENT(IN) :: name
906    INTEGER, INTENT(IN) :: itau
[1797]907    REAL,DIMENSION(:,:),INTENT(IN) :: field  ! --> field(klon,:)
908    REAL,DIMENSION(klon_mpi,size(field,2)) :: buffer_omp
[2344]909    REAL :: Field3d(nbp_lon,jj_nb,size(field,2))
[1539]910    INTEGER :: ip, n, nlev
[1797]911    INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d
912    REAL,allocatable, DIMENSION(:,:) :: fieldok
[1539]913
[3238]914    IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite3d_phy_old for ', name
[1791]915
[2311]916    IF (size(field,1)/=klon) CALL abort_physic('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)
[1331]917    nlev=size(field,2)
[1539]918
[776]919    CALL Gather_omp(field,buffer_omp)
[766]920!$OMP MASTER
[1331]921    CALL grid1Dto2D_mpi(buffer_omp,field3d)
[2854]922    IF (.NOT.lpoint) THEN
[3266]923      ALLOCATE(index3d(nbp_lon*jj_nb*nlev))
924      ALLOCATE(fieldok(nbp_lon*jj_nb,nlev))
925      IF (prt_level >= 10) write(lunout,*)'Sending ',name,' to IOIPSL'
926      CALL histwrite(nid,name,itau,Field3d,nbp_lon*jj_nb*nlev,index3d)
927      IF (prt_level >= 10) write(lunout,*)'Finished sending ',name,' to IOIPSL'
928    ELSE
[1539]929      nlev=size(field,2)
930      ALLOCATE(index3d(npstn*nlev))
931      ALLOCATE(fieldok(npstn,nlev))
932
[2854]933      IF (is_sequential) THEN
[3266]934!       klon_mpi_begin=1
935!       klon_mpi_end=klon
936        DO n=1, nlev
937        DO ip=1, npstn
938          fieldok(ip,n)=buffer_omp(nptabij(ip),n)
939        ENDDO
940        ENDDO
[2854]941      ELSE
[3266]942        DO n=1, nlev
943        DO ip=1, npstn
944          IF(nptabij(ip).GE.klon_mpi_begin.AND. &
945           nptabij(ip).LE.klon_mpi_end) THEN
946           fieldok(ip,n)=buffer_omp(nptabij(ip)-klon_mpi_begin+1,n)
947          ENDIF
948        ENDDO
949        ENDDO
[2854]950      ENDIF
[1897]951      IF (prt_level >= 10) write(lunout,*)'Sending ',name,' to IOIPSL'
[1539]952      CALL histwrite(nid,name,itau,fieldok,npstn*nlev,index3d)
[1897]953      IF (prt_level >= 10) write(lunout,*)'Finished sending ',name,' to IOIPSL'
[2854]954    ENDIF
[3266]955    DEALLOCATE(index3d)
956    DEALLOCATE(fieldok)
[766]957!$OMP END MASTER   
[1791]958
[2854]959  END SUBROUTINE histwrite3d_phy_old
[1791]960
961
962! ug NOUVELLE VERSION DES WRITE AVEC LA BOUCLE DO RENTREE
963  SUBROUTINE histwrite2d_phy(var,field, STD_iff)
[3266]964
965  USE mod_phys_lmdz_omp_transfert, ONLY: bcast_omp
[3003]966  USE dimphy, ONLY: klon, klev
[2854]967  USE mod_phys_lmdz_para, ONLY: gather_omp, grid1dto2d_mpi, &
[1897]968                                jj_nb, klon_mpi, klon_mpi_begin, &
[3238]969                                klon_mpi_end, is_sequential, is_master
[2854]970  USE ioipsl, ONLY: histwrite
971  USE phys_output_var_mod, ONLY: ctrl_out, clef_files, lev_files, &
[1897]972                                 nfiles, vars_defined, clef_stations, &
[3266]973                                 nid_files, swaerofree_diag, swaero_diag, dryaod_diag, ok_4xCO2atm
[2311]974  USE print_control_mod, ONLY: prt_level,lunout
[3435]975  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid_type, unstructured, regular_lonlat
[1791]976#ifdef CPP_XIOS
[2854]977  USE xios, ONLY: xios_send_field
[1791]978#endif
[3435]979  USE print_control_mod, ONLY: lunout, prt_level
[1791]980
981  IMPLICIT NONE
[3266]982  INCLUDE 'clesphys.h'
[1791]983
[3266]984  TYPE(ctrl_out), INTENT(IN) :: var
985  REAL, DIMENSION(:), INTENT(IN) :: field
986  INTEGER, INTENT(IN), OPTIONAL :: STD_iff ! ug RUSTINE POUR LES STD LEVS.....
[1791]987     
[3266]988  INTEGER :: iff, iff_beg, iff_end
989  LOGICAL, SAVE  :: firstx
[2001]990!$OMP THREADPRIVATE(firstx)
991
[3266]992  REAL,DIMENSION(klon_mpi) :: buffer_omp
993  INTEGER, allocatable, DIMENSION(:) :: index2d
994  REAL :: Field2d(nbp_lon,jj_nb)
[1791]995
[3266]996  INTEGER :: ip
997  REAL, ALLOCATABLE, DIMENSION(:) :: fieldok
[1791]998
[3266]999  IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite2d_phy for ',trim(var%name)
[3238]1000
[3266]1001  IF (prt_level >= 10) THEN
1002    WRITE(lunout,*)'Begin histwrite2d_phy for ',trim(var%name)
1003  ENDIF
1004
[1791]1005! ug RUSTINE POUR LES STD LEVS.....
[3266]1006  IF (PRESENT(STD_iff)) THEN
1007        iff_beg = STD_iff
1008        iff_end = STD_iff
1009  ELSE
1010        iff_beg = 1
1011        iff_end = nfiles
1012  ENDIF
[1791]1013
[1807]1014  ! On regarde si on est dans la phase de définition ou d'écriture:
[2854]1015  IF (.NOT.vars_defined) THEN
[1821]1016!$OMP MASTER
[1807]1017      !Si phase de définition.... on définit
[2114]1018      IF (.not. ok_all_xml) THEN
[2854]1019      IF (prt_level >= 10) THEN
[3435]1020      write(lunout,*)"histwrite2d_phy: .not.vars_defined ; time to define ", &
1021                     trim(var%name)
[2854]1022      ENDIF
[1807]1023      DO iff=iff_beg, iff_end
1024         IF (clef_files(iff)) THEN
1025            CALL histdef2d(iff, var)
1026         ENDIF
1027      ENDDO
[2114]1028      ENDIF
[1821]1029!$OMP END MASTER
[3266]1030!--broadcasting the flags that have been changed in histdef2d on OMP masters
1031      CALL bcast_omp(swaero_diag)
1032      CALL bcast_omp(swaerofree_diag)
1033      CALL bcast_omp(dryaod_diag)
1034      CALL bcast_omp(ok_4xCO2atm)
1035
[1807]1036  ELSE
1037
1038    !Et sinon on.... écrit
[3003]1039    IF (SIZE(field)/=klon .AND. SIZE(field)/=klev) CALL abort_physic('iophy::histwrite2d_phy','Field first DIMENSION not equal to klon/klev',1)   
[2854]1040    IF (prt_level >= 10) THEn
1041      WRITE (lunout,*)"histwrite2d_phy: .not.vars_defined ; time to gather and write ", trim(var%name)
1042    ENDIF
[1897]1043   
[3003]1044   
1045    IF (SIZE(field) == klon) then
1046        CALL Gather_omp(field,buffer_omp)
1047    ELSE
1048        buffer_omp(:)=0.
1049    ENDIF
[1791]1050!$OMP MASTER
[3435]1051    IF (grid_type==regular_lonlat) CALL grid1Dto2D_mpi(buffer_omp,Field2d)
[1897]1052
[1791]1053! La boucle sur les fichiers:
[2001]1054      firstx=.true.
[2114]1055
1056      IF (ok_all_xml) THEN
1057#ifdef CPP_XIOS
[2854]1058          IF (prt_level >= 10) THEN
1059             write(lunout,*)'Dans iophy histwrite2D,var%name ', trim(var%name)                       
1060          ENDIF
[3435]1061         
1062          IF (grid_type==regular_lonlat) THEN
1063            IF (SIZE(field) == klon) then
[3003]1064              CALL xios_send_field(var%name, Field2d)
[3435]1065            ELSE
1066               CALL xios_send_field(var%name, field)
1067            ENDIF
1068          ELSE IF (grid_type==unstructured) THEN
1069            CALL xios_send_field(var%name, buffer_omp)
1070          ENDIF
[2854]1071          IF (prt_level >= 10) THEN
[3435]1072             write(lunout,*)'Dans iophy histwrite2D,var%name apres xios_send ',&
1073                             trim(var%name)                       
[2854]1074          ENDIF
[2114]1075#else
[2311]1076        CALL abort_physic ('iophy','cannot have ok_all_xml = .T. without CPP_XIOS defined' ,1)
[2114]1077#endif
1078      ELSE 
1079        DO iff=iff_beg, iff_end
[1791]1080            IF (var%flag(iff) <= lev_files(iff) .AND. clef_files(iff)) THEN
[2001]1081
1082#ifdef CPP_XIOS
1083               IF (firstx) THEN
[2854]1084                  IF (prt_level >= 10) THEN
[3435]1085                     write(lunout,*)'Dans iophy histwrite2D,iff,var%name ',&
1086                                    iff,trim(var%name)                       
1087                     write(lunout,*)"histwrite2d_phy:.NOT.clef_stations(iff)and iff==iff_beg, call xios_send_field"
[2854]1088                  ENDIF
[3435]1089                  IF (grid_type==regular_lonlat) THEN
1090                    IF (SIZE(field) == klon) then
1091                       CALL xios_send_field(var%name, Field2d)
1092                    ELSE
1093                       CALL xios_send_field(var%name, field)
1094                    ENDIF
1095                  ELSE IF (grid_type==unstructured) THEN
1096                    CALL xios_send_field(var%name, buffer_omp)
[3003]1097                  ENDIF
[3435]1098
[2001]1099                  firstx=.false.
1100               ENDIF
1101#endif
1102
[2854]1103                  IF (.NOT.clef_stations(iff)) THEN
[2344]1104                        ALLOCATE(index2d(nbp_lon*jj_nb))
1105                        ALLOCATE(fieldok(nbp_lon*jj_nb))
[2097]1106#ifndef CPP_IOIPSL_NO_OUTPUT
[2344]1107                        CALL histwrite(nid_files(iff),var%name,itau_iophy,Field2d,nbp_lon*jj_nb,index2d)
[1852]1108#endif
[2001]1109!#ifdef CPP_XIOS
1110!                        IF (iff == iff_beg) THEN
[3435]1111!                          IF (prt_level >= 10) THEN
[2002]1112!                            write(lunout,*)"histwrite2d_phy: .NOT.clef_stations(iff) and iff==iff_beg, call xios_send_field"
[3435]1113!                          ENDIF
[2002]1114!                          CALL xios_send_field(var%name, Field2d)
[2001]1115!                        ENDIF
1116!#endif
[1791]1117                  ELSE
1118                        ALLOCATE(fieldok(npstn))
1119                        ALLOCATE(index2d(npstn))
1120
1121                        IF (is_sequential) THEN
[1897]1122                          DO ip=1, npstn
1123                            fieldok(ip)=buffer_omp(nptabij(ip))
1124                          ENDDO
1125                        ELSE
[1791]1126                              DO ip=1, npstn
[1897]1127                                write(lunout,*)'histwrite2d_phy is_sequential npstn ip namenptabij',npstn,ip,var%name,nptabij(ip)
[1791]1128                                     IF(nptabij(ip).GE.klon_mpi_begin.AND. &
1129                                        nptabij(ip).LE.klon_mpi_end) THEN
1130                                       fieldok(ip)=buffer_omp(nptabij(ip)-klon_mpi_begin+1)
1131                                     ENDIF
1132                              ENDDO
[1897]1133                       ENDIF ! of IF (is_sequential)
[2097]1134#ifndef CPP_IOIPSL_NO_OUTPUT
[3435]1135                       IF (prt_level >= 10) THEN
[1897]1136                         write(lunout,*)"histwrite2d_phy: clef_stations(iff) and iff==iff_beg, call wxios_write_2D"
[2854]1137                       ENDIF
[1791]1138                       CALL histwrite(nid_files(iff),var%name,itau_iophy,fieldok,npstn,index2d)
[1852]1139#endif
[1897]1140                  ENDIF ! of IF(.NOT.clef_stations(iff))
[1791]1141                 
[2854]1142                DEALLOCATE(index2d)
1143                DEALLOCATE(fieldok)
[1791]1144            ENDIF !levfiles
[2114]1145        ENDDO ! of DO iff=iff_beg, iff_end
1146      ENDIF
[1791]1147!$OMP END MASTER   
[1807]1148  ENDIF ! vars_defined
[3266]1149
[1897]1150  IF (prt_level >= 10) WRITE(lunout,*)'End histwrite2d_phy ',trim(var%name)
[3266]1151
[1791]1152  END SUBROUTINE histwrite2d_phy
1153
1154
1155! ug NOUVELLE VERSION DES WRITE AVEC LA BOUCLE DO RENTREE
[1807]1156  SUBROUTINE histwrite3d_phy(var, field, STD_iff)
[3266]1157
1158  USE mod_phys_lmdz_omp_transfert, ONLY: bcast_omp
[2854]1159  USE dimphy, ONLY: klon, klev
1160  USE mod_phys_lmdz_para, ONLY: gather_omp, grid1dto2d_mpi, &
[1897]1161                                jj_nb, klon_mpi, klon_mpi_begin, &
[3238]1162                                klon_mpi_end, is_sequential, is_master
[2854]1163  USE ioipsl, ONLY: histwrite
1164  USE phys_output_var_mod, ONLY: ctrl_out, clef_files, lev_files, &
[1897]1165                                 nfiles, vars_defined, clef_stations, &
[3266]1166                                 nid_files, swaerofree_diag
[3435]1167  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid_type, regular_lonlat, unstructured
[1791]1168#ifdef CPP_XIOS
[2854]1169  USE xios, ONLY: xios_send_field
[1791]1170#endif
[2311]1171  USE print_control_mod, ONLY: prt_level,lunout
[1791]1172
1173  IMPLICIT NONE
[3266]1174  INCLUDE 'clesphys.h'
[1791]1175
[3266]1176  TYPE(ctrl_out), INTENT(IN) :: var
1177  REAL, DIMENSION(:,:), INTENT(IN) :: field ! --> field(klon,:)
1178  INTEGER, INTENT(IN), OPTIONAL :: STD_iff ! ug RUSTINE POUR LES STD LEVS.....
[1807]1179     
[3266]1180  INTEGER :: iff, iff_beg, iff_end
1181  LOGICAL, SAVE  :: firstx
[2001]1182!$OMP THREADPRIVATE(firstx)
[3266]1183  REAL,DIMENSION(klon_mpi,SIZE(field,2)) :: buffer_omp
1184  REAL :: Field3d(nbp_lon,jj_nb,SIZE(field,2))
1185  INTEGER :: ip, n, nlev, nlevx
1186  INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d
1187  REAL,ALLOCATABLE, DIMENSION(:,:) :: fieldok
[1791]1188
[3238]1189  IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite3d_phy for ', trim(var%name)
1190
[1897]1191  IF (prt_level >= 10) write(lunout,*)'Begin histrwrite3d ',var%name
[1791]1192
[1828]1193! ug RUSTINE POUR LES STD LEVS.....
1194      IF (PRESENT(STD_iff)) THEN
1195            iff_beg = STD_iff
1196            iff_end = STD_iff
1197      ELSE
1198            iff_beg = 1
1199            iff_end = nfiles
[2854]1200      ENDIF
[1828]1201
[1807]1202  ! On regarde si on est dans la phase de définition ou d'écriture:
[3266]1203  IF (.NOT.vars_defined) THEN
[1807]1204      !Si phase de définition.... on définit
[1821]1205!$OMP MASTER
[1828]1206      DO iff=iff_beg, iff_end
[1807]1207        IF (clef_files(iff)) THEN
1208          CALL histdef3d(iff, var)
1209        ENDIF
1210      ENDDO
[1821]1211!$OMP END MASTER
[3266]1212!--broadcasting the flag that have been changed in histdef3d on OMP masters
1213      CALL bcast_omp(swaerofree_diag)
[1807]1214  ELSE
1215    !Et sinon on.... écrit
[3003]1216
1217    IF (SIZE(field,1)/=klon .AND. SIZE(field,1)/=klev) CALL abort_physic('iophy::histwrite3d_xios','Field first DIMENSION not equal to klon/klev',1)
1218
[1807]1219    nlev=SIZE(field,2)
[2854]1220    IF (nlev.EQ.klev+1) THEN
[2001]1221        nlevx=klev
[2854]1222    ELSE
[2001]1223        nlevx=nlev
[2854]1224    ENDIF
[1791]1225
[3003]1226    IF (SIZE(field,1) == klon) then
1227        CALL Gather_omp(field,buffer_omp)
1228    ELSE
1229        buffer_omp(:,:)=0.
1230    ENDIF
[1791]1231!$OMP MASTER
[3435]1232    IF (grid_type==regular_lonlat) CALL grid1Dto2D_mpi(buffer_omp,field3d)
[1791]1233
1234! BOUCLE SUR LES FICHIERS
[3266]1235    firstx=.true.
[2114]1236
[3266]1237    IF (ok_all_xml) THEN
[2114]1238#ifdef CPP_XIOS
[3435]1239          IF (prt_level >= 10) THEN
1240             write(lunout,*)'Dans iophy histwrite3D,var%name ',&
1241                             trim(var%name)                       
1242          ENDIF
1243          IF (grid_type==regular_lonlat) THEN
1244            IF (SIZE(field,1) == klon) then
1245               CALL xios_send_field(var%name, Field3d(:,:,1:nlevx))
1246            ELSE
1247               CALL xios_send_field(var%name, field)
1248            ENDIF
1249          ELSE IF (grid_type==unstructured) THEN
1250            CALL xios_send_field(var%name, buffer_omp(:,1:nlevx))
[3266]1251        ENDIF
[3435]1252
[2114]1253#else
[2311]1254        CALL abort_physic ('iophy','cannot have ok_all_xml = .T. without CPP_XIOS defined' ,1)
[2114]1255#endif
[3266]1256    ELSE 
[2114]1257
[3266]1258      DO iff=iff_beg, iff_end
1259          IF (var%flag(iff) <= lev_files(iff) .AND. clef_files(iff)) THEN
[2001]1260#ifdef CPP_XIOS
1261              IF (firstx) THEN
[3435]1262                IF (prt_level >= 10) THEN
1263                  write(lunout,*)'Dans iophy, histwrite3D iff nlev klev firstx', &
[2001]1264                                  iff,nlev,klev, firstx                       
[3435]1265                  write(lunout,*)'histwrite3d_phy: call xios_send_field for ', &
[2001]1266                                  trim(var%name), ' with iim jjm nlevx = ', &
[2344]1267                                  nbp_lon,jj_nb,nlevx
[2854]1268                ENDIF
[3435]1269                IF (grid_type==regular_lonlat) THEN
1270                  IF (SIZE(field,1) == klon) then
1271                      CALL xios_send_field(var%name, Field3d(:,:,1:nlevx))
1272                  ELSE
1273                       CALL xios_send_field(var%name, field)
1274                  ENDIF
1275                ELSE IF (grid_type==unstructured) THEN
1276                  CALL xios_send_field(var%name, buffer_omp(:,1:nlevx))
[3003]1277                ENDIF
[3435]1278
[3003]1279                firstx=.false.
[2001]1280              ENDIF
1281#endif
[3266]1282              IF (.NOT.clef_stations(iff)) THEN
[2344]1283                        ALLOCATE(index3d(nbp_lon*jj_nb*nlev))
1284                        ALLOCATE(fieldok(nbp_lon*jj_nb,nlev))
[1852]1285
[2097]1286#ifndef CPP_IOIPSL_NO_OUTPUT
[2344]1287                        CALL histwrite(nid_files(iff),var%name,itau_iophy,Field3d,nbp_lon*jj_nb*nlev,index3d)
[1852]1288#endif
[1825]1289
[2001]1290!#ifdef CPP_XIOS
1291!                        IF (iff == 1) THEN
[2002]1292!                              CALL xios_send_field(var%name, Field3d(:,:,1:klev))
[2001]1293!                        ENDIF
1294!#endif
1295!                       
[3266]1296              ELSE
[1791]1297                        nlev=size(field,2)
1298                        ALLOCATE(index3d(npstn*nlev))
1299                        ALLOCATE(fieldok(npstn,nlev))
1300
1301                        IF (is_sequential) THEN
1302                              DO n=1, nlev
1303                                    DO ip=1, npstn
1304                                          fieldok(ip,n)=buffer_omp(nptabij(ip),n)
1305                                    ENDDO
1306                              ENDDO
1307                        ELSE
1308                              DO n=1, nlev
1309                                    DO ip=1, npstn
1310                                                IF(nptabij(ip).GE.klon_mpi_begin.AND. &
1311                                                      nptabij(ip).LE.klon_mpi_end) THEN
1312                                                fieldok(ip,n)=buffer_omp(nptabij(ip)-klon_mpi_begin+1,n)
1313                                          ENDIF
1314                                    ENDDO
1315                              ENDDO
1316                        ENDIF
[2097]1317#ifndef CPP_IOIPSL_NO_OUTPUT
[1791]1318                        CALL histwrite(nid_files(iff),var%name,itau_iophy,fieldok,npstn*nlev,index3d)
[1852]1319#endif
[3266]1320              ENDIF
1321              DEALLOCATE(index3d)
1322              DEALLOCATE(fieldok)
1323          ENDIF
[1791]1324      ENDDO
[3266]1325    ENDIF
[1791]1326!$OMP END MASTER   
[1807]1327  ENDIF ! vars_defined
[3266]1328
[1897]1329  IF (prt_level >= 10) write(lunout,*)'End histrwrite3d ',var%name
[3266]1330
[1791]1331  END SUBROUTINE histwrite3d_phy
1332 
[1852]1333
1334! VERSION DES HISTWRITE DEDIEES AU TOUT-XIOS-XML DEJA UTILISEE DANS PHYDEV
1335#ifdef CPP_XIOS
1336  SUBROUTINE histwrite2d_xios(field_name,field)
[3266]1337
[3003]1338  USE dimphy, ONLY: klon, klev
[2854]1339  USE mod_phys_lmdz_para, ONLY: gather_omp, grid1Dto2D_mpi, &
[1897]1340                                is_sequential, klon_mpi_begin, klon_mpi_end, &
[3238]1341                                jj_nb, klon_mpi, is_master
[3435]1342  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid_type, unstructured
[2854]1343  USE xios, ONLY: xios_send_field
[2311]1344  USE print_control_mod, ONLY: prt_level,lunout
[1852]1345
1346  IMPLICIT NONE
1347
[3266]1348  CHARACTER(LEN=*), INTENT(IN) :: field_name
1349  REAL, DIMENSION(:), INTENT(IN) :: field
[1852]1350     
[3266]1351  REAL,DIMENSION(klon_mpi) :: buffer_omp
1352  INTEGER, allocatable, DIMENSION(:) :: index2d
1353  REAL :: Field2d(nbp_lon,jj_nb)
[1852]1354
[3266]1355  INTEGER :: ip
1356  REAL, ALLOCATABLE, DIMENSION(:) :: fieldok
[1852]1357
[3266]1358  IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite2d_xios for ', field_name
[3238]1359
[3266]1360  IF (prt_level >= 10) WRITE(lunout,*)'Begin histrwrite2d_xios ',field_name
[1852]1361
[3266]1362  !Et sinon on.... écrit
1363  IF (SIZE(field)/=klon .AND. SIZE(field)/=klev) CALL abort_physic('iophy::histwrite2d_xios','Field first DIMENSION not equal to klon/klev',1)
[1852]1364   
[3266]1365  IF (SIZE(field) == klev) then
[1852]1366!$OMP MASTER
[3003]1367        CALL xios_send_field(field_name,field)
1368!$OMP END MASTER   
[3266]1369  ELSE
[3003]1370        CALL Gather_omp(field,buffer_omp)   
1371!$OMP MASTER
[3435]1372
1373      IF (grid_type==unstructured) THEN
1374 
1375        CALL xios_send_field(field_name, buffer_omp)
1376
1377      ELSE
1378
[3003]1379        CALL grid1Dto2D_mpi(buffer_omp,Field2d)
[1852]1380   
1381!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1382!ATTENTION, STATIONS PAS GEREES !
1383!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1384    !IF(.NOT.clef_stations(iff)) THEN
[3003]1385        IF (.TRUE.) THEN
1386   
1387            CALL xios_send_field(field_name, Field2d)
1388   
1389        ELSE
1390            ALLOCATE(fieldok(npstn))
1391            ALLOCATE(index2d(npstn))
1392   
1393            IF (is_sequential) THEN
1394                DO ip=1, npstn
1395                    fieldok(ip)=buffer_omp(nptabij(ip))
1396                ENDDO
1397            ELSE
1398                DO ip=1, npstn
1399                    PRINT*,'histwrite2d_xios is_sequential npstn ip namenptabij',npstn,ip,field_name,nptabij(ip)
1400                    IF(nptabij(ip).GE.klon_mpi_begin.AND. &
1401                    nptabij(ip).LE.klon_mpi_end) THEN
1402                        fieldok(ip)=buffer_omp(nptabij(ip)-klon_mpi_begin+1)
1403                    ENDIF
1404                ENDDO
1405            ENDIF
[3435]1406            DEALLOCATE(index2d)
1407            DEALLOCATE(fieldok)
[3003]1408   
[3435]1409        ENDIF                 
1410      ENDIF
[1852]1411!$OMP END MASTER   
[3266]1412  ENDIF
[1852]1413
[1897]1414  IF (prt_level >= 10) WRITE(lunout,*)'End histrwrite2d_xios ',field_name
[1852]1415  END SUBROUTINE histwrite2d_xios
1416
1417
1418! ug NOUVELLE VERSION DES WRITE AVEC LA BOUCLE DO RENTREE
1419  SUBROUTINE histwrite3d_xios(field_name, field)
[3266]1420
[2854]1421  USE dimphy, ONLY: klon, klev
1422  USE mod_phys_lmdz_para, ONLY: gather_omp, grid1Dto2D_mpi, &
[1897]1423                                is_sequential, klon_mpi_begin, klon_mpi_end, &
[3238]1424                                jj_nb, klon_mpi, is_master
[2854]1425  USE xios, ONLY: xios_send_field
[3435]1426  USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid_type, unstructured
[2311]1427  USE print_control_mod, ONLY: prt_level,lunout
[1852]1428
1429  IMPLICIT NONE
1430
[3266]1431  CHARACTER(LEN=*), INTENT(IN) :: field_name
1432  REAL, DIMENSION(:,:), INTENT(IN) :: field ! --> field(klon,:)
[1852]1433
[3266]1434  REAL,DIMENSION(klon_mpi,SIZE(field,2)) :: buffer_omp
1435  REAL :: Field3d(nbp_lon,jj_nb,SIZE(field,2))
1436  INTEGER :: ip, n, nlev
1437  INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d
1438  REAL,ALLOCATABLE, DIMENSION(:,:) :: fieldok
[1852]1439
[3266]1440  IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite3d_xios for ', field_name
[1852]1441
[3266]1442  IF (prt_level >= 10) write(lunout,*)'Begin histrwrite3d_xios ',field_name
[3238]1443
[3266]1444  !Et on.... écrit
1445  IF (SIZE(field,1)/=klon .AND. SIZE(field,1)/=klev) CALL abort_physic('iophy::histwrite3d_xios','Field first DIMENSION not equal to klon/klev',1)
[3003]1446   
[3266]1447  IF (SIZE(field,1) == klev) then
[3003]1448!$OMP MASTER
1449        CALL xios_send_field(field_name,field)
1450!$OMP END MASTER   
[3266]1451  ELSE
[3003]1452        nlev=SIZE(field,2)
[1852]1453
1454
[3003]1455        CALL Gather_omp(field,buffer_omp)
[1852]1456!$OMP MASTER
[3435]1457
1458    IF (grid_type==unstructured) THEN
1459
1460      CALL xios_send_field(field_name, buffer_omp(:,1:nlev))
1461
1462    ELSE
[3003]1463        CALL grid1Dto2D_mpi(buffer_omp,field3d)
[1852]1464
1465!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1466!ATTENTION, STATIONS PAS GEREES !
1467!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1468    !IF (.NOT.clef_stations(iff)) THEN
[3003]1469        IF(.TRUE.)THEN
[3435]1470
1471           CALL xios_send_field(field_name, Field3d(:,:,1:nlev))
[3003]1472                           
1473        ELSE
1474            nlev=size(field,2)
1475            ALLOCATE(index3d(npstn*nlev))
1476            ALLOCATE(fieldok(npstn,nlev))
1477   
1478            IF (is_sequential) THEN
1479                DO n=1, nlev
1480                    DO ip=1, npstn
1481                        fieldok(ip,n)=buffer_omp(nptabij(ip),n)
1482                    ENDDO
[1852]1483                ENDDO
[3003]1484            ELSE
1485                DO n=1, nlev
1486                    DO ip=1, npstn
1487                        IF(nptabij(ip).GE.klon_mpi_begin.AND. &
1488                        nptabij(ip).LE.klon_mpi_end) THEN
1489                            fieldok(ip,n)=buffer_omp(nptabij(ip)-klon_mpi_begin+1,n)
1490                        ENDIF
1491                    ENDDO
[1852]1492                ENDDO
[3003]1493            ENDIF
[3435]1494            DEALLOCATE(index3d)
1495            DEALLOCATE(fieldok)
[3003]1496        ENDIF
[3435]1497      ENDIF
[1852]1498!$OMP END MASTER   
[3266]1499  ENDIF
[1852]1500
[1897]1501  IF (prt_level >= 10) write(lunout,*)'End histrwrite3d_xios ',field_name
[3266]1502
[1852]1503  END SUBROUTINE histwrite3d_xios
[2645]1504
[2660]1505#ifdef CPP_XIOS
[2645]1506  SUBROUTINE histwrite0d_xios(field_name, field)
[2854]1507  USE xios, ONLY: xios_send_field
[3238]1508  USE mod_phys_lmdz_para, ONLY: is_master
1509  USE print_control_mod, ONLY: prt_level,lunout
[2645]1510  IMPLICIT NONE
1511
[3266]1512  CHARACTER(LEN=*), INTENT(IN) :: field_name
1513  REAL, INTENT(IN) :: field ! --> scalar
[2645]1514
[3266]1515  IF (check_dim .AND. is_master) WRITE(lunout,*)'histwrite0d_xios for ', field_name
[3238]1516
[2645]1517!$OMP MASTER
[3266]1518  CALL xios_send_field(field_name, field)
[2645]1519!$OMP END MASTER
1520
1521  END SUBROUTINE histwrite0d_xios
[1852]1522#endif
[2660]1523
1524#endif
[3266]1525END MODULE iophy
Note: See TracBrowser for help on using the repository browser.