source: LMDZ5/trunk/libf/phylmd/iophy.F90 @ 2993

Last change on this file since 2993 was 2989, checked in by musat, 7 years ago

The 4co2 output fields are now managed by the XIOS server via
file*lmdz*xml files and the ok_4xCO2atm logical flag.
ok_4xCO2atm is initialized to TRUE if

  • one of the 4co2 variables (rsut4cO2, rlut4co2, etc) are asked for

by XIOS sefrver or

  • if one of the perturbed GES concentration (RCO2_per, RCH4_per, etc)

is different from the actual (RCO2, RCH4, etc) GES concentration.

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