8 REAL,
allocatable,
dimension(:),
save ::
io_lat
9 REAL,
allocatable,
dimension(:),
save ::
io_lon
12 INTEGER,
allocatable,
dimension(:),
save ::
nptabij
44 jj_nb, jj_begin, jj_end, ii_begin, ii_end, &
45 mpi_size, mpi_rank, klon_mpi, &
51 USE ioipsl
, only: flio_dom_set
54 use wxios
, only: wxios_domain_param
57 real,
dimension(klon),
intent(in) :: rlon
58 real,
dimension(klon),
intent(in) :: rlat
60 REAL,
dimension(klon_glo) :: rlat_glo
61 REAL,
dimension(klon_glo) :: rlon_glo
63 INTEGER,
DIMENSION(2) :: ddid
64 INTEGER,
DIMENSION(2) :: dsg
65 INTEGER,
DIMENSION(2) :: dsl
66 INTEGER,
DIMENSION(2) :: dpf
67 INTEGER,
DIMENSION(2) :: dpl
68 INTEGER,
DIMENSION(2) :: dhs
69 INTEGER,
DIMENSION(2) :: dhe
71 integer :: data_ibegin,data_iend
113 dhs=(/ ii_begin-1,0 /)
114 if (mpi_rank==mpi_size-1)
then
120 #ifndef CPP_IOIPSL_NO_OUTPUT
121 call flio_dom_set(mpi_size,mpi_rank,ddid,dsg,dsl,dpf,dpl,dhs,dhe, &
126 IF (mpi_rank == 0)
THEN
129 data_ibegin = ii_begin - 1
132 IF (mpi_rank == mpi_size-1)
THEN
135 data_iend = ii_end + 1
139 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
141 write(
lunout,*)
"init_iophy_new: mpirank=",mpi_rank,
" data_ibegin=",data_ibegin,
" data_iend=",data_iend
142 write(
lunout,*)
"init_iophy_new: mpirank=",mpi_rank,
" data_ibegin=",data_ibegin,
" data_iend=",data_iend
143 write(
lunout,*)
"init_iophy_new: mpirank=",mpi_rank,
" is_south_pole=",is_south_pole
148 1,
nbp_lon, ii_begin, ii_end, jj_begin, jj_end, &
149 klon_mpi+2*(
nbp_lon-1), data_ibegin, data_iend, &
158 subroutine histbeg_phy(name,itau0,zjulian,dtime,nhori,nid_day)
165 character*(*),
intent(IN) :: name
166 integer,
intent(in) :: itau0
167 real,
intent(in) :: zjulian
168 real,
intent(in) :: dtime
169 integer,
intent(out) :: nhori
170 integer,
intent(out) :: nid_day
175 1,
nbp_lon,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day)
191 use wxios
, only: wxios_add_file
194 character*(*),
INTENT(IN) :: name
198 character(LEN=*),
INTENT(IN) :: ffreq
199 INTEGER,
INTENT(IN) :: lev
206 IF((.NOT. is_using_mpi) .OR. is_mpi_root)
THEN
208 CALL wxios_add_file(name, ffreq, lev)
224 USE ioipsl
, only: histwrite
228 integer,
intent(in) :: nid
229 logical,
intent(in) :: lpoint
230 character*(*),
intent(IN) :: name
231 integer,
intent(in) :: itau
232 real,
dimension(:),
intent(in) :: field
233 REAL,
dimension(klon_mpi) :: buffer_omp
234 INTEGER,
allocatable,
dimension(:) :: index2d
238 real,
allocatable,
dimension(:) :: fieldok
240 IF (
size(field)/=
klon)
CALL abort_physic(
'iophy::histwrite2d',
'Field first dimension not equal to klon',1)
242 CALL gather_omp(field,buffer_omp)
244 CALL grid1dto2d_mpi(buffer_omp,field2d)
246 ALLOCATE(index2d(
nbp_lon*jj_nb))
247 ALLOCATE(fieldok(
nbp_lon*jj_nb))
248 CALL histwrite(nid,name,itau,field2d,
nbp_lon*jj_nb,index2d)
250 ALLOCATE(fieldok(
npstn))
251 ALLOCATE(index2d(
npstn))
257 fieldok(ip)=buffer_omp(
nptabij(ip))
262 IF(
nptabij(ip).GE.klon_mpi_begin.AND. &
263 nptabij(ip).LE.klon_mpi_end)
THEN
264 fieldok(ip)=buffer_omp(
nptabij(ip)-klon_mpi_begin+1)
268 CALL histwrite(nid,name,itau,fieldok,
npstn,index2d)
283 USE ioipsl
, only: histwrite
287 integer,
intent(in) :: nid
288 logical,
intent(in) :: lpoint
289 character*(*),
intent(IN) :: name
290 integer,
intent(in) :: itau
291 real,
dimension(:,:),
intent(in) :: field
292 REAL,
dimension(klon_mpi,size(field,2)) :: buffer_omp
293 REAL :: Field3d(
nbp_lon,jj_nb,size(field,2))
294 INTEGER :: ip, n, nlev
295 INTEGER,
ALLOCATABLE,
dimension(:) :: index3d
296 real,
allocatable,
dimension(:,:) :: fieldok
298 IF (
size(field,1)/=
klon)
CALL abort_physic(
'iophy::histwrite3d',
'Field first dimension not equal to klon',1)
301 CALL gather_omp(field,buffer_omp)
303 CALL grid1dto2d_mpi(buffer_omp,field3d)
305 ALLOCATE(index3d(
nbp_lon*jj_nb*nlev))
306 ALLOCATE(fieldok(
nbp_lon*jj_nb,nlev))
307 CALL histwrite(nid,name,itau,field3d,
nbp_lon*jj_nb*nlev,index3d)
310 ALLOCATE(index3d(
npstn*nlev))
311 ALLOCATE(fieldok(
npstn,nlev))
318 fieldok(ip,n)=buffer_omp(
nptabij(ip),n)
324 IF(
nptabij(ip).GE.klon_mpi_begin.AND. &
325 nptabij(ip).LE.klon_mpi_end)
THEN
326 fieldok(ip,n)=buffer_omp(
nptabij(ip)-klon_mpi_begin+1,n)
331 CALL histwrite(nid,name,itau,fieldok,
npstn*nlev,index3d)
342 SUBROUTINE histwrite2d_xios(field_name,field)
346 USE xios
, only: xios_send_field
351 CHARACTER(LEN=*),
INTENT(IN) :: field_name
352 REAL,
DIMENSION(:),
INTENT(IN) :: field
354 REAL,
DIMENSION(klon_mpi) :: buffer_omp
357 IF (
prt_level >= 10)
WRITE(
lunout,*)
'Begin histrwrite2d_xios ',trim(field_name)
359 IF (
SIZE(field)/=
klon)
CALL abort_physic(
'iophy::histwrite2d_xios',
'Field first DIMENSION not equal to klon',1)
361 CALL gather_omp(field,buffer_omp)
363 CALL grid1dto2d_mpi(buffer_omp,field2d)
365 CALL xios_send_field(field_name, field2d)
368 IF (
prt_level >= 10)
WRITE(
lunout,*)
'End histrwrite2d_xios ',trim(field_name)
369 END SUBROUTINE histwrite2d_xios
376 SUBROUTINE histwrite3d_xios(field_name, field)
380 USE xios
, only: xios_send_field
386 CHARACTER(LEN=*),
INTENT(IN) :: field_name
387 REAL,
DIMENSION(:,:),
INTENT(IN) :: field
389 REAL,
DIMENSION(klon_mpi,SIZE(field,2)) :: buffer_omp
390 REAL :: Field3d(
nbp_lon,jj_nb,size(field,2))
391 INTEGER :: ip, n, nlev
393 IF (
prt_level >= 10)
write(
lunout,*)
'Begin histrwrite3d_xios ',trim(field_name)
396 IF (
SIZE(field,1)/=
klon)
CALL abort_physic(
'iophy::histwrite3d',
'Field first DIMENSION not equal to klon',1)
400 CALL gather_omp(field,buffer_omp)
402 CALL grid1dto2d_mpi(buffer_omp,field3d)
404 CALL xios_send_field(field_name, field3d(:,:,1:nlev))
407 IF (
prt_level >= 10)
write(
lunout,*)
'End histrwrite3d_xios ',trim(field_name)
408 END SUBROUTINE histwrite3d_xios
!IM Implemente en modes sequentiel et parallele CALL rlon_glo CALL bcast(rlon_glo)!$OMP MASTER if(is_mpi_root) then!zstophy
integer, save phys_domain_id
real, dimension(:), allocatable, save io_lat
subroutine histbeg_phyxios(name, itau0, zjulian, dtime, ffreq, lev, nhori, nid_day)
!IM Implemente en modes sequentiel et parallele CALL gather(rlat, rlat_glo) CALL bcast(rlat_glo) CALL gather(rlon
!FH On elimine toutes les clefs physiques dans la dynamique prt_level
subroutine histwrite2d_phy(nid, lpoint, name, itau, field)
subroutine histbeg_phy(name, itau0, zjulian, dtime, nhori, nid_day)
integer, dimension(:), allocatable, save nptabij
real, dimension(:), allocatable, save io_lon
subroutine abort_physic(modname, message, ierr)
c c zjulian c cym CALL iim cym klev iim cym jjmp1 cym On stoke le fichier bilKP instantanne s jmax_ins print On stoke le fichier bilKP instantanne s s cym cym nid_bilKPins ENDIF c cIM BEG c cIM cf AM BEG region cym CALL histbeg("histbilKP_ins", iim, zx_lon(:, 1), cym.jjmp1, zx_lat(1,:), cym.imin_ins, imax_ins-imin_ins+1, cym.jmin_ins, jmax_ins-jmin_ins+1, cym.itau_phy, zjulian, dtime, cym.nhori, nid_bilKPins) CALL histbeg_phy("histbilKP_ins"
subroutine histwrite3d_phy(nid, lpoint, name, itau, field)
subroutine init_iophy_new(rlat, rlon)
logical, save is_sequential
!$Header!gestion des impressions de sorties et de débogage la sortie standard prt_level COMMON comprint lunout