source: LMDZ5/branches/testing/libf/cosp/cosp_output_write_mod.F90 @ 2160

Last change on this file since 2160 was 2160, checked in by Laurent Fairhead, 10 years ago

Merged trunk changes -r2070:2158 into testing branch. Compilation problems introduced by revision r2155 have been corrected by hand

File size: 17.5 KB
Line 
1!!!! Abderrahmane Idelkadi aout 2013 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2! Module pour definir (au 1er appel) et ecrire les variables dans les fichiers de sortie cosp
3!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
4   MODULE cosp_output_write_mod
5 
6   USE cosp_output_mod
7 
8   INTEGER, SAVE  :: itau_iocosp
9!$OMP THREADPRIVATE(itau_iocosp)
10   INTEGER, save        :: Nlevout, Ncolout
11!$OMP THREADPRIVATE(Nlevout, Ncolout)
12
13!  INTERFACE histwrite_cosp
14!    MODULE PROCEDURE histwrite2d_cosp,histwrite3d_cosp
15!  END INTERFACE
16
17   CONTAINS
18
19  SUBROUTINE cosp_output_write(Nlevlmdz, Npoints, Ncolumns, itap, dtime, freq_COSP, &
20                               cfg, gbx, vgrid, sglidar, stlidar, isccp)
21
22    USE ioipsl
23    USE control_mod
24
25#ifdef CPP_XIOS
26    USE wxios, only: wxios_closedef
27    USE xios, only: xios_update_calendar
28#endif
29
30!!! Variables d'entree
31  integer               :: itap, Nlevlmdz, Ncolumns, Npoints
32  real                  :: freq_COSP, dtime
33  type(cosp_config)     :: cfg     ! Control outputs
34  type(cosp_gridbox)    :: gbx     ! Gridbox information. Input for COSP
35  type(cosp_sglidar)    :: sglidar ! Output from lidar simulator
36  type(cosp_isccp)      :: isccp   ! Output from ISCCP simulator
37  type(cosp_lidarstats) :: stlidar ! Summary statistics from lidar simulator
38  type(cosp_vgrid)      :: vgrid   ! Information on vertical grid of stats
39
40!!! Variables locales
41  integer               :: icl
42  logical               :: ok_sync
43  integer               :: itau_wcosp
44  real, dimension(Npoints,PARASOL_NREFL) :: parasolcrefl, Ncref
45
46  include "temps.h"
47  include "iniprint.h"
48
49  Nlevout = vgrid%Nlvgrid
50  Ncolout = Ncolumns
51
52! A refaire
53       itau_wcosp = itau_phy + itap + start_time * day_step / iphysiq
54        if (prt_level >= 10) then
55             WRITE(lunout,*)'itau_wcosp, itap, start_time, day_step, iphysiq =', &
56                             itau_wcosp, itap, start_time, day_step, iphysiq
57        endif
58
59! On le donne a  cosp_output_write_mod pour que les histwrite y aient acces:
60       CALL set_itau_iocosp(itau_wcosp)
61        if (prt_level >= 10) then
62              WRITE(lunout,*)'itau_iocosp =',itau_iocosp
63        endif
64
65    ok_sync = .TRUE.
66   
67!DO iinit=1, iinitend
68! AI sept 2014 cette boucle supprimee
69! On n'ecrit pas quand itap=1 (cosp)
70
71   if (prt_level >= 10) then
72         WRITE(lunout,*)'DO iinit=1, iinitend ',iinitend
73   endif
74
75#ifdef CPP_XIOS
76 !$OMP MASTER
77IF (cosp_varsdefined) THEN
78   if (prt_level >= 10) then
79         WRITE(lunout,*)'Apell xios_update_calendar cosp_varsdefined iinitend ', &
80                         cosp_varsdefined,iinitend
81   endif
82    CALL xios_update_calendar(itau_wcosp)
83ENDIF
84  !$OMP END MASTER
85  !$OMP BARRIER
86#endif
87
88 if (cfg%Llidar_sim) then
89! Pb des valeurs indefinies, on les met a 0
90! A refaire proprement
91  do k = 1,Nlevout
92     do ip = 1,Npoints
93     if(stlidar%lidarcld(ip,k).eq.R_UNDEF)then
94      stlidar%lidarcld(ip,k)=0.
95     endif
96     enddo
97
98     do ii= 1,SR_BINS
99      do ip = 1,Npoints
100       if(stlidar%cfad_sr(ip,ii,k).eq.R_UNDEF)then
101        stlidar%cfad_sr(ip,ii,k)=0.
102       endif
103      enddo
104     enddo
105   enddo
106
107  do ip = 1,Npoints
108   do k = 1,Nlevlmdz
109     if(sglidar%beta_mol(ip,k).eq.R_UNDEF)then
110      sglidar%beta_mol(ip,k)=0.
111     endif
112
113     do ii= 1,Ncolumns
114       if(sglidar%beta_tot(ip,ii,k).eq.R_UNDEF)then
115        sglidar%beta_tot(ip,ii,k)=0.
116       endif
117     enddo
118
119    enddo    !k = 1,Nlevlmdz
120   enddo     !ip = 1,Npoints
121
122   do k = 1,LIDAR_NCAT
123    do ip = 1,Npoints
124     if(stlidar%cldlayer(ip,k).eq.R_UNDEF)then
125      stlidar%cldlayer(ip,k)=0.
126     endif
127    enddo
128   enddo
129
130   print*,'Appel histwrite2d_cosp'
131   CALL histwrite2d_cosp(o_cllcalipso,stlidar%cldlayer(:,1))
132   CALL histwrite2d_cosp(o_clhcalipso,stlidar%cldlayer(:,3))
133   CALL histwrite2d_cosp(o_clmcalipso,stlidar%cldlayer(:,2))
134   CALL histwrite2d_cosp(o_cltcalipso,stlidar%cldlayer(:,4))
135   CALL histwrite3d_cosp(o_clcalipso,stlidar%lidarcld,nvert)
136
137   do icl=1,SR_BINS
138      CALL histwrite3d_cosp(o_cfad_lidarsr532,stlidar%cfad_sr(:,icl,:),nvert,icl)
139   enddo
140
141   CALL histwrite3d_cosp(o_parasol_refl,stlidar%parasolrefl,nvertp)
142
143   do k=1,PARASOL_NREFL
144    do ip=1, Npoints
145     if (stlidar%cldlayer(ip,4).gt.0.01) then
146       parasolcrefl(ip,k)=(stlidar%parasolrefl(ip,k)-0.03*(1.-stlidar%cldlayer(ip,4)))/ &
147                            stlidar%cldlayer(ip,4)
148        Ncref(ip,k) = 1.
149     else
150        parasolcrefl(ip,k)=0.
151        Ncref(ip,k) = 0.
152     endif
153    enddo
154   enddo
155   CALL histwrite3d_cosp(o_parasol_crefl,parasolcrefl,nvertp)
156
157   do icl=1,Ncolumns
158      CALL histwrite3d_cosp(o_atb532,sglidar%beta_tot(:,icl,:),nvertmcosp,icl)
159   enddo
160   CALL histwrite3d_cosp(o_beta_mol532,sglidar%beta_mol,nvertmcosp)
161 endif !Lidar
162
163 if (cfg%Lisccp_sim) then
164
165! Traitement des valeurs indefinies
166   do ip = 1,Npoints
167    if(isccp%totalcldarea(ip).eq.-1.E+30)then
168      isccp%totalcldarea(ip)=0.
169    endif
170    if(isccp%meanptop(ip).eq.-1.E+30)then
171      isccp%meanptop(ip)=0.
172    endif
173    if(isccp%meantaucld(ip).eq.-1.E+30)then
174      isccp%meantaucld(ip)=0.
175    endif
176    if(isccp%meanalbedocld(ip).eq.-1.E+30)then
177      isccp%meanalbedocld(ip)=0.
178    endif
179    if(isccp%meantb(ip).eq.-1.E+30)then
180      isccp%meantb(ip)=0.
181    endif
182    if(isccp%meantbclr(ip).eq.-1.E+30)then
183      isccp%meantbclr(ip)=0.
184    endif
185
186    do k=1,7
187     do ii=1,7
188     if(isccp%fq_isccp(ip,ii,k).eq.-1.E+30)then
189      isccp%fq_isccp(ip,ii,k)=0.
190     endif
191     enddo
192    enddo
193
194    do ii=1,Ncolumns
195     if(isccp%boxtau(ip,ii).eq.-1.E+30)then
196       isccp%boxtau(ip,ii)=0.
197     endif
198    enddo
199
200    do ii=1,Ncolumns
201     if(isccp%boxptop(ip,ii).eq.-1.E+30)then
202       isccp%boxptop(ip,ii)=0.
203     endif
204    enddo
205   enddo
206
207   CALL histwrite2d_cosp(o_sunlit,gbx%sunlit)
208   do icl=1,7
209   CALL histwrite3d_cosp(o_clisccp2,isccp%fq_isccp(:,icl,:),nvertisccp,icl)
210   enddo
211   CALL histwrite3d_cosp(o_boxtauisccp,isccp%boxtau,nvertcol)
212   CALL histwrite3d_cosp(o_boxptopisccp,isccp%boxptop,nvertcol)
213   CALL histwrite2d_cosp(o_tclisccp,isccp%totalcldarea)
214   CALL histwrite2d_cosp(o_ctpisccp,isccp%meanptop)
215   CALL histwrite2d_cosp(o_tauisccp,isccp%meantaucld)
216   CALL histwrite2d_cosp(o_albisccp,isccp%meanalbedocld)
217   CALL histwrite2d_cosp(o_meantbisccp,isccp%meantb)
218   CALL histwrite2d_cosp(o_meantbclrisccp,isccp%meantbclr)
219 endif ! Isccp
220
221 IF(.NOT.cosp_varsdefined) THEN
222!$OMP MASTER
223#ifndef CPP_IOIPSL_NO_OUTPUT
224            DO iff=1,3
225                IF (cosp_outfilekeys(iff)) THEN
226                  CALL histend(cosp_nidfiles(iff))
227                ENDIF ! cosp_outfilekeys
228            ENDDO !  iff
229#endif
230! Fermeture dans phys_output_write
231!#ifdef CPP_XIOS
232            !On finalise l'initialisation:
233            !CALL wxios_closedef()
234!#endif
235
236!$OMP END MASTER
237!$OMP BARRIER
238            cosp_varsdefined = .TRUE.
239 END IF
240
241    IF(cosp_varsdefined) THEN
242! On synchronise les fichiers pour IOIPSL
243#ifndef CPP_IOIPSL_NO_OUTPUT
244!$OMP MASTER
245     DO iff=1,3
246         IF (ok_sync .AND. cosp_outfilekeys(iff)) THEN
247             CALL histsync(cosp_nidfiles(iff))
248         ENDIF
249     END DO
250!$OMP END MASTER
251#endif
252    ENDIF  !cosp_varsdefined
253
254    END SUBROUTINE cosp_output_write
255
256! ug Routine pour definir itau_iocosp depuis cosp_output_write_mod:
257  SUBROUTINE set_itau_iocosp(ito)
258      IMPLICIT NONE
259      INTEGER, INTENT(IN) :: ito
260      itau_iocosp = ito
261  END SUBROUTINE
262
263  SUBROUTINE histdef2d_cosp (iff,var)
264
265    USE ioipsl
266    USE dimphy
267    use iophy
268    USE mod_phys_lmdz_para
269#ifdef CPP_XIOS
270  USE wxios
271#endif
272
273    IMPLICIT NONE
274
275    INCLUDE "dimensions.h"
276    INCLUDE "temps.h"
277    INCLUDE "clesphys.h"
278    include "iniprint.h"
279
280    INTEGER                          :: iff
281    TYPE(ctrl_outcosp)               :: var
282
283    REAL zstophym
284    CHARACTER(LEN=20) :: typeecrit
285
286    ! ug On récupère le type écrit de la structure:
287    !       Assez moche, Ã|  refaire si meilleure méthode...
288    IF (INDEX(var%cosp_typeecrit(iff), "once") > 0) THEN
289       typeecrit = 'once'
290    ELSE IF(INDEX(var%cosp_typeecrit(iff), "t_min") > 0) THEN
291       typeecrit = 't_min(X)'
292    ELSE IF(INDEX(var%cosp_typeecrit(iff), "t_max") > 0) THEN
293       typeecrit = 't_max(X)'
294    ELSE IF(INDEX(var%cosp_typeecrit(iff), "inst") > 0) THEN
295       typeecrit = 'inst(X)'
296    ELSE
297       typeecrit = cosp_outfiletypes(iff)
298    ENDIF
299
300    IF (typeecrit=='inst(X)'.OR.typeecrit=='once') THEN
301       zstophym=zoutm_cosp(iff)
302    ELSE
303       zstophym=zdtimemoy_cosp
304    ENDIF
305
306#ifdef CPP_XIOS
307     IF (.not. ok_all_xml) then
308       IF ( var%cles(iff) ) THEN
309         if (prt_level >= 10) then
310              WRITE(lunout,*)'Appel wxios_add_field_to_file var%name =',var%name
311         endif
312        CALL wxios_add_field_to_file(var%name, 2, cosp_nidfiles(iff), cosp_outfilenames(iff), &
313                                     var%description, var%unit, 1, typeecrit)
314       ENDIF
315     ENDIF
316#endif
317
318#ifndef CPP_IOIPSL_NO_OUTPUT
319       IF ( var%cles(iff) ) THEN
320          CALL histdef (cosp_nidfiles(iff), var%name, var%description, var%unit, &
321               iim,jj_nb,nhoricosp(iff), 1,1,1, -99, 32, &
322               typeecrit, zstophym,zoutm_cosp(iff))
323       ENDIF
324#endif
325
326  END SUBROUTINE histdef2d_cosp
327
328 SUBROUTINE histdef3d_cosp (iff,var,nvertsave,ncols)
329    USE ioipsl
330    USE dimphy
331    use iophy
332    USE mod_phys_lmdz_para
333
334#ifdef CPP_XIOS
335  USE wxios
336#endif
337
338
339    IMPLICIT NONE
340
341    INCLUDE "dimensions.h"
342    INCLUDE "temps.h"
343    INCLUDE "clesphys.h"
344    include "iniprint.h"
345
346    INTEGER                        :: iff, klevs
347    INTEGER, INTENT(IN), OPTIONAL  :: ncols ! ug RUSTINE POUR LES variables 4D
348    INTEGER, INTENT(IN)           :: nvertsave
349    TYPE(ctrl_outcosp)             :: var
350
351    REAL zstophym
352    CHARACTER(LEN=20) :: typeecrit, nomi
353    CHARACTER(LEN=20) :: nom
354    character(len=2) :: str2
355    CHARACTER(len=20) :: nam_axvert
356
357! Axe vertical
358      IF (nvertsave.eq.nvertp(iff)) THEN
359          klevs=PARASOL_NREFL
360          nam_axvert="sza"
361      ELSE IF (nvertsave.eq.nvertisccp(iff)) THEN
362          klevs=7
363          nam_axvert="pressure2"
364      ELSE IF (nvertsave.eq.nvertcol(iff)) THEN
365          klevs=Ncolout
366          nam_axvert="column"
367      ELSE
368           klevs=Nlevout
369           nam_axvert="presnivs"
370      ENDIF
371
372! ug RUSTINE POUR LES Champs 4D
373      IF (PRESENT(ncols)) THEN
374               write(str2,'(i2.2)')ncols
375               nomi=var%name
376               nom="c"//str2//"_"//nomi
377      ELSE
378               nom=var%name
379      END IF
380
381    ! ug On récupère le type écrit de la structure:
382    !       Assez moche, Ã|  refaire si meilleure méthode...
383    IF (INDEX(var%cosp_typeecrit(iff), "once") > 0) THEN
384       typeecrit = 'once'
385    ELSE IF(INDEX(var%cosp_typeecrit(iff), "t_min") > 0) THEN
386       typeecrit = 't_min(X)'
387    ELSE IF(INDEX(var%cosp_typeecrit(iff), "t_max") > 0) THEN
388       typeecrit = 't_max(X)'
389    ELSE IF(INDEX(var%cosp_typeecrit(iff), "inst") > 0) THEN
390       typeecrit = 'inst(X)'
391    ELSE
392       typeecrit = cosp_outfiletypes(iff)
393    ENDIF
394
395    IF (typeecrit=='inst(X)'.OR.typeecrit=='once') THEN
396       zstophym=zoutm_cosp(iff)
397    ELSE
398       zstophym=zdtimemoy_cosp
399    ENDIF
400
401#ifdef CPP_XIOS
402      IF (.not. ok_all_xml) then
403        IF ( var%cles(iff) ) THEN
404          if (prt_level >= 10) then
405              WRITE(lunout,*)'Appel wxios_add_field_to_file 3d nom variable nam_axvert = ',nom, nam_axvert
406          endif
407          CALL wxios_add_field_to_file(nom, 3, cosp_nidfiles(iff), cosp_outfilenames(iff), &
408                                       var%description, var%unit, 1, typeecrit, nam_axvert)
409        ENDIF
410      ENDIF
411#endif
412
413#ifndef CPP_IOIPSL_NO_OUTPUT
414       IF ( var%cles(iff) ) THEN
415          CALL histdef (cosp_nidfiles(iff), nom, var%description, var%unit, &
416               iim, jj_nb, nhoricosp(iff), klevs, 1, &
417               klevs, nvertsave, 32, typeecrit, &
418               zstophym, zoutm_cosp(iff))
419       ENDIF
420#endif
421
422  END SUBROUTINE histdef3d_cosp
423
424 SUBROUTINE histwrite2d_cosp(var,field)
425  USE dimphy
426  USE mod_phys_lmdz_para
427  USE ioipsl
428  use iophy
429
430#ifdef CPP_XIOS
431  USE xios, only: xios_send_field
432#endif
433
434  IMPLICIT NONE
435  INCLUDE 'dimensions.h'
436  INCLUDE 'iniprint.h'
437  INCLUDE 'clesphys.h'
438
439    TYPE(ctrl_outcosp), INTENT(IN) :: var
440    REAL, DIMENSION(:), INTENT(IN) :: field
441
442    INTEGER :: iff
443
444    REAL,DIMENSION(klon_mpi) :: buffer_omp
445    INTEGER, allocatable, DIMENSION(:) :: index2d
446    REAL :: Field2d(iim,jj_nb)
447    CHARACTER(LEN=20) ::  nomi, nom
448    character(len=2) :: str2
449    LOGICAL, SAVE  :: firstx
450!$OMP THREADPRIVATE(firstx)
451
452    IF (prt_level >= 9) WRITE(lunout,*)'Begin histrwrite2d ',var%name
453
454  ! On regarde si on est dans la phase de définition ou d'écriture:
455  IF(.NOT.cosp_varsdefined) THEN
456!$OMP MASTER
457      !Si phase de définition.... on définit
458      CALL conf_cospoutputs(var%name,var%cles)
459      DO iff=1, 3
460         IF (cosp_outfilekeys(iff)) THEN
461            CALL histdef2d_cosp(iff, var)
462         ENDIF
463      ENDDO
464!$OMP END MASTER
465  ELSE
466    !Et sinon on.... écrit
467    IF (SIZE(field)/=klon) &
468  CALL abort_gcm('iophy::histwrite2d_cosp','Field first DIMENSION not equal to klon',1)
469
470    CALL Gather_omp(field,buffer_omp)
471!$OMP MASTER
472    CALL grid1Dto2D_mpi(buffer_omp,Field2d)
473
474! La boucle sur les fichiers:
475      firstx=.true.
476      DO iff=1, 3
477           IF (var%cles(iff) .AND. cosp_outfilekeys(iff)) THEN
478                ALLOCATE(index2d(iim*jj_nb))
479#ifndef CPP_IOIPSL_NO_OUTPUT
480        CALL histwrite(cosp_nidfiles(iff),var%name,itau_iocosp,Field2d,iim*jj_nb,index2d)
481#endif
482                deallocate(index2d)
483#ifdef CPP_XIOS
484              IF (.not. ok_all_xml) then
485                 if (firstx) then
486                  if (prt_level >= 10) then
487                    WRITE(lunout,*)'xios_send_field variable ',var%name
488                  endif
489                  CALL xios_send_field(var%name, Field2d)
490                   firstx=.false.
491                 endif
492              ENDIF
493#endif
494           ENDIF
495      ENDDO
496
497#ifdef CPP_XIOS
498      IF (ok_all_xml) THEN
499        if (prt_level >= 10) then
500              WRITE(lunout,*)'xios_send_field variable ',var%name
501        endif
502       CALL xios_send_field(var%name, Field2d)
503      ENDIF
504#endif
505
506!$OMP END MASTER   
507  ENDIF ! vars_defined
508  IF (prt_level >= 9) WRITE(lunout,*)'End histrwrite2d_cosp ',var%name
509  END SUBROUTINE histwrite2d_cosp
510
511! ug NOUVELLE VERSION DES WRITE AVEC LA BOUCLE DO RENTREE
512! AI sept 2013
513  SUBROUTINE histwrite3d_cosp(var, field, nverts, ncols)
514  USE dimphy
515  USE mod_phys_lmdz_para
516  USE ioipsl
517  use iophy
518
519#ifdef CPP_XIOS
520  USE xios, only: xios_send_field
521#endif
522
523
524  IMPLICIT NONE
525  INCLUDE 'dimensions.h'
526  INCLUDE 'iniprint.h'
527  INCLUDE 'clesphys.h'
528
529    TYPE(ctrl_outcosp), INTENT(IN)    :: var
530    REAL, DIMENSION(:,:), INTENT(IN)  :: field ! --> field(klon,:)
531    INTEGER, INTENT(IN), OPTIONAL     :: ncols ! ug RUSTINE POUR LES Champs 4D.....
532    INTEGER, DIMENSION(3), INTENT(IN) :: nverts
533
534    INTEGER :: iff, k
535
536    REAL,DIMENSION(klon_mpi,SIZE(field,2)) :: buffer_omp
537    REAL :: Field3d(iim,jj_nb,SIZE(field,2))
538    INTEGER :: ip, n, nlev
539    INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d
540    CHARACTER(LEN=20) ::  nomi, nom
541    character(len=2) :: str2
542    LOGICAL, SAVE  :: firstx
543!$OMP THREADPRIVATE(firstx)
544
545  IF (prt_level >= 9) write(lunout,*)'Begin histrwrite3d ',var%name
546
547! ug RUSTINE POUR LES STD LEVS.....
548      IF (PRESENT(ncols)) THEN
549              write(str2,'(i2.2)')ncols
550              nomi=var%name
551              nom="c"//str2//"_"//nomi
552      ELSE
553               nom=var%name
554      END IF
555  ! On regarde si on est dans la phase de définition ou d'écriture:
556  IF(.NOT.cosp_varsdefined) THEN
557      !Si phase de définition.... on définit
558!$OMP MASTER
559      CALL conf_cospoutputs(var%name,var%cles)
560      DO iff=1, 3
561        IF (cosp_outfilekeys(iff)) THEN
562          CALL histdef3d_cosp(iff, var, nverts(iff), ncols)
563        ENDIF
564      ENDDO
565!$OMP END MASTER
566  ELSE
567    !Et sinon on.... écrit
568    IF (SIZE(field,1)/=klon) &
569   CALL abort_gcm('iophy::histwrite3d','Field first DIMENSION not equal to klon',1)                                 
570    nlev=SIZE(field,2)
571
572
573    CALL Gather_omp(field,buffer_omp)
574!$OMP MASTER
575    CALL grid1Dto2D_mpi(buffer_omp,field3d)
576
577! BOUCLE SUR LES FICHIERS
578     firstx=.true.
579     DO iff=1, 3
580        IF (var%cles(iff) .AND. cosp_outfilekeys(iff)) THEN
581           ALLOCATE(index3d(iim*jj_nb*nlev))
582#ifndef CPP_IOIPSL_NO_OUTPUT
583    CALL histwrite(cosp_nidfiles(iff),nom,itau_iocosp,Field3d,iim*jj_nb*nlev,index3d)
584#endif
585
586#ifdef CPP_XIOS
587          IF (.not. ok_all_xml) then
588           IF (firstx) THEN
589               CALL xios_send_field(nom, Field3d(:,:,1:nlev))
590               IF (prt_level >= 9) WRITE(lunout,*)'xios_send_field ',var%name
591               firstx=.FALSE.
592           ENDIF
593          ENDIF
594#endif
595         deallocate(index3d)
596        ENDIF
597      ENDDO
598#ifdef CPP_XIOS
599    IF (ok_all_xml) THEN
600     CALL xios_send_field(nom, Field3d(:,:,1:nlev))
601     IF (prt_level >= 9) WRITE(lunout,*)'xios_send_field ',var%name
602    ENDIF
603#endif
604
605!$OMP END MASTER   
606  ENDIF ! vars_defined
607  IF (prt_level >= 9) write(lunout,*)'End histrwrite3d_cosp ',nom
608  END SUBROUTINE histwrite3d_cosp
609
610  SUBROUTINE conf_cospoutputs(nam_var,cles_var)
611!!! Lecture des noms et cles de sortie des variables dans config.def
612    !   en utilisant les routines getin de IOIPSL 
613    use ioipsl
614
615    IMPLICIT NONE
616    include 'iniprint.h'
617
618   CHARACTER(LEN=20)               :: nam_var, nnam_var
619   LOGICAL, DIMENSION(3)           :: cles_var
620
621! Lecture dans config.def ou output.def de cles_var et name_var
622    CALL getin('cles_'//nam_var,cles_var)
623    CALL getin('name_'//nam_var,nam_var)
624    IF(prt_level>10) WRITE(lunout,*)'nam_var cles_var ',nam_var,cles_var(:)
625
626  END SUBROUTINE conf_cospoutputs
627
628 END MODULE cosp_output_write_mod
Note: See TracBrowser for help on using the repository browser.