Changeset 1664


Ignore:
Timestamp:
Oct 9, 2012, 3:29:15 PM (12 years ago)
Author:
Laurent Fairhead
Message:

Version testing basée sur la r1575


Testing release based on r1575

Location:
LMDZ5/branches/testing
Files:
12 deleted
46 edited
3 copied

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/bld.cfg

    r1545 r1664  
    4242bld::target              lib%{DYN}.a lib%{PHYS}.a libgrid.a libfiltrez.a libbibio.a libcosp.a libext_src.a
    4343bld::target              %EXEC%SUFF_NAME.e
    44 bld::exe_dep             %{DYN} %{PHYS} grid filtrez bibio cos ext_src
     44bld::exe_dep             %{DYN} %{PHYS} grid filtrez bibio cosp ext_src
    4545
    4646
  • LMDZ5/branches/testing/libf/dyn3d/ce0l.F90

    r1511 r1664  
    6767#endif
    6868
    69   IF (config_inca /= 'none') THEN
     69  IF (type_trac == 'inca') THEN
    7070#ifdef INCA
    7171    CALL init_const_lmdz(nbtr,anneeref,dayref,iphysiq,day_step,nday)
  • LMDZ5/branches/testing/libf/dyn3d/conf_gcm.F

    r1502 r1664  
    1313      use ioipsl_getincom
    1414#endif
     15      USE infotrac, ONLY : type_trac
    1516      IMPLICIT NONE
    1617c-----------------------------------------------------------------------
     
    571572       offline = .FALSE.
    572573       CALL getin('offline',offline)
     574     
     575!Config  Key  = type_trac
     576!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
     577!Config  Def  = lmdz
     578!Config  Help =
     579!Config         'lmdz' = pas de couplage, pur LMDZ
     580!Config         'inca' = model de chime INCA
     581!Config         'repr' = model de chime REPROBUS
     582      type_trac = 'lmdz'
     583      CALL getin('type_trac',type_trac)
    573584
    574585!Config  Key  = config_inca
     
    643654      write(lunout,*)' tauyy = ', tauyy
    644655      write(lunout,*)' offline = ', offline
     656      write(lunout,*)' type_trac = ', type_trac
    645657      write(lunout,*)' config_inca = ', config_inca
    646658      write(lunout,*)' ok_dynzon = ', ok_dynzon
     
    761773       offline = .FALSE.
    762774       CALL getin('offline',offline)
     775
     776!Config  Key  = type_trac
     777!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
     778!Config  Def  = lmdz
     779!Config  Help =
     780!Config         'lmdz' = pas de couplage, pur LMDZ
     781!Config         'inca' = model de chime INCA
     782!Config         'repr' = model de chime REPROBUS
     783      type_trac = 'lmdz'
     784      CALL getin('type_trac',type_trac)
    763785
    764786!Config  Key  = config_inca
     
    886908      write(lunout,*)' tauy = ', tauy
    887909      write(lunout,*)' offline = ', offline
     910      write(lunout,*)' type_trac = ', type_trac
    888911      write(lunout,*)' config_inca = ', config_inca
    889912      write(lunout,*)' ok_dynzon = ', ok_dynzon
  • LMDZ5/branches/testing/libf/dyn3d/dynredem.F

    r1403 r1664  
    641641#endif
    642642
    643       IF (config_inca /= 'none') THEN
     643      IF (type_trac == 'inca') THEN
    644644! Ajout Anne pour lecture valeurs traceurs dans un fichier start_trac.nc
    645645         ierr_file = NF_OPEN ("start_trac.nc", NF_NOWRITE,nid_trac)
     
    654654      do iq=1,nqtot
    655655
    656          IF (config_inca == 'none') THEN
     656         IF (type_trac /= 'inca') THEN
    657657            ierr = NF_INQ_VARID(nid, tname(iq), nvarid)
    658658            IF (ierr .NE. NF_NOERR) THEN
     
    666666            ierr = NF_PUT_VAR_REAL (nid,nvarid,q(1,1,iq))
    667667#endif
    668         ELSE ! config_inca = 'chem' ou 'aero'
     668        ELSE ! type_trac = inca
    669669! lecture de la valeur du traceur dans start_trac.nc
    670670           IF (ierr_file .ne. 2) THEN
     
    730730#endif
    731731          ENDIF ! (ierr_file .ne. 2)
    732        END IF   ! config_inca
     732       END IF   !type_trac
    733733     
    734734      ENDDO
  • LMDZ5/branches/testing/libf/dyn3d/gcm.F

    r1529 r1664  
    212212c-----------------------------------------------------------------------
    213213
    214       IF (config_inca /= 'none') THEN
     214      IF (type_trac == 'inca') THEN
    215215#ifdef INCA
    216216      call init_const_lmdz(nbtr,anneeref,dayref,iphysiq,day_step,nday,
     
    263263      endif ! of if (read_start)
    264264
    265       IF (config_inca /= 'none') THEN
     265      IF (type_trac == 'inca') THEN
    266266#ifdef INCA
    267267         call init_inca_dim(klon,llm,iim,jjm,
  • LMDZ5/branches/testing/libf/dyn3d/infotrac.F90

    r1454 r1664  
    3232  SUBROUTINE infotrac_init
    3333    USE control_mod
     34#ifdef REPROBUS
     35    USE CHEM_REP, ONLY : Init_chem_rep_trac
     36#endif
    3437    IMPLICIT NONE
    3538!=======================================================================
     
    8588   
    8689
    87     IF (config_inca=='none') THEN
    88        type_trac='lmdz'
     90    ! Coherence test between parameter type_trac, config_inca and preprocessing keys
     91    IF (type_trac=='inca') THEN
     92       WRITE(lunout,*) 'You have choosen to couple with INCA chemestry model : type_trac=', &
     93            type_trac,' config_inca=',config_inca
     94       IF (config_inca/='aero' .AND. config_inca/='chem') THEN
     95          WRITE(lunout,*) 'Incoherence between type_trac and config_inca. Model stops. Modify run.def'
     96          CALL abort_gcm('infotrac_init','Incoherence between type_trac and config_inca',1)
     97       END IF
     98#ifndef INCA
     99       WRITE(lunout,*) 'To run this option you must add cpp key INCA and compile with INCA code'
     100       CALL abort_gcm('infotrac_init','You must compile with cpp key INCA',1)
     101#endif
     102    ELSE IF (type_trac=='repr') THEN
     103       WRITE(lunout,*) 'You have choosen to couple with REPROBUS chemestry model : type_trac=', type_trac
     104#ifndef REPROBUS
     105       WRITE(lunout,*) 'To run this option you must add cpp key REPROBUS and compile with REPRPBUS code'
     106       CALL abort_gcm('infotrac_init','You must compile with cpp key REPROBUS',1)
     107#endif
     108    ELSE IF (type_trac == 'lmdz') THEN
     109       WRITE(lunout,*) 'Tracers are treated in LMDZ only : type_trac=', type_trac
    89110    ELSE
    90        type_trac='inca'
    91     END IF
     111       WRITE(lunout,*) 'type_trac=',type_trac,' not possible. Model stops'
     112       CALL abort_gcm('infotrac_init','bad parameter',1)
     113    END IF
     114
     115
     116    ! Test if config_inca is other then none for run without INCA
     117    IF (type_trac/='inca' .AND. config_inca/='none') THEN
     118       WRITE(lunout,*) 'config_inca will now be changed to none as you do not couple with INCA model'
     119       config_inca='none'
     120    END IF
     121
    92122
    93123!-----------------------------------------------------------------------
     
    97127!
    98128!-----------------------------------------------------------------------
    99     IF (type_trac == 'lmdz') THEN
     129    IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
    100130       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
    101131       IF(ierr.EQ.0) THEN
     
    119149         nbtr=nqtrue
    120150       endif
    121     ELSE
    122        ! nbtr has been read from INCA by init_cont_lmdz() in gcm.F
     151    ELSE ! type_trac=inca
     152       ! nbtr has been read from INCA by init_const_lmdz() in gcm.F
    123153       nqtrue=nbtr+2
    124154    END IF
     
    128158       CALL abort_gcm('infotrac_init','Not enough tracers',1)
    129159    END IF
     160   
     161! Transfert number of tracers to Reprobus
     162    IF (type_trac == 'repr') THEN
     163#ifdef REPROBUS
     164       CALL Init_chem_rep_trac(nbtr)
     165#endif
     166    END IF
     167       
    130168!
    131169! Allocate variables depending on nqtrue and nbtr
     
    162200!    Get choice of advection schema from file tracer.def or from INCA
    163201!---------------------------------------------------------------------
    164     IF (type_trac == 'lmdz') THEN
     202    IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
    165203       IF(ierr.EQ.0) THEN
    166204          ! Continue to read tracer.def
  • LMDZ5/branches/testing/libf/dyn3d/iniacademic.F90

    r1529 r1664  
    209209        ! surface pressure
    210210        if (iflag_phys>2) then
     211           ! specific value for CMIP5 aqua/terra planets
     212           ! "Specify the initial dry mass to be equivalent to
     213           !  a global mean surface pressure (101325 minus 245) Pa."
     214           ps(:)=101080. 
     215        else
     216           ! use reference surface pressure
    211217           ps(:)=preff
    212         else
    213            ps(:)=101080.
    214218        endif
     219       
    215220        ! ground geopotential
    216221        phis(:)=0.
  • LMDZ5/branches/testing/libf/dyn3dpar/ce0l.F90

    r1531 r1664  
    7878#endif
    7979
    80   IF (config_inca /= 'none') THEN
     80  IF (type_trac == 'inca') THEN
    8181#ifdef INCA
    8282      CALL init_const_lmdz( &
  • LMDZ5/branches/testing/libf/dyn3dpar/conf_gcm.F

    r1502 r1664  
    1717      use parallel, ONLY : omp_chunk
    1818      USE control_mod
     19      USE infotrac, ONLY : type_trac
    1920      IMPLICIT NONE
    2021c-----------------------------------------------------------------------
     
    102103      CALL getin('lunout', lunout)
    103104      IF (lunout /= 5 .and. lunout /= 6) THEN
    104         OPEN(lunout,FILE='lmdz.out')
     105        OPEN(UNIT=lunout,FILE='lmdz.out_0000',ACTION='write',
     106     &          STATUS='unknown',FORM='formatted')
     107
    105108      ENDIF
    106109
     
    588591       END IF
    589592       
     593!Config  Key  = type_trac
     594!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
     595!Config  Def  = lmdz
     596!Config  Help =
     597!Config         'lmdz' = pas de couplage, pur LMDZ
     598!Config         'inca' = model de chime INCA
     599!Config         'repr' = model de chime REPROBUS
     600      type_trac = 'lmdz'
     601      CALL getin('type_trac',type_trac)
     602
     603
    590604!Config  Key  = config_inca
    591605!Config  Desc = Choix de configuration de INCA
     
    659673      write(lunout,*)' tauyy = ', tauyy
    660674      write(lunout,*)' offline = ', offline
     675      write(lunout,*)' type_trac = ', type_trac
    661676      write(lunout,*)' config_inca = ', config_inca
    662677      write(lunout,*)' ok_dynzon = ', ok_dynzon
     
    785800     &         'only the file phystoke.nc will still be created '
    786801       END IF
     802
     803!Config  Key  = type_trac
     804!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
     805!Config  Def  = lmdz
     806!Config  Help =
     807!Config         'lmdz' = pas de couplage, pur LMDZ
     808!Config         'inca' = model de chime INCA
     809!Config         'repr' = model de chime REPROBUS
     810      type_trac = 'lmdz'
     811      CALL getin('type_trac',type_trac)
    787812
    788813!Config  Key  = config_inca
     
    933958      write(lunout,*)' tauy = ', tauy
    934959      write(lunout,*)' offline = ', offline
     960      write(lunout,*)' type_trac = ', type_trac
    935961      write(lunout,*)' config_inca = ', config_inca
    936962      write(lunout,*)' ok_dynzon = ', ok_dynzon
  • LMDZ5/branches/testing/libf/dyn3dpar/dynredem.F

    r1403 r1664  
    641641#endif
    642642
    643       IF (config_inca /= 'none') THEN
     643      IF (type_trac == 'inca') THEN
    644644! Ajout Anne pour lecture valeurs traceurs dans un fichier start_trac.nc
    645645         ierr_file = NF_OPEN ("start_trac.nc", NF_NOWRITE,nid_trac)
     
    654654      do iq=1,nqtot
    655655
    656          IF (config_inca == 'none') THEN
     656         IF (type_trac /= 'inca') THEN
    657657            ierr = NF_INQ_VARID(nid, tname(iq), nvarid)
    658658            IF (ierr .NE. NF_NOERR) THEN
     
    666666            ierr = NF_PUT_VAR_REAL (nid,nvarid,q(1,1,iq))
    667667#endif
    668         ELSE ! config_inca = 'chem' ou 'aero'
     668        ELSE ! type_trac=inca
    669669! lecture de la valeur du traceur dans start_trac.nc
    670670           IF (ierr_file .ne. 2) THEN
     
    730730#endif
    731731          ENDIF ! (ierr_file .ne. 2)
    732        END IF   ! config_inca
     732       END IF   ! type_trac
    733733     
    734734      ENDDO
  • LMDZ5/branches/testing/libf/dyn3dpar/dynredem_p.F

    r1403 r1664  
    650650#endif
    651651
    652       IF (config_inca /= 'none') THEN
     652      IF (type_trac == 'inca') THEN
    653653! Ajout Anne pour lecture valeurs traceurs dans un fichier start_trac.nc
    654654         inquire(FILE="start_trac.nc", EXIST=exist_file)
     
    667667      do iq=1,nqtot
    668668
    669          IF (config_inca == 'none') THEN
     669         IF (type_trac /= 'inca') THEN
    670670            ierr = NF_INQ_VARID(nid, tname(iq), nvarid)
    671671            IF (ierr .NE. NF_NOERR) THEN
     
    678678            ierr = NF_PUT_VAR_REAL (nid,nvarid,q(1,1,iq))
    679679#endif
    680         ELSE ! config_inca = 'chem' ou 'aero'
     680        ELSE ! type_trac = inca
    681681! lecture de la valeur du traceur dans start_trac.nc
    682682           IF (ierr_file .ne. 2) THEN
     
    732732#endif
    733733          ENDIF ! (ierr_file .ne. 2)
    734        END IF   ! config_inca
     734       END IF   ! type_trac
    735735     
    736736      ENDDO
  • LMDZ5/branches/testing/libf/dyn3dpar/exner_hyb_p.F

    r1520 r1664  
    125125      endif
    126126!$OMP END MASTER
    127 
     127!$OMP BARRIER
    128128        jjb=jj_begin
    129129        jje=jj_end
     
    171171      endif
    172172c$OMP END MASTER
     173c$OMP BARRIER
    173174c
    174175c
  • LMDZ5/branches/testing/libf/dyn3dpar/exner_milieu_p.F

    r1521 r1664  
    121121      endif
    122122!$OMP END MASTER
    123 
     123!$OMP BARRIER
    124124        jjb=jj_begin
    125125        jje=jj_end
     
    169169      endif
    170170c$OMP END MASTER
     171c$OMP BARRIER
    171172c
    172173c
  • LMDZ5/branches/testing/libf/dyn3dpar/gcm.F

    r1520 r1664  
    240240#endif
    241241
    242       IF (config_inca /= 'none') THEN
     242      IF (type_trac == 'inca') THEN
    243243#ifdef INCA
    244244         call init_const_lmdz(
     
    459459c   Initialisation des dimensions d'INCA :
    460460c   --------------------------------------
    461       IF (config_inca /= 'none') THEN
     461      IF (type_trac == 'inca') THEN
    462462!$OMP PARALLEL
    463463#ifdef INCA
  • LMDZ5/branches/testing/libf/dyn3dpar/infotrac.F90

    r1454 r1664  
    3232  SUBROUTINE infotrac_init
    3333    USE control_mod
     34#ifdef REPROBUS
     35    USE CHEM_REP, ONLY : Init_chem_rep_trac
     36#endif
    3437    IMPLICIT NONE
    3538!=======================================================================
     
    8588   
    8689
    87     IF (config_inca=='none') THEN
    88        type_trac='lmdz'
     90    ! Coherence test between parameter type_trac, config_inca and preprocessing keys
     91    IF (type_trac=='inca') THEN
     92       WRITE(lunout,*) 'You have choosen to couple with INCA chemestry model : type_trac=', &
     93            type_trac,' config_inca=',config_inca
     94       IF (config_inca/='aero' .AND. config_inca/='chem') THEN
     95          WRITE(lunout,*) 'Incoherence between type_trac and config_inca. Model stops. Modify run.def'
     96          CALL abort_gcm('infotrac_init','Incoherence between type_trac and config_inca',1)
     97       END IF
     98#ifndef INCA
     99       WRITE(lunout,*) 'To run this option you must add cpp key INCA and compile with INCA code'
     100       CALL abort_gcm('infotrac_init','You must compile with cpp key INCA',1)
     101#endif
     102    ELSE IF (type_trac=='repr') THEN
     103       WRITE(lunout,*) 'You have choosen to couple with REPROBUS chemestry model : type_trac=', type_trac
     104#ifndef REPROBUS
     105       WRITE(lunout,*) 'To run this option you must add cpp key REPROBUS and compile with REPRPBUS code'
     106       CALL abort_gcm('infotrac_init','You must compile with cpp key REPROBUS',1)
     107#endif
     108    ELSE IF (type_trac == 'lmdz') THEN
     109       WRITE(lunout,*) 'Tracers are treated in LMDZ only : type_trac=', type_trac
    89110    ELSE
    90        type_trac='inca'
    91     END IF
     111       WRITE(lunout,*) 'type_trac=',type_trac,' not possible. Model stops'
     112       CALL abort_gcm('infotrac_init','bad parameter',1)
     113    END IF
     114
     115
     116    ! Test if config_inca is other then none for run without INCA
     117    IF (type_trac/='inca' .AND. config_inca/='none') THEN
     118       WRITE(lunout,*) 'config_inca will now be changed to none as you do not couple with INCA model'
     119       config_inca='none'
     120    END IF
     121
    92122
    93123!-----------------------------------------------------------------------
     
    97127!
    98128!-----------------------------------------------------------------------
    99     IF (type_trac == 'lmdz') THEN
     129    IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
    100130       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
    101131       IF(ierr.EQ.0) THEN
     
    119149         nbtr=nqtrue
    120150       endif
    121     ELSE
    122        ! nbtr has been read from INCA by init_cont_lmdz() in gcm.F
     151    ELSE ! type_trac=inca
     152       ! nbtr has been read from INCA by init_const_lmdz() in gcm.F
    123153       nqtrue=nbtr+2
    124154    END IF
     
    128158       CALL abort_gcm('infotrac_init','Not enough tracers',1)
    129159    END IF
     160   
     161! Transfert number of tracers to Reprobus
     162    IF (type_trac == 'repr') THEN
     163#ifdef REPROBUS
     164       CALL Init_chem_rep_trac(nbtr)
     165#endif
     166    END IF
     167       
    130168!
    131169! Allocate variables depending on nqtrue and nbtr
     
    162200!    Get choice of advection schema from file tracer.def or from INCA
    163201!---------------------------------------------------------------------
    164     IF (type_trac == 'lmdz') THEN
     202    IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
    165203       IF(ierr.EQ.0) THEN
    166204          ! Continue to read tracer.def
  • LMDZ5/branches/testing/libf/dyn3dpar/iniacademic.F90

    r1520 r1664  
    115115  endif
    116116
    117   academic_case: if (iflag_phys == 2) then
     117  academic_case: if (iflag_phys >= 2) then
    118118     ! initializations
    119119
     
    208208     IF (.NOT. read_start) THEN
    209209        ! surface pressure
    210         ps(:)=preff
     210        if (iflag_phys>2) then
     211           ! specific value for CMIP5 aqua/terra planets
     212           ! "Specify the initial dry mass to be equivalent to
     213           !  a global mean surface pressure (101325 minus 245) Pa."
     214           ps(:)=101080. 
     215        else
     216           ! use reference surface pressure
     217           ps(:)=preff
     218        endif
     219       
    211220        ! ground geopotential
    212221        phis(:)=0.
  • LMDZ5/branches/testing/libf/dyn3dpar/leapfrog_p.F

    r1520 r1664  
    189189
    190190      INTEGER :: true_itau
    191       LOGICAL :: verbose=.true.
    192191      INTEGER :: iapptrac
    193192      INTEGER :: AdjustCount
     
    407406           call allgather_timer_average
    408407
    409         if (Verbose) then
     408        if (prt_level > 9) then
    410409       
    411410        print *,'*********************************'
  • LMDZ5/branches/testing/libf/dyn3dpar/parallel.F90

    r1492 r1664  
    4343      integer, dimension(3) :: blocklen,type
    4444      integer :: comp_id
    45 
     45      character(len=4)  :: num
     46      character(len=20) :: filename
     47 
    4648#ifdef CPP_OMP   
    4749      INTEGER :: OMP_GET_NUM_THREADS
     
    7577        mpi_rank=0
    7678      ENDIF
    77  
     79
     80
     81! Open text output file with mpi_rank in suffix of file name
     82      IF (lunout /= 5 .and. lunout /= 6) THEN
     83         WRITE(num,'(I4.4)') mpi_rank
     84         filename='lmdz.out_'//num
     85         IF (mpi_rank .NE. 0) THEN
     86            OPEN(UNIT=lunout,FILE=TRIM(filename),ACTION='write', &
     87               STATUS='unknown',FORM='formatted',IOSTAT=ierr)
     88         ENDIF
     89      ENDIF
     90
    7891     
    7992      allocate(jj_begin_para(0:mpi_size-1))
  • LMDZ5/branches/testing/libf/phylmd/YOEGWD.h

    r776 r1664  
    22! $Header$
    33!
    4 C     -----------------------------------------------------------------
    5 C*    *COMMON* *YOEGWD* - PARAMETERS FOR GRAVITY WAVE DRAG CALCULATIONS
    6 C     -----------------------------------------------------------------
    7 C
     4!  ATTENTION : ce fichier include est compatible format fixe/format libre
     5!                 veillez  n'utiliser que des ! pour les commentaires
     6!                 et  bien positionner les & des lignes de continuation
     7!                 (les placer en colonne 6 et en colonne 73)
     8!     -----------------------------------------------------------------
     9!*    *COMMON* *YOEGWD* - PARAMETERS FOR GRAVITY WAVE DRAG CALCULATIONS
     10!     -----------------------------------------------------------------
     11!
    812      integer NKTOPG,NSTRA
    913      real GFRCRIT,GKWAKE,GRCRIT,GVCRIT,GKDRAG,GKLIFT
    1014      real GHMAX,GRAHILO,GSIGCR,GSSEC,GTSEC,GVSEC
    11       COMMON/YOEGWD/ GFRCRIT,GKWAKE,GRCRIT,GVCRIT,GKDRAG,GKLIFT
    12      *        ,GHMAX,GRAHILO,GSIGCR,NKTOPG,NSTRA,GSSEC,GTSEC,GVSEC
    13 c$OMP THREADPRIVATE(/YOEGWD/)
    14 C
    15 
    16 
     15      COMMON/YOEGWD/ GFRCRIT,GKWAKE,GRCRIT,GVCRIT,GKDRAG,GKLIFT         &
     16     &        ,GHMAX,GRAHILO,GSIGCR,NKTOPG,NSTRA,GSSEC,GTSEC,GVSEC
     17!$OMP THREADPRIVATE(/YOEGWD/)
  • LMDZ5/branches/testing/libf/phylmd/aeropt_2bands.F90

    r1337 r1664  
    928928  DO m=1,nb_aer   
    929929    IF (.NOT. used_aer(m)) THEN
    930       tau_ae(:,:,:,:)=0.
    931       tau_ae_pi(:,:,:,:)=0.
    932       piz_ae(:,:,:,:)=0.
    933       cg_ae(:,:,:,:)=0.
     930      tau_ae(:,:,m,:)=0.
     931      tau_ae_pi(:,:,m,:)=0.
     932      piz_ae(:,:,m,:)=0.
     933      cg_ae(:,:,m,:)=0.
    934934    ENDIF
    935935  ENDDO
  • LMDZ5/branches/testing/libf/phylmd/clesphys.h

    r1539 r1664  
    6666       LOGICAL ok_isccp, ok_regdyn
    6767       REAL lonmin_ins, lonmax_ins, latmin_ins, latmax_ins
    68        REAL ecrit_ins, ecrit_hf, ecrit_hf2mth, ecrit_day
     68       REAL ecrit_ins, ecrit_hf, ecrit_day
    6969       REAL ecrit_mth, ecrit_tra, ecrit_reg
    7070       REAL ecrit_LES
     
    9393     &     , ok_mensuelCOSP,ok_journeCOSP,ok_hfCOSP                     &
    9494     &     , lonmin_ins, lonmax_ins, latmin_ins, latmax_ins             &
    95      &     , ecrit_ins, ecrit_hf, ecrit_hf2mth, ecrit_day               &
     95     &     , ecrit_ins, ecrit_hf, ecrit_day                             &
    9696     &     , ecrit_mth, ecrit_tra, ecrit_reg                            &
    9797     &     , freq_ISCCP, ecrit_ISCCP, freq_COSP, ip_ebil_phy            &
     
    100100     &     , co2_ppm0
    101101     
     102       save /clesphys/
    102103!$OMP THREADPRIVATE(/clesphys/)
    103104 
  • LMDZ5/branches/testing/libf/phylmd/concvl.F

    r1518 r1664  
    238238cc$$$         close (56)
    239239c
    240          print*, 'supcrit1, supcrit2' ,supcrit1, supcrit2
     240         IF (prt_level .ge. 10)
     241     &       WRITE(lunout,*) 'supcrit1, supcrit2' ,supcrit1, supcrit2
    241242C
    242243C===========================================================================
     
    248249          cbmf(i) = 0.
    249250          plcl(i) = 0.
    250           plfc(i) = 0.
    251           wbeff(i) = 0.
    252251          sigd(i) = 0.
    253252         ENDDO
    254253      ENDIF   !(ifrst .EQ. 0)
     254
     255c Initialisation a chaque pas de temps
     256      plfc(:)  = 0.
     257      wbeff(:) = 100.
    255258
    256259      DO k = 1, klev+1
     
    368371      endif 
    369372C------------------------------------------------------------------
    370       print *,' cva_driver -> cbmf,plcl,plfc,wbeff ',
    371      .          cbmf(1),plcl(1),plfc(1),wbeff(1)
     373      IF (prt_level .ge. 10)
     374     .   WRITE(lunout,*) ' cva_driver -> cbmf,plcl,plfc,wbeff ',
     375     .                     cbmf(1),plcl(1),plfc(1),wbeff(1)
    372376
    373377      DO i = 1,klon
  • LMDZ5/branches/testing/libf/phylmd/conf_phys.F90

    r1539 r1664  
    3737
    3838 include "thermcell.h"
     39 include "iniprint.h"
    3940
    4041!IM : on inclut/initialise les taux de CH4, N2O, CFC11 et CFC12
     
    101102
    102103! Local
    103   integer              :: numout = 6
    104104  real                 :: zzz
    105105
     
    199199  call getin('OCEAN', ocean_omp)
    200200  IF (ocean_omp /= 'yyyyyy') THEN
    201      WRITE(numout,*)'ERROR!! Old variable name OCEAN used in parmeter file.'
    202      WRITE(numout,*)'Variable OCEAN has been replaced by the variable type_ocean.'
    203      WRITE(numout,*)'You have to update your parameter file physiq.def to succed running'
     201     WRITE(lunout,*)'ERROR!! Old variable name OCEAN used in parmeter file.'
     202     WRITE(lunout,*)'Variable OCEAN has been replaced by the variable type_ocean.'
     203     WRITE(lunout,*)'You have to update your parameter file physiq.def to succed running'
    204204     CALL abort_gcm('conf_phys','Variable OCEAN no longer existing, use variable name type_ocean',1)
    205205  END IF
     
    13511351!Config Help =
    13521352!
    1353   ecrit_tra_omp = 30.
     1353  ecrit_tra_omp = 0.
    13541354  call getin('ecrit_tra',ecrit_tra_omp)
    13551355!
     
    16961696! Test of coherence between type_ocean and version_ocean
    16971697    IF (type_ocean=='couple' .AND. (version_ocean/='opa8' .AND. version_ocean/='nemo') ) THEN
    1698        WRITE(numout,*)' ERROR version_ocean=',version_ocean,' not valid in coupled configuration'
     1698       WRITE(lunout,*)' ERROR version_ocean=',version_ocean,' not valid in coupled configuration'
    16991699       CALL abort_gcm('conf_phys','version_ocean not valid',1)
    17001700    END IF
     
    17031703       version_ocean='sicOBS'
    17041704    ELSE IF (type_ocean=='slab' .AND. version_ocean/='sicOBS') THEN
    1705        WRITE(numout,*)' ERROR version_ocean=',version_ocean,' not valid with slab ocean'
     1705       WRITE(lunout,*)' ERROR version_ocean=',version_ocean,' not valid with slab ocean'
    17061706       CALL abort_gcm('conf_phys','version_ocean not valid',1)
    17071707    END IF
     
    17171717!$OMP MASTER
    17181718
    1719   write(numout,*)' ##############################################'
    1720   write(numout,*)' Configuration des parametres de la physique: '
    1721   write(numout,*)' Type ocean = ', type_ocean
    1722   write(numout,*)' Version ocean = ', version_ocean
    1723   write(numout,*)' Config veget = ', ok_veget
    1724   write(numout,*)' Sortie journaliere = ', ok_journe
    1725   write(numout,*)' Sortie haute frequence = ', ok_hf
    1726   write(numout,*)' Sortie mensuelle = ', ok_mensuel
    1727   write(numout,*)' Sortie instantanee = ', ok_instan
    1728   write(numout,*)' Frequence appel simulateur ISCCP, freq_ISCCP =', freq_ISCCP
    1729   write(numout,*)' Frequence appel simulateur ISCCP, ecrit_ISCCP =', ecrit_ISCCP
    1730   write(numout,*)' Frequence appel simulateur COSP, freq_COSP =', freq_COSP
    1731   write(numout,*)' Sortie bilan d''energie, ip_ebil_phy =', ip_ebil_phy
    1732   write(numout,*)' Excentricite = ',R_ecc
    1733   write(numout,*)' Equinoxe = ',R_peri
    1734   write(numout,*)' Inclinaison =',R_incl
    1735   write(numout,*)' Constante solaire =',solaire
    1736   write(numout,*)' co2_ppm =',co2_ppm
    1737   write(numout,*)' RCO2_act = ',RCO2_act
    1738   write(numout,*)' CH4_ppb =',CH4_ppb,' RCH4_act = ',RCH4_act
    1739   write(numout,*)' N2O_ppb =',N2O_ppb,' RN2O_act=  ',RN2O_act
    1740   write(numout,*)' CFC11_ppt=',CFC11_ppt,' RCFC11_act=  ',RCFC11_act
    1741   write(numout,*)' CFC12_ppt=',CFC12_ppt,' RCFC12_act=  ',RCFC12_act
    1742   write(numout,*)' RCO2_per = ',RCO2_per,' RCH4_per = ', RCH4_per
    1743   write(numout,*)' RN2O_per = ',RN2O_per,' RCFC11_per = ', RCFC11_per
    1744   write(numout,*)' RCFC12_per = ',RCFC12_per
    1745   write(numout,*)' cvl_corr=', cvl_corr
    1746   write(numout,*)'ok_lic_melt=', ok_lic_melt
    1747   write(numout,*)'cycle_diurne=',cycle_diurne
    1748   write(numout,*)'soil_model=',soil_model
    1749   write(numout,*)'new_oliq=',new_oliq
    1750   write(numout,*)'ok_orodr=',ok_orodr
    1751   write(numout,*)'ok_orolf=',ok_orolf
    1752   write(numout,*)'ok_limitvrai=',ok_limitvrai
    1753   write(numout,*)'nbapp_rad=',nbapp_rad
    1754   write(numout,*)'iflag_con=',iflag_con
    1755   write(numout,*)' epmax = ', epmax
    1756   write(numout,*)' ok_adj_ema = ', ok_adj_ema
    1757   write(numout,*)' iflag_clw = ', iflag_clw
    1758   write(numout,*)' cld_lc_lsc = ', cld_lc_lsc
    1759   write(numout,*)' cld_lc_con = ', cld_lc_con
    1760   write(numout,*)' cld_tau_lsc = ', cld_tau_lsc
    1761   write(numout,*)' cld_tau_con = ', cld_tau_con
    1762   write(numout,*)' ffallv_lsc = ', ffallv_lsc
    1763   write(numout,*)' ffallv_con = ', ffallv_con
    1764   write(numout,*)' coef_eva = ', coef_eva
    1765   write(numout,*)' reevap_ice = ', reevap_ice
    1766   write(numout,*)' iflag_pdf = ', iflag_pdf
    1767   write(numout,*)' iflag_cldcon = ', iflag_cldcon
    1768   write(numout,*)' iflag_radia = ', iflag_radia
    1769   write(numout,*)' iflag_rrtm = ', iflag_rrtm
    1770   write(numout,*)' iflag_ratqs = ', iflag_ratqs
    1771   write(numout,*)' seuil_inversion = ', seuil_inversion
    1772   write(numout,*)' fact_cldcon = ', fact_cldcon
    1773   write(numout,*)' facttemps = ', facttemps
    1774   write(numout,*)' ok_newmicro = ',ok_newmicro
    1775   write(numout,*)' ratqsbas = ',ratqsbas
    1776   write(numout,*)' ratqshaut = ',ratqshaut
    1777   write(numout,*)' tau_ratqs = ',tau_ratqs
    1778   write(numout,*)' top_height = ',top_height
    1779   write(numout,*)' rad_froid = ',rad_froid
    1780   write(numout,*)' rad_chau1 = ',rad_chau1
    1781   write(numout,*)' rad_chau2 = ',rad_chau2
    1782   write(numout,*)' t_glace_min = ',t_glace_min
    1783   write(numout,*)' t_glace_max = ',t_glace_max
    1784   write(numout,*)' rei_min = ',rei_min
    1785   write(numout,*)' rei_max = ',rei_max
    1786   write(numout,*)' overlap = ',overlap
    1787   write(numout,*)' cdmmax = ',cdmmax
    1788   write(numout,*)' cdhmax = ',cdhmax
    1789   write(numout,*)' ksta = ',ksta
    1790   write(numout,*)' ksta_ter = ',ksta_ter
    1791   write(numout,*)' ok_kzmin = ',ok_kzmin
    1792   write(numout,*)' fmagic = ',fmagic
    1793   write(numout,*)' pmagic = ',pmagic
    1794   write(numout,*)' ok_ade = ',ok_ade
    1795   write(numout,*)' ok_aie = ',ok_aie
    1796   write(numout,*)' aerosol_couple = ', aerosol_couple
    1797   write(numout,*)' flag_aerosol = ', flag_aerosol
    1798   write(numout,*)' new_aod = ', new_aod
    1799   write(numout,*)' aer_type = ',aer_type
    1800   write(numout,*)' bl95_b0 = ',bl95_b0
    1801   write(numout,*)' bl95_b1 = ',bl95_b1
    1802   write(numout,*)' lev_histhf = ',lev_histhf
    1803   write(numout,*)' lev_histday = ',lev_histday
    1804   write(numout,*)' lev_histmth = ',lev_histmth
    1805   write(numout,*)' lev_histins = ',lev_histins
    1806   write(numout,*)' lev_histLES = ',lev_histLES
    1807   write(numout,*)' lev_histdayNMC = ',lev_histdayNMC
    1808   write(numout,*)' ok_histNMC = ',ok_histNMC
    1809   write(numout,*)' freq_outNMC = ',freq_outNMC
    1810   write(numout,*)' freq_calNMC = ',freq_calNMC
    1811   write(numout,*)' iflag_pbl = ', iflag_pbl
    1812   write(numout,*)' iflag_thermals = ', iflag_thermals
    1813   write(numout,*)' iflag_thermals_ed = ', iflag_thermals_ed
    1814   write(numout,*)' iflag_thermals_optflux = ', iflag_thermals_optflux
    1815   write(numout,*)' iflag_clos = ', iflag_clos
    1816   write(numout,*)' type_run = ',type_run
    1817   write(numout,*)' ok_isccp = ',ok_isccp
    1818   write(numout,*)' ok_cosp = ',ok_cosp
    1819   write(numout,*)' ok_mensuelCOSP = ',ok_mensuelCOSP
    1820   write(numout,*)' ok_journeCOSP = ',ok_journeCOSP
    1821   write(numout,*)' ok_hfCOSP =',ok_hfCOSP
    1822   write(numout,*)' solarlong0 = ', solarlong0
    1823   write(numout,*)' qsol0 = ', qsol0
    1824   write(numout,*)' inertie_sol = ', inertie_sol
    1825   write(numout,*)' inertie_ice = ', inertie_ice
    1826   write(numout,*)' inertie_sno = ', inertie_sno
    1827   write(numout,*)' f_cdrag_ter = ',f_cdrag_ter
    1828   write(numout,*)' f_cdrag_oce = ',f_cdrag_oce
    1829   write(numout,*)' f_rugoro = ',f_rugoro
    1830   write(numout,*)' supcrit1 = ', supcrit1
    1831   write(numout,*)' supcrit2 = ', supcrit2
    1832   write(numout,*)' iflag_mix = ', iflag_mix
    1833   write(numout,*)' scut = ', scut
    1834   write(numout,*)' qqa1 = ', qqa1
    1835   write(numout,*)' qqa2 = ', qqa2
    1836   write(numout,*)' gammas = ', gammas
    1837   write(numout,*)' Fmax = ', Fmax
    1838   write(numout,*)' alphas = ', alphas
    1839   write(numout,*)' iflag_wake = ', iflag_wake
    1840   write(numout,*)' alp_offset = ', alp_offset
    1841 
    1842   write(numout,*)' lonmin lonmax latmin latmax bilKP_ins =',&
     1719  write(lunout,*)' ##############################################'
     1720  write(lunout,*)' Configuration des parametres de la physique: '
     1721  write(lunout,*)' Type ocean = ', type_ocean
     1722  write(lunout,*)' Version ocean = ', version_ocean
     1723  write(lunout,*)' Config veget = ', ok_veget
     1724  write(lunout,*)' Sortie journaliere = ', ok_journe
     1725  write(lunout,*)' Sortie haute frequence = ', ok_hf
     1726  write(lunout,*)' Sortie mensuelle = ', ok_mensuel
     1727  write(lunout,*)' Sortie instantanee = ', ok_instan
     1728  write(lunout,*)' Frequence appel simulateur ISCCP, freq_ISCCP =', freq_ISCCP
     1729  write(lunout,*)' Frequence appel simulateur ISCCP, ecrit_ISCCP =', ecrit_ISCCP
     1730  write(lunout,*)' Frequence appel simulateur COSP, freq_COSP =', freq_COSP
     1731  write(lunout,*)' Sortie bilan d''energie, ip_ebil_phy =', ip_ebil_phy
     1732  write(lunout,*)' Excentricite = ',R_ecc
     1733  write(lunout,*)' Equinoxe = ',R_peri
     1734  write(lunout,*)' Inclinaison =',R_incl
     1735  write(lunout,*)' Constante solaire =',solaire
     1736  write(lunout,*)' co2_ppm =',co2_ppm
     1737  write(lunout,*)' RCO2_act = ',RCO2_act
     1738  write(lunout,*)' CH4_ppb =',CH4_ppb,' RCH4_act = ',RCH4_act
     1739  write(lunout,*)' N2O_ppb =',N2O_ppb,' RN2O_act=  ',RN2O_act
     1740  write(lunout,*)' CFC11_ppt=',CFC11_ppt,' RCFC11_act=  ',RCFC11_act
     1741  write(lunout,*)' CFC12_ppt=',CFC12_ppt,' RCFC12_act=  ',RCFC12_act
     1742  write(lunout,*)' RCO2_per = ',RCO2_per,' RCH4_per = ', RCH4_per
     1743  write(lunout,*)' RN2O_per = ',RN2O_per,' RCFC11_per = ', RCFC11_per
     1744  write(lunout,*)' RCFC12_per = ',RCFC12_per
     1745  write(lunout,*)' cvl_corr=', cvl_corr
     1746  write(lunout,*)'ok_lic_melt=', ok_lic_melt
     1747  write(lunout,*)'cycle_diurne=',cycle_diurne
     1748  write(lunout,*)'soil_model=',soil_model
     1749  write(lunout,*)'new_oliq=',new_oliq
     1750  write(lunout,*)'ok_orodr=',ok_orodr
     1751  write(lunout,*)'ok_orolf=',ok_orolf
     1752  write(lunout,*)'ok_limitvrai=',ok_limitvrai
     1753  write(lunout,*)'nbapp_rad=',nbapp_rad
     1754  write(lunout,*)'iflag_con=',iflag_con
     1755  write(lunout,*)' epmax = ', epmax
     1756  write(lunout,*)' ok_adj_ema = ', ok_adj_ema
     1757  write(lunout,*)' iflag_clw = ', iflag_clw
     1758  write(lunout,*)' cld_lc_lsc = ', cld_lc_lsc
     1759  write(lunout,*)' cld_lc_con = ', cld_lc_con
     1760  write(lunout,*)' cld_tau_lsc = ', cld_tau_lsc
     1761  write(lunout,*)' cld_tau_con = ', cld_tau_con
     1762  write(lunout,*)' ffallv_lsc = ', ffallv_lsc
     1763  write(lunout,*)' ffallv_con = ', ffallv_con
     1764  write(lunout,*)' coef_eva = ', coef_eva
     1765  write(lunout,*)' reevap_ice = ', reevap_ice
     1766  write(lunout,*)' iflag_pdf = ', iflag_pdf
     1767  write(lunout,*)' iflag_cldcon = ', iflag_cldcon
     1768  write(lunout,*)' iflag_radia = ', iflag_radia
     1769  write(lunout,*)' iflag_rrtm = ', iflag_rrtm
     1770  write(lunout,*)' iflag_ratqs = ', iflag_ratqs
     1771  write(lunout,*)' seuil_inversion = ', seuil_inversion
     1772  write(lunout,*)' fact_cldcon = ', fact_cldcon
     1773  write(lunout,*)' facttemps = ', facttemps
     1774  write(lunout,*)' ok_newmicro = ',ok_newmicro
     1775  write(lunout,*)' ratqsbas = ',ratqsbas
     1776  write(lunout,*)' ratqshaut = ',ratqshaut
     1777  write(lunout,*)' tau_ratqs = ',tau_ratqs
     1778  write(lunout,*)' top_height = ',top_height
     1779  write(lunout,*)' rad_froid = ',rad_froid
     1780  write(lunout,*)' rad_chau1 = ',rad_chau1
     1781  write(lunout,*)' rad_chau2 = ',rad_chau2
     1782  write(lunout,*)' t_glace_min = ',t_glace_min
     1783  write(lunout,*)' t_glace_max = ',t_glace_max
     1784  write(lunout,*)' rei_min = ',rei_min
     1785  write(lunout,*)' rei_max = ',rei_max
     1786  write(lunout,*)' overlap = ',overlap
     1787  write(lunout,*)' cdmmax = ',cdmmax
     1788  write(lunout,*)' cdhmax = ',cdhmax
     1789  write(lunout,*)' ksta = ',ksta
     1790  write(lunout,*)' ksta_ter = ',ksta_ter
     1791  write(lunout,*)' ok_kzmin = ',ok_kzmin
     1792  write(lunout,*)' fmagic = ',fmagic
     1793  write(lunout,*)' pmagic = ',pmagic
     1794  write(lunout,*)' ok_ade = ',ok_ade
     1795  write(lunout,*)' ok_aie = ',ok_aie
     1796  write(lunout,*)' aerosol_couple = ', aerosol_couple
     1797  write(lunout,*)' flag_aerosol = ', flag_aerosol
     1798  write(lunout,*)' new_aod = ', new_aod
     1799  write(lunout,*)' aer_type = ',aer_type
     1800  write(lunout,*)' bl95_b0 = ',bl95_b0
     1801  write(lunout,*)' bl95_b1 = ',bl95_b1
     1802  write(lunout,*)' lev_histhf = ',lev_histhf
     1803  write(lunout,*)' lev_histday = ',lev_histday
     1804  write(lunout,*)' lev_histmth = ',lev_histmth
     1805  write(lunout,*)' lev_histins = ',lev_histins
     1806  write(lunout,*)' lev_histLES = ',lev_histLES
     1807  write(lunout,*)' lev_histdayNMC = ',lev_histdayNMC
     1808  write(lunout,*)' ok_histNMC = ',ok_histNMC
     1809  write(lunout,*)' freq_outNMC = ',freq_outNMC
     1810  write(lunout,*)' freq_calNMC = ',freq_calNMC
     1811  write(lunout,*)' iflag_pbl = ', iflag_pbl
     1812  write(lunout,*)' iflag_thermals = ', iflag_thermals
     1813  write(lunout,*)' iflag_thermals_ed = ', iflag_thermals_ed
     1814  write(lunout,*)' iflag_thermals_optflux = ', iflag_thermals_optflux
     1815  write(lunout,*)' iflag_clos = ', iflag_clos
     1816  write(lunout,*)' type_run = ',type_run
     1817  write(lunout,*)' ok_isccp = ',ok_isccp
     1818  write(lunout,*)' ok_cosp = ',ok_cosp
     1819  write(lunout,*)' ok_mensuelCOSP = ',ok_mensuelCOSP
     1820  write(lunout,*)' ok_journeCOSP = ',ok_journeCOSP
     1821  write(lunout,*)' ok_hfCOSP =',ok_hfCOSP
     1822  write(lunout,*)' solarlong0 = ', solarlong0
     1823  write(lunout,*)' qsol0 = ', qsol0
     1824  write(lunout,*)' inertie_sol = ', inertie_sol
     1825  write(lunout,*)' inertie_ice = ', inertie_ice
     1826  write(lunout,*)' inertie_sno = ', inertie_sno
     1827  write(lunout,*)' f_cdrag_ter = ',f_cdrag_ter
     1828  write(lunout,*)' f_cdrag_oce = ',f_cdrag_oce
     1829  write(lunout,*)' f_rugoro = ',f_rugoro
     1830  write(lunout,*)' supcrit1 = ', supcrit1
     1831  write(lunout,*)' supcrit2 = ', supcrit2
     1832  write(lunout,*)' iflag_mix = ', iflag_mix
     1833  write(lunout,*)' scut = ', scut
     1834  write(lunout,*)' qqa1 = ', qqa1
     1835  write(lunout,*)' qqa2 = ', qqa2
     1836  write(lunout,*)' gammas = ', gammas
     1837  write(lunout,*)' Fmax = ', Fmax
     1838  write(lunout,*)' alphas = ', alphas
     1839  write(lunout,*)' iflag_wake = ', iflag_wake
     1840  write(lunout,*)' alp_offset = ', alp_offset
     1841
     1842  write(lunout,*)' lonmin lonmax latmin latmax bilKP_ins =',&
    18431843   lonmin_ins, lonmax_ins, latmin_ins, latmax_ins
    1844   write(numout,*)' ecrit_ hf, ins, day, mth, reg, tra, ISCCP, LES',&
     1844  write(lunout,*)' ecrit_ hf, ins, day, mth, reg, tra, ISCCP, LES',&
    18451845   ecrit_hf, ecrit_ins, ecrit_day, ecrit_mth, ecrit_reg, ecrit_tra, ecrit_ISCCP, ecrit_LES
    18461846
    1847   write(numout,*) 'ok_strato = ', ok_strato
    1848   write(numout,*) 'ok_hines = ',  ok_hines
    1849   write(numout,*) 'read_climoz = ', read_climoz
    1850   write(numout,*) 'carbon_cycle_tr = ', carbon_cycle_tr
    1851   write(numout,*) 'carbon_cycle_cpl = ', carbon_cycle_cpl
     1847  write(lunout,*) 'ok_strato = ', ok_strato
     1848  write(lunout,*) 'ok_hines = ',  ok_hines
     1849  write(lunout,*) 'read_climoz = ', read_climoz
     1850  write(lunout,*) 'carbon_cycle_tr = ', carbon_cycle_tr
     1851  write(lunout,*) 'carbon_cycle_cpl = ', carbon_cycle_cpl
    18521852 
    18531853!$OMP END MASTER
     
    18661866   use IOIPSL
    18671867   implicit none
    1868 
     1868   include "iniprint.h"
    18691869! Configuration de l'interace atm/surf
    18701870!
     
    18741874  REAL,SAVE     :: tau_calv_omp
    18751875
    1876 ! Local
    1877   integer              :: numout = 6
    18781876!
    18791877!Config Key  = tau_calv
     
    18911889 
    18921890!$OMP MASTER
    1893   write(numout,*)' ##############################################'
    1894   WRITE(numout,*)' Configuration de l''interface atm/surfaces  : '
    1895   WRITE(numout,*)' tau_calv = ',tau_calv
     1891  write(lunout,*)' ##############################################'
     1892  WRITE(lunout,*)' Configuration de l''interface atm/surfaces  : '
     1893  WRITE(lunout,*)' tau_calv = ',tau_calv
    18961894!$OMP END MASTER
    18971895
  • LMDZ5/branches/testing/libf/phylmd/cv3p1_closure.F

    r1518 r1664  
    516516        wb2(il) = sqrt(2.*max(Ale(il)+cin(il),0.))
    517517      ENDDO
    518 c
    519       IF (flag_wb==0) THEN
    520         wbeff(:) = wbmax
    521       ELSE IF (flag_wb==1) THEN
    522         wbeff(1:ncum) = wbmax/(1.+500./(ph(1:ncum,1)-plfc(1:ncum)))
    523       ELSE IF (flag_wb==2) THEN
    524         wbeff(1:ncum) = wbmax*(0.01*(ph(1:ncum,1)-plfc(1:ncum)))**2
    525       ENDIF
    526 c
     518
     519      DO il = 1, ncum
     520         IF (plfc(il) .lt. 100.) THEN
     521c        This is an irealistic value for plfc => no calculation of wbeff
     522            wbeff(il) = 100.1
     523         ELSE
     524c        Calculate wbeff
     525            IF (flag_wb==0) THEN
     526               wbeff(il) = wbmax
     527            ELSE IF (flag_wb==1) THEN
     528               wbeff(il) = wbmax/(1.+500./(ph(il,1)-plfc(il)))
     529            ELSE IF (flag_wb==2) THEN
     530               wbeff(il) = wbmax*(0.01*(ph(il,1)-plfc(il)))**2
     531            ENDIF
     532         END IF
     533      END DO
     534
     535
    527536      DO il = 1,ncum
    528537cjyg    Modification du coef de wb*wb pour conformite avec papier Wake
  • LMDZ5/branches/testing/libf/phylmd/cv3p_mixing.F

    r1519 r1664  
    8181      Rmix(F) = qqa1*Rmix1(F) + qqa2*Rmix2(F)
    8282C
    83       INTEGER ifrst
     83      INTEGER, SAVE :: ifrst
    8484      DATA ifrst/0/
    8585c$OMP THREADPRIVATE(ifrst)
  • LMDZ5/branches/testing/libf/phylmd/fisrtilp.F90

    r1507 r1664  
    147147  IF (appel1er) THEN
    148148     !
    149      PRINT*, 'fisrtilp, ninter:', ninter
    150      PRINT*, 'fisrtilp, evap_prec:', evap_prec
    151      PRINT*, 'fisrtilp, cpartiel:', cpartiel
     149     WRITE(lunout,*) 'fisrtilp, ninter:', ninter
     150     WRITE(lunout,*) 'fisrtilp, evap_prec:', evap_prec
     151     WRITE(lunout,*) 'fisrtilp, cpartiel:', cpartiel
    152152     IF (ABS(dtime/REAL(ninter)-360.0).GT.0.001) THEN
    153         PRINT*, 'fisrtilp: Ce n est pas prevu, voir Z.X.Li', dtime
    154         PRINT*, 'Je prefere un sous-intervalle de 6 minutes'
     153        WRITE(lunout,*) 'fisrtilp: Ce n est pas prevu, voir Z.X.Li', dtime
     154        WRITE(lunout,*) 'Je prefere un sous-intervalle de 6 minutes'
    155155        !         CALL abort
    156156     ENDIF
     
    616616
    617617  if (ncoreczq>0) then
    618      print*,'WARNING : ZQ dans fisrtilp ',ncoreczq,' val < 1.e-15.'
     618     WRITE(lunout,*)'WARNING : ZQ dans fisrtilp ',ncoreczq,' val < 1.e-15.'
    619619  endif
    620620
  • LMDZ5/branches/testing/libf/phylmd/fisrtilp_tr.F

    r1403 r1664  
    2424#include "YOMCST.h"
    2525#include "tracstoke.h"
     26#include "iniprint.h"
    2627c
    2728c Arguments:
     
    136137      IF (appel1er) THEN
    137138c
    138          PRINT*, 'fisrtilp, calcrat:', calcrat
    139          PRINT*, 'fisrtilp, ninter:', ninter
    140          PRINT*, 'fisrtilp, evap_prec:', evap_prec
    141          PRINT*, 'fisrtilp, cpartiel:', cpartiel
     139         WRITE(lunout,*) 'fisrtilp, calcrat:', calcrat
     140         WRITE(lunout,*) 'fisrtilp, ninter:', ninter
     141         WRITE(lunout,*) 'fisrtilp, evap_prec:', evap_prec
     142         WRITE(lunout,*) 'fisrtilp, cpartiel:', cpartiel
    142143         IF (ABS(dtime/REAL(ninter)-360.0).GT.0.001) THEN
    143           PRINT*, 'fisrtilp: Ce n est pas prevu, voir Z.X.Li', dtime
    144           PRINT*, 'Je prefere un sous-intervalle de 6 minutes'
     144          WRITE(lunout,*)
     145     $    'fisrtilp: Ce n est pas prevu, voir Z.X.Li', dtime
     146          WRITE(lunout,*) 'Je prefere un sous-intervalle de 6 minutes'
    145147          CALL abort
    146148         ENDIF
  • LMDZ5/branches/testing/libf/phylmd/hgardfou.F

    r1550 r1664  
    1111#include "YOMCST.h"
    1212#include "indicesol.h"
     13#include "iniprint.h"
    1314      REAL t(klon,klev), tsol(klon,nbsrf)
    1415      CHARACTER*(*) text
     
    2728
    2829      IF (firstcall) THEN
    29          PRINT*, 'hgardfou garantit la temperature dans [100,370] K'
     30         WRITE(lunout,*)
     31     $  'hgardfou garantit la temperature dans [100,370] K'
    3032         firstcall = .FALSE.
    3133c        DO i = 1, klon
    32 c         print*,'i=',i,'rlon=',rlon(i),'rlat=',rlat(i)
     34c         WRITE(lunout,*)'i=',i,'rlon=',rlon(i),'rlat=',rlat(i)
    3335c        ENDDO
    3436c
     
    5456           ok = .FALSE.
    5557           DO i = 1, jbad
    56              PRINT *,'i,k,temperature,lon,lat,pourc ter,oce,lic,sic =',
     58             WRITE(lunout,*)
     59     $       'i,k,temperature,lon,lat,pourc ter,oce,lic,sic =',
    5760     $       jadrs(i),k,zt(jadrs(i)),rlon(jadrs(i)),rlat(jadrs(i)),
    5861     $       (pctsrf(jadrs(i),nsrf),nsrf=1,nbsrf)
     
    7477           ok = .FALSE.
    7578           DO i = 1, jbad
    76              PRINT *,'i,k,temperature,lon,lat,pourc ter,oce,lic,sic =',
     79             WRITE(lunout,*)
     80     $       'i,k,temperature,lon,lat,pourc ter,oce,lic,sic =',
    7781     $       jadrs(i),k,zt(jadrs(i)),rlon(jadrs(i)),rlat(jadrs(i)),
    7882     $       (pctsrf(jadrs(i),nsrf),nsrf=1,nbsrf)
     
    99103           ok = .FALSE.
    100104           DO i = 1, jbad
    101             PRINT *,'i,nsrf,temperature,lon,lat,pourc ter,oce,lic,sic ='
     105            WRITE(lunout,*)
     106     $      'i,nsrf,temperature,lon,lat,pourc ter,oce,lic,sic ='
    102107     $      ,jadrs(i),nsrf,zt(jadrs(i)),rlon(jadrs(i)),rlat(jadrs(i))
    103108     $      ,pctsrf(jadrs(i),nsrf)
     
    119124           ok = .FALSE.
    120125           DO i = 1, jbad
    121             PRINT *,'i,nsrf,temperature,lon,lat,pourc ter,oce,lic,sic ='
     126            WRITE(lunout,*)
     127     $      'i,nsrf,temperature,lon,lat,pourc ter,oce,lic,sic ='
    122128     $      ,jadrs(i),nsrf,zt(jadrs(i)),rlon(jadrs(i)),rlat(jadrs(i))
    123129     $      ,pctsrf(jadrs(i),nsrf)
  • LMDZ5/branches/testing/libf/phylmd/ini_histrac.h

    r1403 r1664  
    22! $Id $
    33!
    4   IF (ecrit_tra>0. .AND. config_inca == 'none') THEN
     4  IF (ecrit_tra>0.) THEN
    55!$OMP MASTER
    66     CALL ymds2ju(annee_ref, 1, day_ref, 0.0, zjulian)
     
    124124     CALL histend(nid_tra)
    125125!$OMP END MASTER
    126   END IF ! ecrit_tra>0. .AND. config_inca == 'none'
     126  END IF ! ecrit_tra>0.
    127127 
  • LMDZ5/branches/testing/libf/phylmd/init_phys_lmdz.F90

    r1146 r1664  
    66  USE mod_grid_phy_lmdz
    77  USE dimphy, ONLY : Init_dimphy
     8  USE infotrac, ONLY : type_trac
     9#ifdef REPROBUS
     10  USE CHEM_REP, ONLY : Init_chem_rep_phys
     11#endif
     12
    813  IMPLICIT NONE
    914 
     
    1924!$OMP PARALLEL
    2025    CALL Init_dimphy(klon_omp,nbp_lev)
     26
     27! Initialization of Reprobus
     28    IF (type_trac == 'repr') THEN
     29#ifdef REPROBUS
     30       CALL Init_chem_rep_phys(klon_omp,nbp_lev)
     31#endif
     32    END IF
     33
    2134!$OMP END PARALLEL
    2235 
  • LMDZ5/branches/testing/libf/phylmd/mod_phys_lmdz_mpi_data.F90

    r1001 r1664  
    167167  SUBROUTINE print_module_data
    168168  IMPLICIT NONE
    169  
    170  
    171     PRINT *, 'ii_begin =', ii_begin
    172     PRINT *, 'ii_end =', ii_end
    173     PRINT *, 'jj_begin =',jj_begin
    174     PRINT *, 'jj_end =', jj_end
    175     PRINT *, 'jj_nb =', jj_nb
    176     PRINT *, 'ij_begin =', ij_begin
    177     PRINT *, 'ij_end =', ij_end
    178     PRINT *, 'ij_nb =', ij_nb
    179     PRINT *, 'klon_mpi_begin =', klon_mpi_begin
    180     PRINT *, 'klon_mpi_end =', klon_mpi_end
    181     PRINT *, 'klon_mpi =', klon_mpi
    182     PRINT *, 'jj_para_nb =', jj_para_nb
    183     PRINT *, 'jj_para_begin =', jj_para_begin
    184     PRINT *, 'jj_para_end =', jj_para_end
    185     PRINT *, 'ii_para_begin =', ii_para_begin
    186     PRINT *, 'ii_para_end =', ii_para_end
    187     PRINT *, 'ij_para_nb =', ij_para_nb
    188     PRINT *, 'ij_para_begin =', ij_para_begin
    189     PRINT *, 'ij_para_end =', ij_para_end
    190     PRINT *, 'klon_mpi_para_nb =', klon_mpi_para_nb
    191     PRINT *, 'klon_mpi_para_begin =', klon_mpi_para_begin
    192     PRINT *, 'klon_mpi_para_end  =', klon_mpi_para_end
    193     PRINT *, 'mpi_rank =', mpi_rank
    194     PRINT *, 'mpi_size =', mpi_size
    195     PRINT *, 'mpi_root =', mpi_root
    196     PRINT *, 'is_mpi_root =', is_mpi_root
    197     PRINT *, 'is_north_pole =', is_north_pole
    198     PRINT *, 'is_south_pole =', is_south_pole
    199     PRINT *, 'COMM_LMDZ_PHY =', COMM_LMDZ_PHY
     169  INCLUDE "iniprint.h"
     170 
     171    WRITE(lunout,*) 'ii_begin =', ii_begin
     172    WRITE(lunout,*) 'ii_end =', ii_end
     173    WRITE(lunout,*) 'jj_begin =',jj_begin
     174    WRITE(lunout,*) 'jj_end =', jj_end
     175    WRITE(lunout,*) 'jj_nb =', jj_nb
     176    WRITE(lunout,*) 'ij_begin =', ij_begin
     177    WRITE(lunout,*) 'ij_end =', ij_end
     178    WRITE(lunout,*) 'ij_nb =', ij_nb
     179    WRITE(lunout,*) 'klon_mpi_begin =', klon_mpi_begin
     180    WRITE(lunout,*) 'klon_mpi_end =', klon_mpi_end
     181    WRITE(lunout,*) 'klon_mpi =', klon_mpi
     182    WRITE(lunout,*) 'jj_para_nb =', jj_para_nb
     183    WRITE(lunout,*) 'jj_para_begin =', jj_para_begin
     184    WRITE(lunout,*) 'jj_para_end =', jj_para_end
     185    WRITE(lunout,*) 'ii_para_begin =', ii_para_begin
     186    WRITE(lunout,*) 'ii_para_end =', ii_para_end
     187    WRITE(lunout,*) 'ij_para_nb =', ij_para_nb
     188    WRITE(lunout,*) 'ij_para_begin =', ij_para_begin
     189    WRITE(lunout,*) 'ij_para_end =', ij_para_end
     190    WRITE(lunout,*) 'klon_mpi_para_nb =', klon_mpi_para_nb
     191    WRITE(lunout,*) 'klon_mpi_para_begin =', klon_mpi_para_begin
     192    WRITE(lunout,*) 'klon_mpi_para_end  =', klon_mpi_para_end
     193    WRITE(lunout,*) 'mpi_rank =', mpi_rank
     194    WRITE(lunout,*) 'mpi_size =', mpi_size
     195    WRITE(lunout,*) 'mpi_root =', mpi_root
     196    WRITE(lunout,*) 'is_mpi_root =', is_mpi_root
     197    WRITE(lunout,*) 'is_north_pole =', is_north_pole
     198    WRITE(lunout,*) 'is_south_pole =', is_south_pole
     199    WRITE(lunout,*) 'COMM_LMDZ_PHY =', COMM_LMDZ_PHY
    200200 
    201201  END SUBROUTINE print_module_data
  • LMDZ5/branches/testing/libf/phylmd/mod_phys_lmdz_omp_data.F90

    r1403 r1664  
    9191  SUBROUTINE Print_module_data
    9292  IMPLICIT NONE
     93  INCLUDE "iniprint.h"
    9394
    9495!$OMP CRITICAL 
    95   PRINT *,'--------> TASK ',omp_rank
    96   PRINT *,'omp_size =',omp_size
    97   PRINT *,'omp_rank =',omp_rank
    98   PRINT *,'is_omp_root =',is_omp_root
    99   PRINT *,'klon_omp_para_nb =',klon_omp_para_nb
    100   PRINT *,'klon_omp_para_begin =',klon_omp_para_begin
    101   PRINT *,'klon_omp_para_end =',klon_omp_para_end   
    102   PRINT *,'klon_omp =',klon_omp
    103   PRINT *,'klon_omp_begin =',klon_omp_begin
    104   PRINT *,'klon_omp_end =',klon_omp_end   
     96  WRITE(lunout,*)'--------> TASK ',omp_rank
     97  WRITE(lunout,*)'omp_size =',omp_size
     98  WRITE(lunout,*)'omp_rank =',omp_rank
     99  WRITE(lunout,*)'is_omp_root =',is_omp_root
     100  WRITE(lunout,*)'klon_omp_para_nb =',klon_omp_para_nb
     101  WRITE(lunout,*)'klon_omp_para_begin =',klon_omp_para_begin
     102  WRITE(lunout,*)'klon_omp_para_end =',klon_omp_para_end   
     103  WRITE(lunout,*)'klon_omp =',klon_omp
     104  WRITE(lunout,*)'klon_omp_begin =',klon_omp_begin
     105  WRITE(lunout,*)'klon_omp_end =',klon_omp_end   
    105106!$OMP END CRITICAL
    106107
  • LMDZ5/branches/testing/libf/phylmd/mod_phys_lmdz_para.F90

    r1327 r1664  
    4747  USE mod_grid_phy_lmdz
    4848  IMPLICIT NONE
    49  
     49    INCLUDE "iniprint.h"
     50 
    5051    REAL :: Test_Field1d_glo(klon_glo,nbp_lev)
    5152    REAL :: tmp1d_glo(klon_glo,nbp_lev)
     
    8081!$OMP MASTER 
    8182      Checksum=sum(Test_Field1d_glo-tmp1d_glo)
    82       PRINT *, "------> Checksum =",Checksum," MUST BE 0"
     83      WRITE(lunout,*) "------> Checksum =",Checksum," MUST BE 0"
    8384!$OMP END MASTER
    8485    ENDIF
     
    9293!$OMP MASTER 
    9394      Checksum=sum(Test_Field1d_glo-tmp1d_glo)
    94       PRINT *, "------> Checksum =",Checksum," MUST BE 0"
     95      WRITE(lunout,*) "------> Checksum =",Checksum," MUST BE 0"
    9596!$OMP END MASTER
    9697    ENDIF
     
    102103!$OMP MASTER 
    103104      Checksum=sum(Test_Field1d_glo*omp_size*mpi_size-tmp1d_glo)
    104       PRINT *, "------> Checksum =",Checksum," MUST BE 0"
     105      WRITE(lunout,*) "------> Checksum =",Checksum," MUST BE 0"
    105106!$OMP END MASTER
    106107    ENDIF
  • LMDZ5/branches/testing/libf/phylmd/pbl_surface_mod.F90

    r1539 r1664  
    385385    REAL, DIMENSION(klon)              :: yts, yrugos, ypct, yz0_new
    386386    REAL, DIMENSION(klon)              :: yalb, yalb1, yalb2
    387     REAL, DIMENSION(klon)              :: yu1, yv1
     387    REAL, DIMENSION(klon)              :: yu1, yv1,ytoto
    388388    REAL, DIMENSION(klon)              :: ysnow, yqsurf, yagesno, yqsol
    389389    REAL, DIMENSION(klon)              :: yrain_f, ysnow_f
     
    439439    LOGICAL, PARAMETER                 :: zxli=.FALSE. ! utiliser un jeu de fonctions simples
    440440    LOGICAL, PARAMETER                 :: check=.FALSE.
     441    REAL, DIMENSION(klon)              :: Kech_h       ! Coefficient d'echange pour l'energie
    441442
    442443! For debugging with IOIPSL
     
    900901          y_flux_q1(:) =  flat/RLVTT
    901902          yfluxlat(:) =  flat
     903
     904          Kech_h(:) = ycdragh(:) * (1.0+SQRT(yu(:,1)**2+yv(:,1)**2)) * &
     905               ypplay(:,1)/(RD*yt(:,1))
     906          ytoto(:)=(1./RCPD)*(AcoefH(:)+BcoefH(:)*y_flux_t1(:)*dtime)
     907          ytsurf_new(:)=ytoto(:)-y_flux_t1(:)/(Kech_h(:)*RCPD)
     908          y_d_ts(:) = ytsurf_new(:) - yts(:)
     909
    902910       ELSE
    903911          y_flux_t1(:) =  yfluxsens(:)
  • LMDZ5/branches/testing/libf/phylmd/phys_output_mod.F90

    r1546 r1664  
    1717
    1818
    19    integer, parameter                           :: nfiles = 6
    20    logical, dimension(nfiles), save             :: clef_files
    21    logical, dimension(nfiles), save             :: clef_stations
    22    integer, dimension(nfiles), save             :: lev_files
    23    integer, dimension(nfiles), save             :: nid_files
    24    integer, dimension(nfiles), save  :: nnid_files
     19  integer, parameter                           :: nfiles = 6
     20  logical, dimension(nfiles), save             :: clef_files
     21  logical, dimension(nfiles), save             :: clef_stations
     22  integer, dimension(nfiles), save             :: lev_files
     23  integer, dimension(nfiles), save             :: nid_files
     24  integer, dimension(nfiles), save  :: nnid_files
    2525!!$OMP THREADPRIVATE(clef_files, clef_stations, lev_files,nid_files,nnid_files)
    26    integer, dimension(nfiles), private, save :: nnhorim
    27  
    28    integer, dimension(nfiles), private, save :: nhorim, nvertm
    29    integer, dimension(nfiles), private, save :: nvertap, nvertbp, nvertAlt
    30 !   integer, dimension(nfiles), private, save :: nvertp0
    31    real, dimension(nfiles), private, save                :: zoutm
    32    real,                    private, save                :: zdtime
    33    CHARACTER(len=20), dimension(nfiles), private, save   :: type_ecri
    34 !$OMP THREADPRIVATE(nhorim, nvertm, zoutm,zdtime,type_ecri)
    35 
    36 !   integer, save                     :: nid_hf3d
     26  integer, dimension(nfiles), private, save :: nnhorim
     27
     28  integer, dimension(nfiles), private, save :: nhorim, nvertm
     29  integer, dimension(nfiles), private, save :: nvertap, nvertbp, nvertAlt
     30  !   integer, dimension(nfiles), private, save :: nvertp0
     31  real, dimension(nfiles), private, save                :: zoutm
     32  real,                    private, save                :: zdtime
     33  CHARACTER(len=20), dimension(nfiles), private, save   :: type_ecri
     34  !$OMP THREADPRIVATE(nhorim, nvertm, zoutm,zdtime,type_ecri)
     35
     36  !   integer, save                     :: nid_hf3d
    3737
    3838!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    39 !! Definition pour chaque variable du niveau d ecriture dans chaque fichier
     39  !! Definition pour chaque variable du niveau d ecriture dans chaque fichier
    4040!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!/ histmth, histday, histhf, histins /),'!!!!!!!!!!!!
    4141!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    4545
    4646  TYPE ctrl_out
    47    integer,dimension(6) :: flag
    48    character(len=20)     :: name
     47     integer,dimension(6) :: flag
     48     character(len=20)     :: name
    4949  END TYPE ctrl_out
    5050
     
    6161  type(ctrl_out),save :: o_contfracOR   = ctrl_out((/ 10, 1,  1, 10, 10, 10 /),'contfracOR')
    6262  type(ctrl_out),save :: o_aireTER      = ctrl_out((/ 10, 10, 1, 10, 10, 10 /),'aireTER')
    63  
     63
    6464!!! 2D
    6565  type(ctrl_out),save :: o_flat         = ctrl_out((/ 5, 1, 10, 10, 5, 10 /),'flat')
     
    7070  type(ctrl_out),save :: o_t2m_max      = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'t2m_max')
    7171  type(ctrl_out),save,dimension(4) :: o_t2m_srf      = (/ ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'t2m_ter'), &
    72                                                  ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'t2m_lic'), &
    73                                                  ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'t2m_oce'), &
    74                                                  ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'t2m_sic') /)
     72       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'t2m_lic'), &
     73       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'t2m_oce'), &
     74       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'t2m_sic') /)
    7575
    7676  type(ctrl_out),save :: o_wind10m      = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'wind10m')
     
    8484
    8585  type(ctrl_out),save,dimension(4) :: o_u10m_srf     = (/ ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'u10m_ter'), &
    86                                               ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'u10m_lic'), &
    87                                               ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'u10m_oce'), &
    88                                               ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'u10m_sic') /)
     86       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'u10m_lic'), &
     87       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'u10m_oce'), &
     88       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'u10m_sic') /)
    8989
    9090  type(ctrl_out),save,dimension(4) :: o_v10m_srf     = (/ ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'v10m_ter'), &
    91                                               ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'v10m_lic'), &
    92                                               ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'v10m_oce'), &
    93                                               ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'v10m_sic') /)
     91       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'v10m_lic'), &
     92       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'v10m_oce'), &
     93       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'v10m_sic') /)
    9494
    9595  type(ctrl_out),save :: o_qsol         = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'qsol')
     
    103103  type(ctrl_out),save :: o_evap         = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'evap')
    104104  type(ctrl_out),save,dimension(4) :: o_evap_srf     = (/ ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'evap_ter'), &
    105                                            ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'evap_lic'), &
    106                                            ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'evap_oce'), &
    107                                            ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'evap_sic') /)
     105       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'evap_lic'), &
     106       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'evap_oce'), &
     107       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'evap_sic') /)
    108108  type(ctrl_out),save :: o_msnow       = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'msnow')
    109109  type(ctrl_out),save :: o_fsnow       = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fsnow')
     
    124124  type(ctrl_out),save :: o_SWdn200clr   = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'SWdn200clr')
    125125
    126 ! arajouter
    127 !  type(ctrl_out),save :: o_LWupTOA     = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'LWupTOA')
    128 !  type(ctrl_out),save :: o_LWupTOAclr  = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'LWupTOAclr')
    129 !  type(ctrl_out),save :: o_LWdnTOA     = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'LWdnTOA')
    130 !  type(ctrl_out),save :: o_LWdnTOAclr  = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'LWdnTOAclr')
     126  ! arajouter
     127  !  type(ctrl_out),save :: o_LWupTOA     = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'LWupTOA')
     128  !  type(ctrl_out),save :: o_LWupTOAclr  = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'LWupTOAclr')
     129  !  type(ctrl_out),save :: o_LWdnTOA     = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'LWdnTOA')
     130  !  type(ctrl_out),save :: o_LWdnTOAclr  = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'LWdnTOAclr')
    131131
    132132  type(ctrl_out),save :: o_LWup200      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'LWup200')
     
    157157  type(ctrl_out),save :: o_tauy         = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'tauy')
    158158  type(ctrl_out),save,dimension(4) :: o_taux_srf     = (/ ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'taux_ter'), &
    159                                                  ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'taux_lic'), &
    160                                                  ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'taux_oce'), &
    161                                                  ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'taux_sic') /)
     159       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'taux_lic'), &
     160       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'taux_oce'), &
     161       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'taux_sic') /)
    162162
    163163  type(ctrl_out),save,dimension(4) :: o_tauy_srf     = (/ ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tauy_ter'), &
    164                                                  ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tauy_lic'), &
    165                                                  ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tauy_oce'), &
    166                                                  ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tauy_sic') /)
     164       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tauy_lic'), &
     165       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tauy_oce'), &
     166       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tauy_sic') /)
    167167
    168168
    169169  type(ctrl_out),save,dimension(4) :: o_pourc_srf    = (/ ctrl_out((/ 1, 7, 10, 10, 10, 10 /),'pourc_ter'), &
    170                                                  ctrl_out((/ 1, 7, 10, 10, 10, 10 /),'pourc_lic'), &
    171                                                  ctrl_out((/ 1, 7, 10, 10, 10, 10 /),'pourc_oce'), &
    172                                                  ctrl_out((/ 1, 7, 10, 10, 10, 10 /),'pourc_sic') /)     
     170       ctrl_out((/ 1, 7, 10, 10, 10, 10 /),'pourc_lic'), &
     171       ctrl_out((/ 1, 7, 10, 10, 10, 10 /),'pourc_oce'), &
     172       ctrl_out((/ 1, 7, 10, 10, 10, 10 /),'pourc_sic') /)     
    173173
    174174  type(ctrl_out),save,dimension(4) :: o_fract_srf    = (/ ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'fract_ter'), &
    175                                                  ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'fract_lic'), &
    176                                                  ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'fract_oce'), &
    177                                                  ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'fract_sic') /)
     175       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'fract_lic'), &
     176       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'fract_oce'), &
     177       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'fract_sic') /)
    178178
    179179  type(ctrl_out),save,dimension(4) :: o_tsol_srf     = (/ ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tsol_ter'), &
    180                                                  ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tsol_lic'), &
    181                                                  ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tsol_oce'), &
    182                                                  ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tsol_sic') /)
     180       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tsol_lic'), &
     181       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tsol_oce'), &
     182       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tsol_sic') /)
    183183
    184184  type(ctrl_out),save,dimension(4) :: o_sens_srf     = (/ ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'sens_ter'), &
    185                                                  ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'sens_lic'), &
    186                                                  ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'sens_oce'), &
    187                                                  ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'sens_sic') /)
     185       ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'sens_lic'), &
     186       ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'sens_oce'), &
     187       ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'sens_sic') /)
    188188
    189189  type(ctrl_out),save,dimension(4) :: o_lat_srf      = (/ ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'lat_ter'), &
    190                                                  ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'lat_lic'), &
    191                                                  ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'lat_oce'), &
    192                                                  ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'lat_sic') /)
     190       ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'lat_lic'), &
     191       ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'lat_oce'), &
     192       ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'lat_sic') /)
    193193
    194194  type(ctrl_out),save,dimension(4) :: o_flw_srf      = (/ ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'flw_ter'), &
    195                                                  ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'flw_lic'), &
    196                                                  ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'flw_oce'), &
    197                                                  ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'flw_sic') /)
    198                                                  
     195       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'flw_lic'), &
     196       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'flw_oce'), &
     197       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'flw_sic') /)
     198
    199199  type(ctrl_out),save,dimension(4) :: o_fsw_srf      = (/ ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fsw_ter'), &
    200                                                   ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fsw_lic'), &
    201                                                   ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fsw_oce'), &
    202                                                   ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fsw_sic') /)
     200       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fsw_lic'), &
     201       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fsw_oce'), &
     202       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fsw_sic') /)
    203203
    204204  type(ctrl_out),save,dimension(4) :: o_wbils_srf    = (/ ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbils_ter'), &
    205                                                  ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbils_lic'), &
    206                                                  ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbils_oce'), &
    207                                                  ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbils_sic') /)
     205       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbils_lic'), &
     206       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbils_oce'), &
     207       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbils_sic') /)
    208208
    209209  type(ctrl_out),save,dimension(4) :: o_wbilo_srf    = (/ ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbilo_ter'), &
    210                                                      ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbilo_lic'), &
    211                                                  ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbilo_oce'), &
    212                                                  ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbilo_sic') /)
     210       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbilo_lic'), &
     211       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbilo_oce'), &
     212       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbilo_sic') /)
    213213
    214214
     
    226226  type(ctrl_out),save :: o_uq           = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'uq')
    227227  type(ctrl_out),save :: o_vq           = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'vq')
    228  
     228
    229229  type(ctrl_out),save :: o_cape         = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'cape')
    230230  type(ctrl_out),save :: o_pbase        = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'pbase')
     
    240240  type(ctrl_out),save :: o_s_lcl        = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_lcl')
    241241  type(ctrl_out),save :: o_s_therm      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_therm')
    242 !IM : Les champs suivants (s_capCL, s_oliqCL, s_cteiCL, s_trmb1, s_trmb2, s_trmb3) ne sont pas definis dans HBTM.F
    243 ! type(ctrl_out),save :: o_s_capCL      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_capCL')
    244 ! type(ctrl_out),save :: o_s_oliqCL     = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_oliqCL')
    245 ! type(ctrl_out),save :: o_s_cteiCL     = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_cteiCL')
    246 ! type(ctrl_out),save :: o_s_trmb1      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_trmb1')
    247 ! type(ctrl_out),save :: o_s_trmb2      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_trmb2')
    248 ! type(ctrl_out),save :: o_s_trmb3      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_trmb3')
     242  !IM : Les champs suivants (s_capCL, s_oliqCL, s_cteiCL, s_trmb1, s_trmb2, s_trmb3) ne sont pas definis dans HBTM.F
     243  ! type(ctrl_out),save :: o_s_capCL      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_capCL')
     244  ! type(ctrl_out),save :: o_s_oliqCL     = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_oliqCL')
     245  ! type(ctrl_out),save :: o_s_cteiCL     = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_cteiCL')
     246  ! type(ctrl_out),save :: o_s_trmb1      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_trmb1')
     247  ! type(ctrl_out),save :: o_s_trmb2      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_trmb2')
     248  ! type(ctrl_out),save :: o_s_trmb3      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_trmb3')
    249249
    250250  type(ctrl_out),save :: o_slab_bils    = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'slab_bils_oce')
     
    261261
    262262
    263 ! Champs interpolles sur des niveaux de pression ??? a faire correctement
    264                                              
     263  ! Champs interpolles sur des niveaux de pression ??? a faire correctement
     264
    265265  type(ctrl_out),save,dimension(7) :: o_uSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u850'), &
    266                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u700'), &
    267                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u500'), &
    268                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u200'), &
    269                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u100'), &
    270                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u50'), &
    271                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u10') /)
    272                                                      
     266       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u700'), &
     267       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u500'), &
     268       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u200'), &
     269       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u100'), &
     270       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u50'), &
     271       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u10') /)
     272
    273273
    274274  type(ctrl_out),save,dimension(7) :: o_vSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v850'), &
    275                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v700'), &
    276                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v500'), &
    277                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v200'), &
    278                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v100'), &
    279                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v50'), &
    280                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v10') /)
     275       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v700'), &
     276       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v500'), &
     277       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v200'), &
     278       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v100'), &
     279       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v50'), &
     280       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v10') /)
    281281
    282282  type(ctrl_out),save,dimension(7) :: o_wSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w850'), &
    283                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w700'), &
    284                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w500'), &
    285                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w200'), &
    286                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w100'), &
    287                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w50'), &
    288                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w10') /)
     283       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w700'), &
     284       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w500'), &
     285       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w200'), &
     286       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w100'), &
     287       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w50'), &
     288       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w10') /)
    289289
    290290  type(ctrl_out),save,dimension(7) :: o_tSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t850'), &
    291                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t700'), &
    292                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t500'), &
    293                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t200'), &
    294                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t100'), &
    295                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t50'), &
    296                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t10') /)
     291       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t700'), &
     292       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t500'), &
     293       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t200'), &
     294       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t100'), &
     295       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t50'), &
     296       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t10') /)
    297297
    298298  type(ctrl_out),save,dimension(7) :: o_qSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q850'), &
    299                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q700'), &
    300                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q500'), &
    301                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q200'), &
    302                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q100'), &
    303                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q50'), &
    304                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q10') /)
     299       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q700'), &
     300       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q500'), &
     301       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q200'), &
     302       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q100'), &
     303       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q50'), &
     304       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q10') /)
    305305
    306306  type(ctrl_out),save,dimension(7) :: o_zSTDlevs   = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z850'), &
    307                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z700'), &
    308                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z500'), &
    309                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z200'), &
    310                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z100'), &
    311                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z50'), &
    312                                                      ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z10') /)
     307       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z700'), &
     308       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z500'), &
     309       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z200'), &
     310       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z100'), &
     311       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z50'), &
     312       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z10') /)
    313313
    314314
     
    318318  type(ctrl_out),save :: o_dthmin       = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'dthmin')
    319319  type(ctrl_out),save,dimension(4) :: o_u10_srf      = (/ ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'u10_ter'), &
    320                                                      ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'u10_lic'), &
    321                                                      ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'u10_oce'), &
    322                                                      ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'u10_sic') /)
     320       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'u10_lic'), &
     321       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'u10_oce'), &
     322       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'u10_sic') /)
    323323
    324324  type(ctrl_out),save,dimension(4) :: o_v10_srf      = (/ ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'v10_ter'), &
    325                                                      ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'v10_lic'), &
    326                                                      ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'v10_oce'), &
    327                                                      ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'v10_sic') /)
     325       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'v10_lic'), &
     326       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'v10_oce'), &
     327       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'v10_sic') /)
    328328
    329329  type(ctrl_out),save :: o_cldtau       = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'cldtau')                     
     
    339339
    340340  type(ctrl_out),save,dimension(4) :: o_tke_srf      = (/ ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_ter'), &
    341                                                      ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_lic'), &
    342                                                      ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_oce'), &
    343                                                      ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_sic') /)
     341       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_lic'), &
     342       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_oce'), &
     343       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_sic') /)
    344344
    345345  type(ctrl_out),save,dimension(4) :: o_tke_max_srf  = (/ ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_max_ter'), &
    346                                                      ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_max_lic'), &
    347                                                      ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_max_oce'), &
    348                                                      ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_max_sic') /)
     346       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_max_lic'), &
     347       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_max_oce'), &
     348       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_max_sic') /)
    349349
    350350  type(ctrl_out),save :: o_kz           = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'kz')
     
    370370
    371371  type(ctrl_out),save,dimension(10) :: o_tausumaero  = (/ ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASBCM'), &
    372                                                      ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASPOMM'), &
    373                                                      ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASSO4M'), &
    374                                                      ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_CSSO4M'), &
    375                                                      ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_SSSSM'), &
    376                                                      ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASSSM'), &
    377                                                      ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_CSSSM'), &
    378                                                      ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_CIDUSTM'), &
    379                                                      ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_AIBCM'), &
    380                                                      ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_AIPOMM') /)
     372       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASPOMM'), &
     373       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASSO4M'), &
     374       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_CSSO4M'), &
     375       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_SSSSM'), &
     376       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASSSM'), &
     377       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_CSSSM'), &
     378       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_CIDUSTM'), &
     379       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_AIBCM'), &
     380       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_AIPOMM') /)
    381381
    382382  type(ctrl_out),save :: o_od550aer     = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'od550aer')
     
    465465
    466466  type(ctrl_out),save,dimension(4) :: o_albe_srf     = (/ ctrl_out((/ 3, 7, 10, 7, 10, 10 /),'albe_ter'), &
    467                                                      ctrl_out((/ 3, 7, 10, 7, 10, 10 /),'albe_lic'), &
    468                                                      ctrl_out((/ 3, 7, 10, 7, 10, 10 /),'albe_oce'), &
    469                                                      ctrl_out((/ 3, 7, 10, 7, 10, 10 /),'albe_sic') /)
     467       ctrl_out((/ 3, 7, 10, 7, 10, 10 /),'albe_lic'), &
     468       ctrl_out((/ 3, 7, 10, 7, 10, 10 /),'albe_oce'), &
     469       ctrl_out((/ 3, 7, 10, 7, 10, 10 /),'albe_sic') /)
    470470
    471471  type(ctrl_out),save,dimension(4) :: o_ages_srf     = (/ ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'ages_ter'), &
    472                                                      ctrl_out((/ 3, 10, 10, 10, 10, 10 /),'ages_lic'), &
    473                                                      ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'ages_oce'), &
    474                                                      ctrl_out((/ 3, 10, 10, 10, 10, 10 /),'ages_sic') /)
     472       ctrl_out((/ 3, 10, 10, 10, 10, 10 /),'ages_lic'), &
     473       ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'ages_oce'), &
     474       ctrl_out((/ 3, 10, 10, 10, 10, 10 /),'ages_sic') /)
    475475
    476476  type(ctrl_out),save,dimension(4) :: o_rugs_srf     = (/ ctrl_out((/ 3, 6, 10, 10, 10, 10 /),'rugs_ter'), &
    477                                                      ctrl_out((/ 3, 6, 10, 10, 10, 10 /),'rugs_lic'), &
    478                                                      ctrl_out((/ 3, 6, 10, 10, 10, 10 /),'rugs_oce'), &
    479                                                      ctrl_out((/ 3, 6, 10, 10, 10, 10 /),'rugs_sic') /)
     477       ctrl_out((/ 3, 6, 10, 10, 10, 10 /),'rugs_lic'), &
     478       ctrl_out((/ 3, 6, 10, 10, 10, 10 /),'rugs_oce'), &
     479       ctrl_out((/ 3, 6, 10, 10, 10, 10 /),'rugs_sic') /)
    480480
    481481  type(ctrl_out),save :: o_alb1         = ctrl_out((/ 3, 10, 10, 10, 10, 10 /),'alb1')
     
    602602
    603603
    604     CONTAINS
     604CONTAINS
    605605
    606606!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    607607!!!!!!!!! Ouverture des fichier et definition des variable de sortie !!!!!!!!
    608 !! histbeg, histvert et histdef
     608  !! histbeg, histvert et histdef
    609609!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    610  
     610
    611611  SUBROUTINE phys_output_open(rlon,rlat,pim,tabij,ipt,jpt,plon,plat, &
    612612       jjmp1,nlevSTD,clevSTD,nbteta, &
     
    617617       new_aod, aerosol_couple)   
    618618
    619   USE iophy
    620   USE dimphy
    621   USE infotrac
    622   USE ioipsl
    623   USE mod_phys_lmdz_para
    624   USE aero_mod, only : naero_spc,name_aero
    625 
    626   IMPLICIT NONE
    627   include "dimensions.h"
    628   include "temps.h"
    629   include "indicesol.h"
    630   include "clesphys.h"
    631   include "thermcell.h"
    632   include "comvert.h"
     619    USE iophy
     620    USE dimphy
     621    USE infotrac
     622    USE ioipsl
     623    USE mod_phys_lmdz_para
     624    USE aero_mod, only : naero_spc,name_aero
     625
     626    IMPLICIT NONE
     627    include "dimensions.h"
     628    include "temps.h"
     629    include "indicesol.h"
     630    include "clesphys.h"
     631    include "thermcell.h"
     632    include "comvert.h"
     633    include "iniprint.h"
    633634
    634635    real,dimension(klon),intent(in) :: rlon
     
    640641    REAL,dimension(pim,2) :: plat_bounds, plon_bounds
    641642
    642   integer                               :: jjmp1
    643   integer                               :: nbteta, nlevSTD, radpas
    644   logical                               :: ok_mensuel, ok_journe, ok_hf, ok_instan
    645   logical                               :: ok_LES,ok_ade,ok_aie
    646   logical                               :: new_aod, aerosol_couple
    647   integer, intent(in)::  read_climoz ! read ozone climatology
    648   !     Allowed values are 0, 1 and 2
    649   !     0: do not read an ozone climatology
    650   !     1: read a single ozone climatology that will be used day and night
    651   !     2: read two ozone climatologies, the average day and night
    652   !     climatology and the daylight climatology
    653 
    654   real                                  :: dtime
    655   integer                               :: idayref
    656   real                                  :: zjulian
    657   real, dimension(klev)                 :: Ahyb, Bhyb, Alt
    658   character(len=4), dimension(nlevSTD)  :: clevSTD
    659   integer                               :: nsrf, k, iq, iiq, iff, i, j, ilev
    660   integer                               :: naero
    661   logical                               :: ok_veget
    662   integer                               :: iflag_pbl
    663   CHARACTER(len=4)                      :: bb2
    664   CHARACTER(len=2)                      :: bb3
    665   character(len=6)                      :: type_ocean
    666   CHARACTER(len=3)                      :: ctetaSTD(nbteta)
    667   real, dimension(nfiles)               :: ecrit_files
    668   CHARACTER(len=20), dimension(nfiles)  :: phys_out_filenames
    669   INTEGER, dimension(iim*jjmp1)         ::  ndex2d
    670   INTEGER, dimension(iim*jjmp1*klev)    :: ndex3d
    671   integer                               :: imin_ins, imax_ins
    672   integer                               :: jmin_ins, jmax_ins
    673   integer, dimension(nfiles)            :: phys_out_levmin, phys_out_levmax
    674   integer, dimension(nfiles)            :: phys_out_filelevels
    675   CHARACTER(len=20), dimension(nfiles)  :: type_ecri_files, phys_out_filetypes
    676   character(len=20), dimension(nfiles)  :: chtimestep   = (/ 'DefFreq', 'DefFreq','DefFreq', 'DefFreq', 'DefFreq', 'DefFreq' /)
    677   logical, dimension(nfiles)            :: phys_out_filekeys
    678   logical, dimension(nfiles)            :: phys_out_filestations
     643    integer                               :: jjmp1
     644    integer                               :: nbteta, nlevSTD, radpas
     645    logical                               :: ok_mensuel, ok_journe, ok_hf, ok_instan
     646    logical                               :: ok_LES,ok_ade,ok_aie
     647    logical                               :: new_aod, aerosol_couple
     648    integer, intent(in)::  read_climoz ! read ozone climatology
     649    !     Allowed values are 0, 1 and 2
     650    !     0: do not read an ozone climatology
     651    !     1: read a single ozone climatology that will be used day and night
     652    !     2: read two ozone climatologies, the average day and night
     653    !     climatology and the daylight climatology
     654
     655    real                                  :: dtime
     656    integer                               :: idayref
     657    real                                  :: zjulian
     658    real, dimension(klev)                 :: Ahyb, Bhyb, Alt
     659    character(len=4), dimension(nlevSTD)  :: clevSTD
     660    integer                               :: nsrf, k, iq, iiq, iff, i, j, ilev
     661    integer                               :: naero
     662    logical                               :: ok_veget
     663    integer                               :: iflag_pbl
     664    CHARACTER(len=4)                      :: bb2
     665    CHARACTER(len=2)                      :: bb3
     666    character(len=6)                      :: type_ocean
     667    CHARACTER(len=3)                      :: ctetaSTD(nbteta)
     668    real, dimension(nfiles)               :: ecrit_files
     669    CHARACTER(len=20), dimension(nfiles)  :: phys_out_filenames
     670    INTEGER, dimension(iim*jjmp1)         ::  ndex2d
     671    INTEGER, dimension(iim*jjmp1*klev)    :: ndex3d
     672    integer                               :: imin_ins, imax_ins
     673    integer                               :: jmin_ins, jmax_ins
     674    integer, dimension(nfiles)            :: phys_out_levmin, phys_out_levmax
     675    integer, dimension(nfiles)            :: phys_out_filelevels
     676    CHARACTER(len=20), dimension(nfiles)  :: type_ecri_files, phys_out_filetypes
     677    character(len=20), dimension(nfiles)  :: chtimestep   = (/ 'DefFreq', 'DefFreq','DefFreq', 'DefFreq', 'DefFreq', 'DefFreq' /)
     678    logical, dimension(nfiles)            :: phys_out_filekeys
     679    logical, dimension(nfiles)            :: phys_out_filestations
    679680
    680681!!!!!!!!!! stockage dans une region limitee pour chaque fichier !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    681 !                 entre [phys_out_lonmin,phys_out_lonmax] et [phys_out_latmin,phys_out_latmax]
    682 
    683   logical, dimension(nfiles), save  :: phys_out_regfkey       = (/ .false., .false., .false., .false., .false., .false. /)
    684   real, dimension(nfiles), save     :: phys_out_lonmin        = (/ -180., -180., -180., -180., -180., -180. /)
    685   real, dimension(nfiles), save     :: phys_out_lonmax        = (/ 180., 180., 180., 180., 180., 180. /)
    686   real, dimension(nfiles), save     :: phys_out_latmin        = (/ -90., -90., -90., -90., -90., -90. /)
    687   real, dimension(nfiles), save     :: phys_out_latmax        = (/ 90., 90., 90., 90., 90., 90. /)
    688 
    689    print*,'Debut phys_output_mod.F90'
    690 ! Initialisations (Valeurs par defaut
    691 
    692    if (.not. allocated(o_trac)) ALLOCATE(o_trac(nqtot))
    693 
    694    levmax = (/ klev, klev, klev, klev, klev, klev /)
    695 
    696    phys_out_filenames(1) = 'histmth'
    697    phys_out_filenames(2) = 'histday'
    698    phys_out_filenames(3) = 'histhf'
    699    phys_out_filenames(4) = 'histins'
    700    phys_out_filenames(5) = 'histLES'
    701    phys_out_filenames(6) = 'histstn'
    702 
    703    type_ecri(1) = 'ave(X)'
    704    type_ecri(2) = 'ave(X)'
    705    type_ecri(3) = 'ave(X)'
    706    type_ecri(4) = 'inst(X)'
    707    type_ecri(5) = 'ave(X)'
    708    type_ecri(6) = 'inst(X)'
    709 
    710    clef_files(1) = ok_mensuel
    711    clef_files(2) = ok_journe
    712    clef_files(3) = ok_hf
    713    clef_files(4) = ok_instan
    714    clef_files(5) = ok_LES
    715    clef_files(6) = ok_instan
    716 
    717 !sortir des fichiers "stations" si clef_stations(:)=.TRUE.
    718    clef_stations(1) = .FALSE.
    719    clef_stations(2) = .FALSE.
    720    clef_stations(3) = .FALSE.
    721    clef_stations(4) = .FALSE.
    722    clef_stations(5) = .FALSE.
    723    clef_stations(6) = .FALSE.
    724 
    725    lev_files(1) = lev_histmth
    726    lev_files(2) = lev_histday
    727    lev_files(3) = lev_histhf
    728    lev_files(4) = lev_histins
    729    lev_files(5) = lev_histLES
    730    lev_files(6) = lev_histins
    731 
    732    ecrit_files(1) = ecrit_mth
    733    ecrit_files(2) = ecrit_day
    734    ecrit_files(3) = ecrit_hf
    735    ecrit_files(4) = ecrit_ins
    736    ecrit_files(5) = ecrit_LES
    737    ecrit_files(6) = ecrit_ins
    738  
    739 !! Lectures des parametres de sorties dans physiq.def
    740 
    741    call getin('phys_out_regfkey',phys_out_regfkey)
    742    call getin('phys_out_lonmin',phys_out_lonmin)
    743    call getin('phys_out_lonmax',phys_out_lonmax)
    744    call getin('phys_out_latmin',phys_out_latmin)
    745    call getin('phys_out_latmax',phys_out_latmax)
    746      phys_out_levmin(:)=levmin(:)
    747    call getin('phys_out_levmin',levmin)
    748      phys_out_levmax(:)=levmax(:)
    749    call getin('phys_out_levmax',levmax)
    750    call getin('phys_out_filenames',phys_out_filenames)
    751      phys_out_filekeys(:)=clef_files(:)
    752    call getin('phys_out_filekeys',clef_files)
    753      phys_out_filestations(:)=clef_stations(:)
    754    call getin('phys_out_filestations',clef_stations)
    755      phys_out_filelevels(:)=lev_files(:)
    756    call getin('phys_out_filelevels',lev_files)
    757    call getin('phys_out_filetimesteps',chtimestep)
    758      phys_out_filetypes(:)=type_ecri(:)
    759    call getin('phys_out_filetypes',type_ecri)
    760 
    761    type_ecri_files(:)=type_ecri(:)
    762 
    763    print*,'phys_out_lonmin=',phys_out_lonmin
    764    print*,'phys_out_lonmax=',phys_out_lonmax
    765    print*,'phys_out_latmin=',phys_out_latmin
    766    print*,'phys_out_latmax=',phys_out_latmax
    767    print*,'phys_out_filenames=',phys_out_filenames
    768    print*,'phys_out_filetypes=',type_ecri
    769    print*,'phys_out_filekeys=',clef_files
    770    print*,'phys_out_filestations=',clef_stations
    771    print*,'phys_out_filelevels=',lev_files
     682    !                 entre [phys_out_lonmin,phys_out_lonmax] et [phys_out_latmin,phys_out_latmax]
     683
     684    logical, dimension(nfiles), save  :: phys_out_regfkey       = (/ .false., .false., .false., .false., .false., .false. /)
     685    real, dimension(nfiles), save     :: phys_out_lonmin        = (/ -180., -180., -180., -180., -180., -180. /)
     686    real, dimension(nfiles), save     :: phys_out_lonmax        = (/ 180., 180., 180., 180., 180., 180. /)
     687    real, dimension(nfiles), save     :: phys_out_latmin        = (/ -90., -90., -90., -90., -90., -90. /)
     688    real, dimension(nfiles), save     :: phys_out_latmax        = (/ 90., 90., 90., 90., 90., 90. /)
     689
     690    write(lunout,*) 'Debut phys_output_mod.F90'
     691    ! Initialisations (Valeurs par defaut
     692
     693    if (.not. allocated(o_trac)) ALLOCATE(o_trac(nqtot))
     694
     695    levmax = (/ klev, klev, klev, klev, klev, klev /)
     696
     697    phys_out_filenames(1) = 'histmth'
     698    phys_out_filenames(2) = 'histday'
     699    phys_out_filenames(3) = 'histhf'
     700    phys_out_filenames(4) = 'histins'
     701    phys_out_filenames(5) = 'histLES'
     702    phys_out_filenames(6) = 'histstn'
     703
     704    type_ecri(1) = 'ave(X)'
     705    type_ecri(2) = 'ave(X)'
     706    type_ecri(3) = 'ave(X)'
     707    type_ecri(4) = 'inst(X)'
     708    type_ecri(5) = 'ave(X)'
     709    type_ecri(6) = 'inst(X)'
     710
     711    clef_files(1) = ok_mensuel
     712    clef_files(2) = ok_journe
     713    clef_files(3) = ok_hf
     714    clef_files(4) = ok_instan
     715    clef_files(5) = ok_LES
     716    clef_files(6) = ok_instan
     717
     718    !sortir des fichiers "stations" si clef_stations(:)=.TRUE.
     719    clef_stations(1) = .FALSE.
     720    clef_stations(2) = .FALSE.
     721    clef_stations(3) = .FALSE.
     722    clef_stations(4) = .FALSE.
     723    clef_stations(5) = .FALSE.
     724    clef_stations(6) = .FALSE.
     725
     726    lev_files(1) = lev_histmth
     727    lev_files(2) = lev_histday
     728    lev_files(3) = lev_histhf
     729    lev_files(4) = lev_histins
     730    lev_files(5) = lev_histLES
     731    lev_files(6) = lev_histins
     732
     733    ecrit_files(1) = ecrit_mth
     734    ecrit_files(2) = ecrit_day
     735    ecrit_files(3) = ecrit_hf
     736    ecrit_files(4) = ecrit_ins
     737    ecrit_files(5) = ecrit_LES
     738    ecrit_files(6) = ecrit_ins
     739
     740    !! Lectures des parametres de sorties dans physiq.def
     741
     742    call getin('phys_out_regfkey',phys_out_regfkey)
     743    call getin('phys_out_lonmin',phys_out_lonmin)
     744    call getin('phys_out_lonmax',phys_out_lonmax)
     745    call getin('phys_out_latmin',phys_out_latmin)
     746    call getin('phys_out_latmax',phys_out_latmax)
     747    phys_out_levmin(:)=levmin(:)
     748    call getin('phys_out_levmin',levmin)
     749    phys_out_levmax(:)=levmax(:)
     750    call getin('phys_out_levmax',levmax)
     751    call getin('phys_out_filenames',phys_out_filenames)
     752    phys_out_filekeys(:)=clef_files(:)
     753    call getin('phys_out_filekeys',clef_files)
     754    phys_out_filestations(:)=clef_stations(:)
     755    call getin('phys_out_filestations',clef_stations)
     756    phys_out_filelevels(:)=lev_files(:)
     757    call getin('phys_out_filelevels',lev_files)
     758    call getin('phys_out_filetimesteps',chtimestep)
     759    phys_out_filetypes(:)=type_ecri(:)
     760    call getin('phys_out_filetypes',type_ecri)
     761
     762    type_ecri_files(:)=type_ecri(:)
     763
     764    write(lunout,*)'phys_out_lonmin=',phys_out_lonmin
     765    write(lunout,*)'phys_out_lonmax=',phys_out_lonmax
     766    write(lunout,*)'phys_out_latmin=',phys_out_latmin
     767    write(lunout,*)'phys_out_latmax=',phys_out_latmax
     768    write(lunout,*)'phys_out_filenames=',phys_out_filenames
     769    write(lunout,*)'phys_out_filetypes=',type_ecri
     770    write(lunout,*)'phys_out_filekeys=',clef_files
     771    write(lunout,*)'phys_out_filestations=',clef_stations
     772    write(lunout,*)'phys_out_filelevels=',lev_files
    772773
    773774!!!!!!!!!!!!!!!!!!!!!!! Boucle sur les fichiers !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    774 ! Appel de histbeg et histvert pour creer le fichier et les niveaux verticaux !!
    775 ! Appel des histbeg pour definir les variables (nom, moy ou inst, freq de sortie ..
     775    ! Appel de histbeg et histvert pour creer le fichier et les niveaux verticaux !!
     776    ! Appel des histbeg pour definir les variables (nom, moy ou inst, freq de sortie ..
    776777!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    777778
    778  zdtime = dtime         ! Frequence ou l on moyenne
    779 
    780 ! Calcul des Ahyb, Bhyb et Alt
    781          do k=1,klev
    782           Ahyb(k)=(ap(k)+ap(k+1))/2.
    783           Bhyb(k)=(bp(k)+bp(k+1))/2.
    784           Alt(k)=log(preff/presnivs(k))*8.
    785          enddo
    786 !          if(prt_level.ge.1) then
    787            print*,'Ap Hybrid = ',Ahyb(1:klev)
    788            print*,'Bp Hybrid = ',Bhyb(1:klev)
    789            print*,'Alt approx des couches pour une haut d echelle de 8km = ',Alt(1:klev)
    790 !          endif
    791  DO iff=1,nfiles
    792 
    793     IF (clef_files(iff)) THEN
    794 
    795       if ( chtimestep(iff).eq.'DefFreq' ) then
    796 ! Par defaut ecrit_files = (ecrit_mensuel ecrit_jour ecrit_hf ...)*86400.
    797         ecrit_files(iff)=ecrit_files(iff)*86400.
    798       else
    799         call convers_timesteps(chtimestep(iff),dtime,ecrit_files(iff))
    800       endif
    801        print*,'ecrit_files(',iff,')= ',ecrit_files(iff)
    802 
    803       zoutm(iff) = ecrit_files(iff) ! Frequence ou l on ecrit en seconde
    804 
    805       idayref = day_ref
    806       CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
     779    zdtime = dtime         ! Frequence ou l on moyenne
     780
     781    ! Calcul des Ahyb, Bhyb et Alt
     782    do k=1,klev
     783       Ahyb(k)=(ap(k)+ap(k+1))/2.
     784       Bhyb(k)=(bp(k)+bp(k+1))/2.
     785       Alt(k)=log(preff/presnivs(k))*8.
     786    enddo
     787    !          if(prt_level.ge.1) then
     788    write(lunout,*)'Ap Hybrid = ',Ahyb(1:klev)
     789    write(lunout,*)'Bp Hybrid = ',Bhyb(1:klev)
     790    write(lunout,*)'Alt approx des couches pour une haut d echelle de 8km = ',Alt(1:klev)
     791    !          endif
     792    DO iff=1,nfiles
     793
     794       IF (clef_files(iff)) THEN
     795
     796          if ( chtimestep(iff).eq.'DefFreq' ) then
     797             ! Par defaut ecrit_files = (ecrit_mensuel ecrit_jour ecrit_hf ...)*86400.
     798             ecrit_files(iff)=ecrit_files(iff)*86400.
     799          else
     800             call convers_timesteps(chtimestep(iff),dtime,ecrit_files(iff))
     801          endif
     802          write(lunout,*)'ecrit_files(',iff,')= ',ecrit_files(iff)
     803
     804          zoutm(iff) = ecrit_files(iff) ! Frequence ou l on ecrit en seconde
     805
     806          idayref = day_ref
     807          CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
    807808
    808809!!!!!!!!!!!!!!!!! Traitement dans le cas ou l'on veut stocker sur un domaine limite !!
    809810!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    810      if (phys_out_regfkey(iff)) then
    811 
    812         imin_ins=1
    813         imax_ins=iim
    814         jmin_ins=1
    815         jmax_ins=jjmp1
    816 
    817 ! correction abderr       
    818         do i=1,iim
    819            print*,'io_lon(i)=',io_lon(i)
    820            if (io_lon(i).le.phys_out_lonmin(iff)) imin_ins=i
    821            if (io_lon(i).le.phys_out_lonmax(iff)) imax_ins=i+1
    822         enddo
    823 
    824         do j=1,jjmp1
    825             print*,'io_lat(j)=',io_lat(j)
    826             if (io_lat(j).ge.phys_out_latmin(iff)) jmax_ins=j+1
    827             if (io_lat(j).ge.phys_out_latmax(iff)) jmin_ins=j
    828         enddo
    829 
    830         print*,'On stoke le fichier histoire numero ',iff,' sur ', &
    831          imin_ins,imax_ins,jmin_ins,jmax_ins
    832          print*,'longitudes : ', &
    833          io_lon(imin_ins),io_lon(imax_ins), &
    834          'latitudes : ', &
    835          io_lat(jmax_ins),io_lat(jmin_ins)
    836 
    837  CALL histbeg(phys_out_filenames(iff),iim,io_lon,jjmp1,io_lat, &
    838               imin_ins,imax_ins-imin_ins+1, &
    839               jmin_ins,jmax_ins-jmin_ins+1, &
    840               itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
     811          if (phys_out_regfkey(iff)) then
     812
     813             imin_ins=1
     814             imax_ins=iim
     815             jmin_ins=1
     816             jmax_ins=jjmp1
     817
     818             ! correction abderr       
     819             do i=1,iim
     820                write(lunout,*)'io_lon(i)=',io_lon(i)
     821                if (io_lon(i).le.phys_out_lonmin(iff)) imin_ins=i
     822                if (io_lon(i).le.phys_out_lonmax(iff)) imax_ins=i+1
     823             enddo
     824
     825             do j=1,jjmp1
     826                write(lunout,*)'io_lat(j)=',io_lat(j)
     827                if (io_lat(j).ge.phys_out_latmin(iff)) jmax_ins=j+1
     828                if (io_lat(j).ge.phys_out_latmax(iff)) jmin_ins=j
     829             enddo
     830
     831             write(lunout,*)'On stoke le fichier histoire numero ',iff,' sur ', &
     832                  imin_ins,imax_ins,jmin_ins,jmax_ins
     833             write(lunout,*)'longitudes : ', &
     834                  io_lon(imin_ins),io_lon(imax_ins), &
     835                  'latitudes : ', &
     836                  io_lat(jmax_ins),io_lat(jmin_ins)
     837
     838             CALL histbeg(phys_out_filenames(iff),iim,io_lon,jjmp1,io_lat, &
     839                  imin_ins,imax_ins-imin_ins+1, &
     840                  jmin_ins,jmax_ins-jmin_ins+1, &
     841                  itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
    841842!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    842 !IM fichiers stations
    843      else if (clef_stations(iff)) THEN
    844 
    845      print*,'phys_output_mod phys_out_filenames=',phys_out_filenames(iff)
    846 
    847       call histbeg_phy_all(rlon,rlat,pim,tabij,ipt,jpt,plon,plat,plon_bounds,plat_bounds, &
    848                            phys_out_filenames(iff), &
    849                            itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
    850        else
    851  CALL histbeg_phy(phys_out_filenames(iff),itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
    852        endif
    853  
    854       CALL histvert(nid_files(iff), "presnivs", "Vertical levels", "Pa", &
    855            levmax(iff) - levmin(iff) + 1, &
    856            presnivs(levmin(iff):levmax(iff)), nvertm(iff),"down")
     843             !IM fichiers stations
     844          else if (clef_stations(iff)) THEN
     845
     846             write(lunout,*)'phys_output_mod phys_out_filenames=',phys_out_filenames(iff)
     847
     848             call histbeg_phy_all(rlon,rlat,pim,tabij,ipt,jpt,plon,plat,plon_bounds,plat_bounds, &
     849                  phys_out_filenames(iff), &
     850                  itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
     851          else
     852             CALL histbeg_phy(phys_out_filenames(iff),itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
     853          endif
     854
     855          CALL histvert(nid_files(iff), "presnivs", "Vertical levels", "Pa", &
     856               levmax(iff) - levmin(iff) + 1, &
     857               presnivs(levmin(iff):levmax(iff)), nvertm(iff),"down")
    857858
    858859!!!!!!!!!!!!! Traitement des champs 3D pour histhf !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    859860!!!!!!!!!!!!!!! A Revoir plus tard !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    860 !          IF (iff.eq.3.and.lev_files(iff).ge.4) THEN
    861 !          CALL histbeg_phy("histhf3d",itau_phy, &
    862 !     &                     zjulian, dtime, &
    863 !     &                     nhorim, nid_hf3d)
    864 
    865 !         CALL histvert(nid_hf3d, "presnivs", &
    866 !     &                 "Vertical levels", "mb", &
    867 !     &                 klev, presnivs/100., nvertm)
    868 !          ENDIF
    869 !
     861          !          IF (iff.eq.3.and.lev_files(iff).ge.4) THEN
     862          !          CALL histbeg_phy("histhf3d",itau_phy, &
     863          !     &                     zjulian, dtime, &
     864          !     &                     nhorim, nid_hf3d)
     865
     866          !         CALL histvert(nid_hf3d, "presnivs", &
     867          !     &                 "Vertical levels", "mb", &
     868          !     &                 klev, presnivs/100., nvertm)
     869          !          ENDIF
     870          !
    870871!!!! Composentes de la coordonnee sigma-hybride
    871    CALL histvert(nid_files(iff), "Ahyb","Ahyb comp of Hyb Cord ", "Pa", &
    872                  levmax(iff) - levmin(iff) + 1,Ahyb,nvertap(iff))
    873 
    874    CALL histvert(nid_files(iff), "Bhyb","Bhyb comp of Hyb Cord", " ", &
    875                  levmax(iff) - levmin(iff) + 1,Bhyb,nvertbp(iff))
    876 
    877    CALL histvert(nid_files(iff), "Alt","Height approx for scale heigh of 8km at levels", "Km", &
    878                  levmax(iff) - levmin(iff) + 1,Alt,nvertAlt(iff))
    879 
    880 !   CALL histvert(nid_files(iff), "preff","Reference pressure", "Pa", &
    881 !                 1,preff,nvertp0(iff))
     872          CALL histvert(nid_files(iff), "Ahyb","Ahyb comp of Hyb Cord ", "Pa", &
     873               levmax(iff) - levmin(iff) + 1,Ahyb,nvertap(iff))
     874
     875          CALL histvert(nid_files(iff), "Bhyb","Bhyb comp of Hyb Cord", " ", &
     876               levmax(iff) - levmin(iff) + 1,Bhyb,nvertbp(iff))
     877
     878          CALL histvert(nid_files(iff), "Alt","Height approx for scale heigh of 8km at levels", "Km", &
     879               levmax(iff) - levmin(iff) + 1,Alt,nvertAlt(iff))
     880
     881          !   CALL histvert(nid_files(iff), "preff","Reference pressure", "Pa", &
     882          !                 1,preff,nvertp0(iff))
    882883!!! Champs 1D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    883  IF (.NOT.clef_stations(iff)) THEN
    884 !
    885 !IM: there is no way to have one single value in a netcdf file
    886 !
    887    type_ecri(1) = 'once'
    888    type_ecri(2) = 'once'
    889    type_ecri(3) = 'once'
    890    type_ecri(4) = 'once'
    891    type_ecri(5) = 'once'
    892    type_ecri(6) = 'once'
    893    CALL histdef2d(iff,clef_stations(iff),o_aire%flag,o_aire%name,"Grid area", "-")
    894    CALL histdef2d(iff,clef_stations(iff),o_contfracATM%flag,o_contfracATM%name,"% sfce ter+lic", "-")
    895  ENDIF
    896    type_ecri(:) = type_ecri_files(:)
     884          IF (.NOT.clef_stations(iff)) THEN
     885             !
     886             !IM: there is no way to have one single value in a netcdf file
     887             !
     888             type_ecri(1) = 'once'
     889             type_ecri(2) = 'once'
     890             type_ecri(3) = 'once'
     891             type_ecri(4) = 'once'
     892             type_ecri(5) = 'once'
     893             type_ecri(6) = 'once'
     894             CALL histdef2d(iff,clef_stations(iff),o_aire%flag,o_aire%name,"Grid area", "-")
     895             CALL histdef2d(iff,clef_stations(iff),o_contfracATM%flag,o_contfracATM%name,"% sfce ter+lic", "-")
     896          ENDIF
     897          type_ecri(:) = type_ecri_files(:)
    897898
    898899!!! Champs 2D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    899  CALL histdef2d(iff,clef_stations(iff),o_phis%flag,o_phis%name,"Surface geop.height", "m2/s2" )
    900  CALL histdef2d(iff,clef_stations(iff),o_contfracOR%flag,o_contfracOR%name,"% sfce terre OR", "-" )
    901  CALL histdef2d(iff,clef_stations(iff),o_aireTER%flag,o_aireTER%name,"Grid area CONT", "-" )
    902  CALL histdef2d(iff,clef_stations(iff),o_flat%flag,o_flat%name, "Latent heat flux", "W/m2")
    903  CALL histdef2d(iff,clef_stations(iff),o_slp%flag,o_slp%name, "Sea Level Pressure", "Pa" )
    904  CALL histdef2d(iff,clef_stations(iff),o_tsol%flag,o_tsol%name, "Surface Temperature", "K")
    905  CALL histdef2d(iff,clef_stations(iff),o_t2m%flag,o_t2m%name, "Temperature 2m", "K" )
    906   IF (.NOT.clef_stations(iff)) THEN
    907 !
    908 !IM: there is no way to have one single value in a netcdf file
    909 !
    910    type_ecri(1) = 't_min(X)'
    911    type_ecri(2) = 't_min(X)'
    912    type_ecri(3) = 't_min(X)'
    913    type_ecri(4) = 't_min(X)'
    914    type_ecri(5) = 't_min(X)'
    915    type_ecri(6) = 't_min(X)'
    916    CALL histdef2d(iff,clef_stations(iff),o_t2m_min%flag,o_t2m_min%name, "Temp 2m min", "K" )
    917    type_ecri(1) = 't_max(X)'
    918    type_ecri(2) = 't_max(X)'
    919    type_ecri(3) = 't_max(X)'
    920    type_ecri(4) = 't_max(X)'
    921    type_ecri(5) = 't_max(X)'
    922    type_ecri(6) = 't_max(X)'
    923    CALL histdef2d(iff,clef_stations(iff),o_t2m_max%flag,o_t2m_max%name, "Temp 2m max", "K" )
    924   ENDIF
    925    type_ecri(:) = type_ecri_files(:)
    926  CALL histdef2d(iff,clef_stations(iff),o_wind10m%flag,o_wind10m%name, "10-m wind speed", "m/s")
    927  CALL histdef2d(iff,clef_stations(iff),o_wind10max%flag,o_wind10max%name, "10m wind speed max", "m/s")
    928  CALL histdef2d(iff,clef_stations(iff),o_sicf%flag,o_sicf%name, "Sea-ice fraction", "-" )
    929  CALL histdef2d(iff,clef_stations(iff),o_q2m%flag,o_q2m%name, "Specific humidity 2m", "kg/kg")
    930  CALL histdef2d(iff,clef_stations(iff),o_u10m%flag,o_u10m%name, "Vent zonal 10m", "m/s" )
    931  CALL histdef2d(iff,clef_stations(iff),o_v10m%flag,o_v10m%name, "Vent meridien 10m", "m/s")
    932  CALL histdef2d(iff,clef_stations(iff),o_psol%flag,o_psol%name, "Surface Pressure", "Pa" )
    933  CALL histdef2d(iff,clef_stations(iff),o_qsurf%flag,o_qsurf%name, "Surface Air humidity", "kg/kg")
    934 
    935   if (.not. ok_veget) then
    936  CALL histdef2d(iff,clef_stations(iff),o_qsol%flag,o_qsol%name, "Soil watter content", "mm" )
    937   endif
    938 
    939  CALL histdef2d(iff,clef_stations(iff),o_ndayrain%flag,o_ndayrain%name, "Number of dayrain(liq+sol)", "-")
    940  CALL histdef2d(iff,clef_stations(iff),o_precip%flag,o_precip%name, "Precip Totale liq+sol", "kg/(s*m2)" )
    941  CALL histdef2d(iff,clef_stations(iff),o_plul%flag,o_plul%name, "Large-scale Precip.", "kg/(s*m2)")
    942  CALL histdef2d(iff,clef_stations(iff),o_pluc%flag,o_pluc%name, "Convective Precip.", "kg/(s*m2)")
    943  CALL histdef2d(iff,clef_stations(iff),o_snow%flag,o_snow%name, "Snow fall", "kg/(s*m2)" )
    944  CALL histdef2d(iff,clef_stations(iff),o_msnow%flag,o_msnow%name, "Surface snow amount", "kg/m2" )
    945  CALL histdef2d(iff,clef_stations(iff),o_fsnow%flag,o_fsnow%name, "Surface snow area fraction", "-" )
    946  CALL histdef2d(iff,clef_stations(iff),o_evap%flag,o_evap%name, "Evaporat", "kg/(s*m2)" )
    947  CALL histdef2d(iff,clef_stations(iff),o_tops%flag,o_tops%name, "Solar rad. at TOA", "W/m2")
    948  CALL histdef2d(iff,clef_stations(iff),o_tops0%flag,o_tops0%name, "CS Solar rad. at TOA", "W/m2")
    949  CALL histdef2d(iff,clef_stations(iff),o_topl%flag,o_topl%name, "IR rad. at TOA", "W/m2" )
    950  CALL histdef2d(iff,clef_stations(iff),o_topl0%flag,o_topl0%name, "IR rad. at TOA", "W/m2")
    951  CALL histdef2d(iff,clef_stations(iff),o_SWupTOA%flag,o_SWupTOA%name, "SWup at TOA", "W/m2")
    952  CALL histdef2d(iff,clef_stations(iff),o_SWupTOAclr%flag,o_SWupTOAclr%name, "SWup clear sky at TOA", "W/m2")
    953  CALL histdef2d(iff,clef_stations(iff),o_SWdnTOA%flag,o_SWdnTOA%name, "SWdn at TOA", "W/m2" )
    954  CALL histdef2d(iff,clef_stations(iff),o_SWdnTOAclr%flag,o_SWdnTOAclr%name, "SWdn clear sky at TOA", "W/m2")
    955  CALL histdef2d(iff,clef_stations(iff),o_nettop%flag,o_nettop%name, "Net dn radiatif flux at TOA", "W/m2")
    956  CALL histdef2d(iff,clef_stations(iff),o_SWup200%flag,o_SWup200%name, "SWup at 200mb", "W/m2" )
    957  CALL histdef2d(iff,clef_stations(iff),o_SWup200clr%flag,o_SWup200clr%name, "SWup clear sky at 200mb", "W/m2")
    958  CALL histdef2d(iff,clef_stations(iff),o_SWdn200%flag,o_SWdn200%name, "SWdn at 200mb", "W/m2" )
    959  CALL histdef2d(iff,clef_stations(iff),o_SWdn200clr%flag,o_SWdn200clr%name, "SWdn clear sky at 200mb", "W/m2")
    960  CALL histdef2d(iff,clef_stations(iff),o_LWup200%flag,o_LWup200%name, "LWup at 200mb", "W/m2")
    961  CALL histdef2d(iff,clef_stations(iff),o_LWup200clr%flag,o_LWup200clr%name, "LWup clear sky at 200mb", "W/m2")
    962  CALL histdef2d(iff,clef_stations(iff),o_LWdn200%flag,o_LWdn200%name, "LWdn at 200mb", "W/m2")
    963  CALL histdef2d(iff,clef_stations(iff),o_LWdn200clr%flag,o_LWdn200clr%name, "LWdn clear sky at 200mb", "W/m2")
    964  CALL histdef2d(iff,clef_stations(iff),o_sols%flag,o_sols%name, "Solar rad. at surf.", "W/m2")
    965  CALL histdef2d(iff,clef_stations(iff),o_sols0%flag,o_sols0%name, "Solar rad. at surf.", "W/m2")
    966  CALL histdef2d(iff,clef_stations(iff),o_soll%flag,o_soll%name, "IR rad. at surface", "W/m2") 
    967  CALL histdef2d(iff,clef_stations(iff),o_radsol%flag,o_radsol%name, "Rayonnement au sol", "W/m2")
    968  CALL histdef2d(iff,clef_stations(iff),o_soll0%flag,o_soll0%name, "IR rad. at surface", "W/m2")
    969  CALL histdef2d(iff,clef_stations(iff),o_SWupSFC%flag,o_SWupSFC%name, "SWup at surface", "W/m2")
    970  CALL histdef2d(iff,clef_stations(iff),o_SWupSFCclr%flag,o_SWupSFCclr%name, "SWup clear sky at surface", "W/m2")
    971  CALL histdef2d(iff,clef_stations(iff),o_SWdnSFC%flag,o_SWdnSFC%name, "SWdn at surface", "W/m2")
    972  CALL histdef2d(iff,clef_stations(iff),o_SWdnSFCclr%flag,o_SWdnSFCclr%name, "SWdn clear sky at surface", "W/m2")
    973  CALL histdef2d(iff,clef_stations(iff),o_LWupSFC%flag,o_LWupSFC%name, "Upwd. IR rad. at surface", "W/m2")
    974  CALL histdef2d(iff,clef_stations(iff),o_LWdnSFC%flag,o_LWdnSFC%name, "Down. IR rad. at surface", "W/m2")
    975  CALL histdef2d(iff,clef_stations(iff),o_LWupSFCclr%flag,o_LWupSFCclr%name, "CS Upwd. IR rad. at surface", "W/m2")
    976  CALL histdef2d(iff,clef_stations(iff),o_LWdnSFCclr%flag,o_LWdnSFCclr%name, "Down. CS IR rad. at surface", "W/m2")
    977  CALL histdef2d(iff,clef_stations(iff),o_bils%flag,o_bils%name, "Surf. total heat flux", "W/m2")
    978  CALL histdef2d(iff,clef_stations(iff),o_sens%flag,o_sens%name, "Sensible heat flux", "W/m2")
    979  CALL histdef2d(iff,clef_stations(iff),o_fder%flag,o_fder%name, "Heat flux derivation", "W/m2")
    980  CALL histdef2d(iff,clef_stations(iff),o_ffonte%flag,o_ffonte%name, "Thermal flux for snow melting", "W/m2")
    981  CALL histdef2d(iff,clef_stations(iff),o_fqcalving%flag,o_fqcalving%name, "Ice Calving", "kg/m2/s")
    982  CALL histdef2d(iff,clef_stations(iff),o_fqfonte%flag,o_fqfonte%name, "Land ice melt", "kg/m2/s")
    983 
    984  CALL histdef2d(iff,clef_stations(iff),o_taux%flag,o_taux%name, "Zonal wind stress","Pa")
    985  CALL histdef2d(iff,clef_stations(iff),o_tauy%flag,o_tauy%name, "Meridional wind stress","Pa")
    986 
    987      DO nsrf = 1, nbsrf
    988  CALL histdef2d(iff,clef_stations(iff),o_pourc_srf(nsrf)%flag,o_pourc_srf(nsrf)%name,"% "//clnsurf(nsrf),"%")
    989  CALL histdef2d(iff,clef_stations(iff),o_fract_srf(nsrf)%flag,o_fract_srf(nsrf)%name,"Fraction "//clnsurf(nsrf),"1")
    990  CALL histdef2d(iff,clef_stations(iff), &
    991 o_taux_srf(nsrf)%flag,o_taux_srf(nsrf)%name,"Zonal wind stress"//clnsurf(nsrf),"Pa")
    992  CALL histdef2d(iff,clef_stations(iff), &
    993 o_tauy_srf(nsrf)%flag,o_tauy_srf(nsrf)%name,"Meridional wind stress "//clnsurf(nsrf),"Pa")
    994  CALL histdef2d(iff,clef_stations(iff), &
    995 o_tsol_srf(nsrf)%flag,o_tsol_srf(nsrf)%name,"Temperature "//clnsurf(nsrf),"K")
    996  CALL histdef2d(iff,clef_stations(iff), &
    997 o_u10m_srf(nsrf)%flag,o_u10m_srf(nsrf)%name,"Vent Zonal 10m "//clnsurf(nsrf),"m/s")
    998  CALL histdef2d(iff,clef_stations(iff), &
    999 o_evap_srf(nsrf)%flag,o_evap_srf(nsrf)%name,"evaporation at surface "//clnsurf(nsrf),"kg/(s*m2)")
    1000  CALL histdef2d(iff,clef_stations(iff), &
    1001 o_v10m_srf(nsrf)%flag,o_v10m_srf(nsrf)%name,"Vent meredien 10m "//clnsurf(nsrf),"m/s")
    1002  CALL histdef2d(iff,clef_stations(iff), &
    1003 o_t2m_srf(nsrf)%flag,o_t2m_srf(nsrf)%name,"Temp 2m "//clnsurf(nsrf),"K")
    1004  CALL histdef2d(iff,clef_stations(iff), &
    1005 o_sens_srf(nsrf)%flag,o_sens_srf(nsrf)%name,"Sensible heat flux "//clnsurf(nsrf),"W/m2")
    1006  CALL histdef2d(iff,clef_stations(iff), &
    1007 o_lat_srf(nsrf)%flag,o_lat_srf(nsrf)%name,"Latent heat flux "//clnsurf(nsrf),"W/m2")
    1008  CALL histdef2d(iff,clef_stations(iff), &
    1009 o_flw_srf(nsrf)%flag,o_flw_srf(nsrf)%name,"LW "//clnsurf(nsrf),"W/m2")
    1010  CALL histdef2d(iff,clef_stations(iff), &
    1011 o_fsw_srf(nsrf)%flag,o_fsw_srf(nsrf)%name,"SW "//clnsurf(nsrf),"W/m2")
    1012  CALL histdef2d(iff,clef_stations(iff), &
    1013 o_wbils_srf(nsrf)%flag,o_wbils_srf(nsrf)%name,"Bilan sol "//clnsurf(nsrf),"W/m2" )
    1014  CALL histdef2d(iff,clef_stations(iff), &
    1015 o_wbilo_srf(nsrf)%flag,o_wbilo_srf(nsrf)%name,"Bilan eau "//clnsurf(nsrf),"kg/(m2*s)")
    1016   if (iflag_pbl>1 .and. lev_files(iff).gt.10 ) then
    1017  CALL histdef2d(iff,clef_stations(iff), &
    1018 o_tke_srf(nsrf)%flag,o_tke_srf(nsrf)%name,"Max Turb. Kinetic Energy "//clnsurf(nsrf),"-")
    1019 
    1020   IF (.NOT.clef_stations(iff)) THEN
    1021 !
    1022 !IM: there is no way to have one single value in a netcdf file
    1023 !
    1024    type_ecri(1) = 't_max(X)'
    1025    type_ecri(2) = 't_max(X)'
    1026    type_ecri(3) = 't_max(X)'
    1027    type_ecri(4) = 't_max(X)'
    1028    type_ecri(5) = 't_max(X)'
    1029    type_ecri(6) = 't_max(X)'
    1030   CALL histdef2d(iff,clef_stations(iff), &
    1031   o_tke_max_srf(nsrf)%flag,o_tke_max_srf(nsrf)%name,"Max Turb. Kinetic Energy "//clnsurf(nsrf),"-")
    1032    type_ecri(:) = type_ecri_files(:)
    1033   ENDIF
    1034 
    1035   endif
    1036 
    1037  CALL histdef2d(iff,clef_stations(iff), &
    1038 o_albe_srf(nsrf)%flag,o_albe_srf(nsrf)%name,"Albedo VIS surf. "//clnsurf(nsrf),"-")
    1039  CALL histdef2d(iff,clef_stations(iff), &
    1040 o_rugs_srf(nsrf)%flag,o_rugs_srf(nsrf)%name,"Surface roughness "//clnsurf(nsrf),"m")
    1041  CALL histdef2d(iff,clef_stations(iff), &
    1042 o_ages_srf(nsrf)%flag,o_ages_srf(nsrf)%name,"Snow age", "day")
    1043 END DO
    1044 
    1045 IF (new_aod .AND. (.NOT. aerosol_couple)) THEN
    1046  IF (ok_ade.OR.ok_aie) THEN
    1047 
    1048   CALL histdef2d(iff,clef_stations(iff), &
    1049 o_od550aer%flag,o_od550aer%name, "Total aerosol optical depth at 550nm", "-")
    1050   CALL histdef2d(iff,clef_stations(iff), &
    1051 o_od865aer%flag,o_od865aer%name, "Total aerosol optical depth at 870nm", "-")
    1052   CALL histdef2d(iff,clef_stations(iff), &
    1053 o_absvisaer%flag,o_absvisaer%name, "Absorption aerosol visible optical depth", "-")
    1054   CALL histdef2d(iff,clef_stations(iff), &
    1055 o_od550lt1aer%flag,o_od550lt1aer%name, "Fine mode optical depth", "-")
    1056 
    1057 
    1058   CALL histdef2d(iff,clef_stations(iff), &
    1059 o_sconcso4%flag,o_sconcso4%name,"Surface Concentration of Sulfate ","kg/m3")
    1060   CALL histdef2d(iff,clef_stations(iff), &
    1061 o_sconcoa%flag,o_sconcoa%name,"Surface Concentration of Organic Aerosol ","kg/m3")
    1062   CALL histdef2d(iff,clef_stations(iff), &
    1063 o_sconcbc%flag,o_sconcbc%name,"Surface Concentration of Black Carbon ","kg/m3")
    1064   CALL histdef2d(iff,clef_stations(iff), &
    1065 o_sconcss%flag,o_sconcss%name,"Surface Concentration of Sea Salt ","kg/m3")
    1066   CALL histdef2d(iff,clef_stations(iff), &
    1067 o_sconcdust%flag,o_sconcdust%name,"Surface Concentration of Dust ","kg/m3")
    1068   CALL histdef3d(iff,clef_stations(iff), &
    1069 o_concso4%flag,o_concso4%name,"Concentration of Sulfate ","kg/m3")
    1070   CALL histdef3d(iff,clef_stations(iff), &
    1071 o_concoa%flag,o_concoa%name,"Concentration of Organic Aerosol ","kg/m3")
    1072   CALL histdef3d(iff,clef_stations(iff), &
    1073 o_concbc%flag,o_concbc%name,"Concentration of Black Carbon ","kg/m3")
    1074   CALL histdef3d(iff,clef_stations(iff), &
    1075 o_concss%flag,o_concss%name,"Concentration of Sea Salt ","kg/m3")
    1076   CALL histdef3d(iff,clef_stations(iff), &
    1077 o_concdust%flag,o_concdust%name,"Concentration of Dust ","kg/m3")
    1078   CALL histdef2d(iff,clef_stations(iff), &
    1079 o_loadso4%flag,o_loadso4%name,"Column Load of Sulfate ","kg/m2")
    1080   CALL histdef2d(iff,clef_stations(iff), &
    1081 o_loadoa%flag,o_loadoa%name,"Column Load of Organic Aerosol ","kg/m2")
    1082   CALL histdef2d(iff,clef_stations(iff), &
    1083 o_loadbc%flag,o_loadbc%name,"Column Load of Black Carbon ","kg/m2")
    1084   CALL histdef2d(iff,clef_stations(iff), &
    1085 o_loadss%flag,o_loadss%name,"Column Load of Sea Salt ","kg/m2")
    1086   CALL histdef2d(iff,clef_stations(iff), &
    1087 o_loaddust%flag,o_loaddust%name,"Column Load of Dust ","kg/m2")
    1088 
    1089   DO naero = 1, naero_spc
    1090   CALL histdef2d(iff,clef_stations(iff), &
    1091 o_tausumaero(naero)%flag,o_tausumaero(naero)%name,"Aerosol Optical depth at 550 nm "//name_aero(naero),"1")
    1092   END DO
    1093  ENDIF
    1094 ENDIF
    1095 
    1096  IF (ok_ade) THEN
    1097   CALL histdef2d(iff,clef_stations(iff), &
    1098 o_topswad%flag,o_topswad%name, "ADE at TOA", "W/m2")
    1099   CALL histdef2d(iff,clef_stations(iff), &
    1100 o_solswad%flag,o_solswad%name, "ADE at SRF", "W/m2")
    1101 
    1102  CALL histdef2d(iff,clef_stations(iff), &
    1103 o_swtoaas_nat%flag,o_swtoaas_nat%name, "Natural aerosol radiative forcing all-sky at TOA", "W/m2")
    1104  CALL histdef2d(iff,clef_stations(iff), &
    1105 o_swsrfas_nat%flag,o_swsrfas_nat%name, "Natural aerosol radiative forcing all-sky at SRF", "W/m2")
    1106  CALL histdef2d(iff,clef_stations(iff), &
    1107 o_swtoacs_nat%flag,o_swtoacs_nat%name, "Natural aerosol radiative forcing clear-sky at TOA", "W/m2")
    1108  CALL histdef2d(iff,clef_stations(iff), &
    1109 o_swsrfcs_nat%flag,o_swsrfcs_nat%name, "Natural aerosol radiative forcing clear-sky at SRF", "W/m2")
    1110 
    1111  CALL histdef2d(iff,clef_stations(iff), &
    1112 o_swtoaas_ant%flag,o_swtoaas_ant%name, "Anthropogenic aerosol radiative forcing all-sky at TOA", "W/m2")
    1113  CALL histdef2d(iff,clef_stations(iff), &
    1114 o_swsrfas_ant%flag,o_swsrfas_ant%name, "Anthropogenic aerosol radiative forcing all-sky at SRF", "W/m2")
    1115  CALL histdef2d(iff,clef_stations(iff), &
    1116 o_swtoacs_ant%flag,o_swtoacs_ant%name, "Anthropogenic aerosol radiative forcing clear-sky at TOA", "W/m2")
    1117  CALL histdef2d(iff,clef_stations(iff), &
    1118 o_swsrfcs_ant%flag,o_swsrfcs_ant%name, "Anthropogenic aerosol radiative forcing clear-sky at SRF", "W/m2")
    1119 
    1120  IF (.NOT. aerosol_couple) THEN
    1121  CALL histdef2d(iff,clef_stations(iff), &
    1122 o_swtoacf_nat%flag,o_swtoacf_nat%name, "Natural aerosol impact on cloud radiative forcing at TOA", "W/m2")
    1123  CALL histdef2d(iff,clef_stations(iff), &
    1124 o_swsrfcf_nat%flag,o_swsrfcf_nat%name, "Natural aerosol impact on cloud radiative forcing  at SRF", "W/m2")
    1125  CALL histdef2d(iff,clef_stations(iff), &
    1126 o_swtoacf_ant%flag,o_swtoacf_ant%name, "Anthropogenic aerosol impact on cloud radiative forcing at TOA", "W/m2")
    1127  CALL histdef2d(iff,clef_stations(iff), &
    1128 o_swsrfcf_ant%flag,o_swsrfcf_ant%name, "Anthropogenic aerosol impact on cloud radiative forcing at SRF", "W/m2")
    1129  CALL histdef2d(iff,clef_stations(iff), &
    1130 o_swtoacf_zero%flag,o_swtoacf_zero%name, "Cloud radiative forcing (allsky-clearsky fluxes) at TOA", "W/m2")
    1131  CALL histdef2d(iff,clef_stations(iff), &
    1132 o_swsrfcf_zero%flag,o_swsrfcf_zero%name, "Cloud radiative forcing (allsky-clearsky fluxes) at SRF", "W/m2")
    1133  ENDIF
    1134 
    1135  ENDIF
    1136 
    1137  IF (ok_aie) THEN
    1138   CALL histdef2d(iff,clef_stations(iff), &
    1139 o_topswai%flag,o_topswai%name, "AIE at TOA", "W/m2")
    1140   CALL histdef2d(iff,clef_stations(iff), &
    1141 o_solswai%flag,o_solswai%name, "AIE at SFR", "W/m2")
    1142 !Cloud droplet number concentration
    1143   CALL histdef3d(iff,clef_stations(iff), &
    1144 o_scdnc%flag,o_scdnc%name, "Cloud droplet number concentration","m-3")
    1145   CALL histdef2d(iff,clef_stations(iff), &
    1146 o_cldncl%flag,o_cldncl%name, "CDNC at top of liquid water cloud", "m-3")
    1147   CALL histdef3d(iff,clef_stations(iff), &
    1148 o_reffclws%flag,o_reffclws%name, "Stratiform Cloud Droplet Effective Radius (aerosol diags.)","m")
    1149   CALL histdef3d(iff,clef_stations(iff), &
    1150 o_reffclwc%flag,o_reffclwc%name, "Convective Cloud Droplet Effective Radius (aerosol diags.)","m")
    1151   CALL histdef2d(iff,clef_stations(iff), &
    1152 o_cldnvi%flag,o_cldnvi%name, "Column Integrated Cloud Droplet Number", "m-2")
    1153   CALL histdef3d(iff,clef_stations(iff), &
    1154 o_lcc3d%flag,o_lcc3d%name, "Cloud liquid fraction","1")
    1155   CALL histdef3d(iff,clef_stations(iff), &
    1156 o_lcc3dcon%flag,o_lcc3dcon%name, "Convective cloud liquid fraction","1")
    1157   CALL histdef3d(iff,clef_stations(iff), &
    1158 o_lcc3dstra%flag,o_lcc3dstra%name, "Stratiform cloud liquid fraction","1")
    1159   CALL histdef2d(iff,clef_stations(iff), &
    1160 o_lcc%flag,o_lcc%name, "Cloud liquid fraction at top of cloud","1")
    1161   CALL histdef2d(iff,clef_stations(iff), &
    1162 o_reffclwtop%flag,o_reffclwtop%name, "Droplet effective radius at top of liquid water cloud", "m")
    1163  ENDIF
    1164 
    1165 
    1166  CALL histdef2d(iff,clef_stations(iff), &
    1167 o_alb1%flag,o_alb1%name, "Surface VIS albedo", "-")
    1168  CALL histdef2d(iff,clef_stations(iff), &
    1169 o_alb2%flag,o_alb2%name, "Surface Near IR albedo", "-")
    1170  CALL histdef2d(iff,clef_stations(iff), &
    1171 o_cdrm%flag,o_cdrm%name, "Momentum drag coef.", "-")
    1172  CALL histdef2d(iff,clef_stations(iff), &
    1173 o_cdrh%flag,o_cdrh%name, "Heat drag coef.", "-" )
    1174  CALL histdef2d(iff,clef_stations(iff), &
    1175 o_cldl%flag,o_cldl%name, "Low-level cloudiness", "-")
    1176  CALL histdef2d(iff,clef_stations(iff), &
    1177 o_cldm%flag,o_cldm%name, "Mid-level cloudiness", "-")
    1178  CALL histdef2d(iff,clef_stations(iff), &
    1179 o_cldh%flag,o_cldh%name, "High-level cloudiness", "-")
    1180  CALL histdef2d(iff,clef_stations(iff), &
    1181 o_cldt%flag,o_cldt%name, "Total cloudiness", "-")
    1182  CALL histdef2d(iff,clef_stations(iff), &
    1183 o_cldq%flag,o_cldq%name, "Cloud liquid water path", "kg/m2")
    1184  CALL histdef2d(iff,clef_stations(iff), &
    1185 o_lwp%flag,o_lwp%name, "Cloud water path", "kg/m2")
    1186  CALL histdef2d(iff,clef_stations(iff), &
    1187 o_iwp%flag,o_iwp%name, "Cloud ice water path", "kg/m2" )
    1188  CALL histdef2d(iff,clef_stations(iff), &
    1189 o_ue%flag,o_ue%name, "Zonal energy transport", "-")
    1190  CALL histdef2d(iff,clef_stations(iff), &
    1191 o_ve%flag,o_ve%name, "Merid energy transport", "-")
    1192  CALL histdef2d(iff,clef_stations(iff), &
    1193 o_uq%flag,o_uq%name, "Zonal humidity transport", "-")
    1194  CALL histdef2d(iff,clef_stations(iff), &
    1195 o_vq%flag,o_vq%name, "Merid humidity transport", "-")
    1196 
    1197      IF(iflag_con.GE.3) THEN ! sb
    1198  CALL histdef2d(iff,clef_stations(iff), &
    1199 o_cape%flag,o_cape%name, "Conv avlbl pot ener", "J/kg")
    1200  CALL histdef2d(iff,clef_stations(iff), &
    1201 o_pbase%flag,o_pbase%name, "Cld base pressure", "Pa")
    1202  CALL histdef2d(iff,clef_stations(iff), &
    1203 o_ptop%flag,o_ptop%name, "Cld top pressure", "Pa")
    1204  CALL histdef2d(iff,clef_stations(iff), &
    1205 o_fbase%flag,o_fbase%name, "Cld base mass flux", "kg/m2/s")
    1206  CALL histdef2d(iff,clef_stations(iff), &
    1207 o_plcl%flag,o_plcl%name, "Lifting Condensation Level", "hPa")
    1208  CALL histdef2d(iff,clef_stations(iff), &
    1209 o_plfc%flag,o_plfc%name, "Level of Free Convection", "hPa")
    1210  CALL histdef2d(iff,clef_stations(iff), &
    1211 o_wbeff%flag,o_wbeff%name, "Conv. updraft velocity at LFC", "m/s")
    1212  CALL histdef2d(iff,clef_stations(iff), &
    1213 o_prw%flag,o_prw%name, "Precipitable water", "kg/m2")
    1214   IF (.NOT.clef_stations(iff)) THEN
    1215 !
    1216 !IM: there is no way to have one single value in a netcdf file
    1217 !
    1218     type_ecri(1) = 't_max(X)'
    1219     type_ecri(2) = 't_max(X)'
    1220     type_ecri(3) = 't_max(X)'
    1221     type_ecri(4) = 't_max(X)'
    1222     type_ecri(5) = 't_max(X)'
    1223     type_ecri(6) = 't_max(X)'
    1224     CALL histdef2d(iff,clef_stations(iff), &
    1225   o_cape_max%flag,o_cape_max%name, "CAPE max.", "J/kg")
    1226   ENDIF
    1227    type_ecri(:) = type_ecri_files(:)
    1228  CALL histdef3d(iff,clef_stations(iff), &
    1229 o_upwd%flag,o_upwd%name, "saturated updraft", "kg/m2/s")
    1230  CALL histdef3d(iff,clef_stations(iff), &
    1231 o_Ma%flag,o_Ma%name, "undilute adiab updraft", "kg/m2/s")
    1232  CALL histdef3d(iff,clef_stations(iff), &
    1233 o_dnwd%flag,o_dnwd%name, "saturated downdraft", "kg/m2/s")
    1234  CALL histdef3d(iff,clef_stations(iff), &
    1235 o_dnwd0%flag,o_dnwd0%name, "unsat. downdraft", "kg/m2/s")
    1236  CALL histdef3d(iff,clef_stations(iff), &
    1237 o_mc%flag,o_mc%name, "Convective mass flux", "kg/m2/s")
    1238    type_ecri(1) = 'inst(X)'
    1239    type_ecri(2) = 'inst(X)'
    1240    type_ecri(3) = 'inst(X)'
    1241    type_ecri(4) = 'inst(X)'
    1242    type_ecri(5) = 'inst(X)'
    1243    type_ecri(6) = 'inst(X)'
    1244  CALL histdef2d(iff,clef_stations(iff), &
    1245 o_ftime_con%flag,o_ftime_con%name, "Fraction of time convection Occurs", " ")
    1246    type_ecri(:) = type_ecri_files(:)
    1247      ENDIF !iflag_con .GE. 3
    1248 
    1249  CALL histdef2d(iff,clef_stations(iff), &
    1250 o_s_pblh%flag,o_s_pblh%name, "Boundary Layer Height", "m")
    1251  CALL histdef2d(iff,clef_stations(iff), &
    1252 o_s_pblt%flag,o_s_pblt%name, "t at Boundary Layer Height", "K")
    1253  CALL histdef2d(iff,clef_stations(iff), &
    1254 o_s_lcl%flag,o_s_lcl%name, "Condensation level", "m")
    1255  CALL histdef2d(iff,clef_stations(iff), &
    1256 o_s_therm%flag,o_s_therm%name, "Exces du thermique", "K")
    1257 !IM : Les champs suivants (s_oliqCL, s_cteiCL, s_trmb1, s_trmb2, s_trmb3) ne sont pas definis dans HBTM.F
    1258 !CALL histdef2d(iff,clef_stations(iff), &
    1259 !o_s_capCL%flag,o_s_capCL%name, "Conv avlbl pot enerfor ABL", "J/m2" )
    1260 !CALL histdef2d(iff,clef_stations(iff), &
    1261 !o_s_oliqCL%flag,o_s_oliqCL%name, "Liq Water in BL", "kg/m2")
    1262 !CALL histdef2d(iff,clef_stations(iff), &
    1263 !o_s_cteiCL%flag,o_s_cteiCL%name, "Instability criteria(ABL)", "K")
    1264 !CALL histdef2d(iff,clef_stations(iff), &
    1265 !o_s_trmb1%flag,o_s_trmb1%name, "deep_cape(HBTM2)", "J/m2")
    1266 !CALL histdef2d(iff,clef_stations(iff), &
    1267 !o_s_trmb2%flag,o_s_trmb2%name, "inhibition (HBTM2)", "J/m2")
    1268 !CALL histdef2d(iff,clef_stations(iff), &
    1269 !o_s_trmb3%flag,o_s_trmb3%name, "Point Omega (HBTM2)", "m")
    1270 
    1271 ! Champs interpolles sur des niveaux de pression
    1272 
    1273    type_ecri(1) = 'inst(X)'
    1274    type_ecri(2) = 'inst(X)'
    1275    type_ecri(3) = 'inst(X)'
    1276    type_ecri(4) = 'inst(X)'
    1277    type_ecri(5) = 'inst(X)'
    1278    type_ecri(6) = 'inst(X)'
    1279 
    1280 ! Attention a reverifier
    1281 
    1282         ilev=0       
    1283         DO k=1, nlevSTD
    1284      bb2=clevSTD(k)
    1285      IF(bb2.EQ."850".OR.bb2.EQ."700".OR.bb2.EQ."500".OR.bb2.EQ."200" &
    1286 .OR.bb2.EQ."100".OR.bb2.EQ."50".OR.bb2.EQ."10")THEN
    1287       ilev=ilev+1
    1288 !     print*,'ilev k bb2 flag name ',ilev,k, bb2,o_uSTDlevs(ilev)%flag,o_uSTDlevs(ilev)%name
    1289  CALL histdef2d(iff,clef_stations(iff), &
    1290 o_uSTDlevs(ilev)%flag,o_uSTDlevs(ilev)%name,"Zonal wind "//bb2//"hPa", "m/s")
    1291  CALL histdef2d(iff,clef_stations(iff), &
    1292 o_vSTDlevs(ilev)%flag,o_vSTDlevs(ilev)%name,"Meridional wind "//bb2//"hPa", "m/s")
    1293  CALL histdef2d(iff,clef_stations(iff), &
    1294 o_wSTDlevs(ilev)%flag,o_wSTDlevs(ilev)%name,"Vertical wind "//bb2//"hPa", "Pa/s")
    1295  CALL histdef2d(iff,clef_stations(iff), &
    1296 o_zSTDlevs(ilev)%flag,o_zSTDlevs(ilev)%name,"Geopotential height "//bb2//"hPa", "m")
    1297  CALL histdef2d(iff,clef_stations(iff), &
    1298 o_qSTDlevs(ilev)%flag,o_qSTDlevs(ilev)%name,"Specific humidity "//bb2//"hPa", "kg/kg" )
    1299  CALL histdef2d(iff,clef_stations(iff), &
    1300 o_tSTDlevs(ilev)%flag,o_tSTDlevs(ilev)%name,"Temperature "//bb2//"hPa", "K")
    1301      ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR."500".OR.bb2.EQ."200".OR.bb2.EQ."50".OR.bb2.EQ."10")
    1302        ENDDO
    1303    type_ecri(:) = type_ecri_files(:)
    1304 
    1305  CALL histdef2d(iff,clef_stations(iff), &
    1306 o_t_oce_sic%flag,o_t_oce_sic%name, "Temp mixte oce-sic", "K")
    1307 
    1308  IF (type_ocean=='slab') &
    1309      CALL histdef2d(iff,clef_stations(iff), &
    1310 o_slab_bils%flag, o_slab_bils%name,"Bilan au sol sur ocean slab", "W/m2")
    1311 
    1312 ! Couplage conv-CL
    1313  IF (iflag_con.GE.3) THEN
    1314     IF (iflag_coupl>=1) THEN
    1315  CALL histdef2d(iff,clef_stations(iff), &
    1316 o_ale_bl%flag,o_ale_bl%name, "ALE BL", "m2/s2")
    1317  CALL histdef2d(iff,clef_stations(iff), &
    1318 o_alp_bl%flag,o_alp_bl%name, "ALP BL", "m2/s2")
    1319     ENDIF
    1320  ENDIF !(iflag_con.GE.3)
    1321 
    1322  CALL histdef2d(iff,clef_stations(iff), &
    1323 o_weakinv%flag,o_weakinv%name, "Weak inversion", "-")
    1324  CALL histdef2d(iff,clef_stations(iff), &
    1325 o_dthmin%flag,o_dthmin%name, "dTheta mini", "K/m")
    1326  CALL histdef2d(iff,clef_stations(iff), &
    1327 o_rh2m%flag,o_rh2m%name, "Relative humidity at 2m", "%" )
    1328 
    1329   IF (.NOT.clef_stations(iff)) THEN
    1330 !
    1331 !IM: there is no way to have one single value in a netcdf file
    1332 !
    1333    type_ecri(1) = 't_min(X)'
    1334    type_ecri(2) = 't_min(X)'
    1335    type_ecri(3) = 't_min(X)'
    1336    type_ecri(4) = 't_min(X)'
    1337    type_ecri(5) = 't_min(X)'
    1338    type_ecri(6) = 't_min(X)'
    1339    CALL histdef2d(iff,clef_stations(iff),o_rh2m_min%flag,o_rh2m_min%name, "Min Relative humidity at 2m", "%" )
    1340    type_ecri(1) = 't_max(X)'
    1341    type_ecri(2) = 't_max(X)'
    1342    type_ecri(3) = 't_max(X)'
    1343    type_ecri(4) = 't_max(X)'
    1344    type_ecri(5) = 't_max(X)'
    1345    type_ecri(6) = 't_max(X)'
    1346    CALL histdef2d(iff,clef_stations(iff),o_rh2m_max%flag,o_rh2m_max%name, "Max Relative humidity at 2m", "%" )
    1347   ENDIF 
    1348 
    1349    type_ecri(:) = type_ecri_files(:)
    1350  CALL histdef2d(iff,clef_stations(iff),o_qsat2m%flag,o_qsat2m%name, "Saturant humidity at 2m", "%")
    1351  CALL histdef2d(iff,clef_stations(iff),o_tpot%flag,o_tpot%name, "Surface air potential temperature", "K")
    1352  CALL histdef2d(iff,clef_stations(iff), &
    1353 o_tpote%flag,o_tpote%name, "Surface air equivalent potential temperature", "K")
    1354  CALL histdef2d(iff,clef_stations(iff),o_SWnetOR%flag,o_SWnetOR%name, "Sfce net SW radiation OR", "W/m2")
    1355  CALL histdef2d(iff,clef_stations(iff),o_SWdownOR%flag,o_SWdownOR%name, "Sfce incident SW radiation OR", "W/m2")
    1356  CALL histdef2d(iff,clef_stations(iff),o_LWdownOR%flag,o_LWdownOR%name, "Sfce incident LW radiation OR", "W/m2")
    1357  CALL histdef2d(iff,clef_stations(iff),o_snowl%flag,o_snowl%name, "Solid Large-scale Precip.", "kg/(m2*s)")
    1358 
    1359  CALL histdef2d(iff,clef_stations(iff),o_solldown%flag,o_solldown%name, "Down. IR rad. at surface", "W/m2")
    1360  CALL histdef2d(iff,clef_stations(iff),o_dtsvdfo%flag,o_dtsvdfo%name, "Boundary-layer dTs(o)", "K/s")
    1361  CALL histdef2d(iff,clef_stations(iff),o_dtsvdft%flag,o_dtsvdft%name, "Boundary-layer dTs(t)", "K/s")
    1362  CALL histdef2d(iff,clef_stations(iff),o_dtsvdfg%flag,o_dtsvdfg%name, "Boundary-layer dTs(g)", "K/s")
    1363  CALL histdef2d(iff,clef_stations(iff),o_dtsvdfi%flag,o_dtsvdfi%name, "Boundary-layer dTs(g)", "K/s")
    1364  CALL histdef2d(iff,clef_stations(iff),o_rugs%flag,o_rugs%name, "rugosity", "-" )
    1365 
    1366 ! Champs 3D:
    1367  CALL histdef3d(iff,clef_stations(iff),o_ec550aer%flag,o_ec550aer%name, "Extinction at 550nm", "m^-1")
    1368  CALL histdef3d(iff,clef_stations(iff),o_lwcon%flag,o_lwcon%name, "Cloud liquid water content", "kg/kg")
    1369  CALL histdef3d(iff,clef_stations(iff),o_iwcon%flag,o_iwcon%name, "Cloud ice water content", "kg/kg")
    1370  CALL histdef3d(iff,clef_stations(iff),o_temp%flag,o_temp%name, "Air temperature", "K" )
    1371  CALL histdef3d(iff,clef_stations(iff),o_theta%flag,o_theta%name, "Potential air temperature", "K" )
    1372  CALL histdef3d(iff,clef_stations(iff),o_ovap%flag,o_ovap%name, "Specific humidity", "kg/kg" )
    1373  CALL histdef3d(iff,clef_stations(iff), &
    1374 o_ovapinit%flag,o_ovapinit%name, "Specific humidity (begin of timestep)", "kg/kg" )
    1375  CALL histdef3d(iff,clef_stations(iff), &
    1376 o_geop%flag,o_geop%name, "Geopotential height", "m2/s2")
    1377  CALL histdef3d(iff,clef_stations(iff), &
    1378 o_vitu%flag,o_vitu%name, "Zonal wind", "m/s" )
    1379  CALL histdef3d(iff,clef_stations(iff), &
    1380 o_vitv%flag,o_vitv%name, "Meridional wind", "m/s" )
    1381  CALL histdef3d(iff,clef_stations(iff), &
    1382 o_vitw%flag,o_vitw%name, "Vertical wind", "Pa/s" )
    1383  CALL histdef3d(iff,clef_stations(iff), &
    1384 o_pres%flag,o_pres%name, "Air pressure", "Pa" )
    1385  CALL histdef3d(iff,clef_stations(iff), &
    1386 o_paprs%flag,o_paprs%name, "Air pressure Inter-Couches", "Pa" )
    1387  CALL histdef3d(iff,clef_stations(iff), &
    1388 o_mass%flag,o_mass%name, "Masse Couches", "kg/m2" )
    1389  CALL histdef3d(iff,clef_stations(iff), &
    1390 o_zfull%flag,o_zfull%name, "Altitude of full pressure levels", "m" )
    1391  CALL histdef3d(iff,clef_stations(iff), &
    1392 o_zhalf%flag,o_zhalf%name, "Altitude of half pressure levels", "m" )
    1393  CALL histdef3d(iff,clef_stations(iff), &
    1394 o_rneb%flag,o_rneb%name, "Cloud fraction", "-")
    1395  CALL histdef3d(iff,clef_stations(iff), &
    1396 o_rnebcon%flag,o_rnebcon%name, "Convective Cloud Fraction", "-")
    1397  CALL histdef3d(iff,clef_stations(iff), &
    1398 o_rhum%flag,o_rhum%name, "Relative humidity", "-")
    1399  CALL histdef3d(iff,clef_stations(iff), &
    1400 o_ozone%flag,o_ozone%name, "Ozone mole fraction", "-")
    1401  if (read_climoz == 2) &
    1402       CALL histdef3d(iff,clef_stations(iff), &
    1403 o_ozone_light%flag,o_ozone_light%name, &
    1404       "Daylight ozone mole fraction", "-")
    1405  CALL histdef3d(iff,clef_stations(iff), &
    1406 o_dtphy%flag,o_dtphy%name, "Physics dT", "K/s")
    1407  CALL histdef3d(iff,clef_stations(iff), &
    1408 o_dqphy%flag,o_dqphy%name, "Physics dQ", "(kg/kg)/s")
    1409  CALL histdef3d(iff,clef_stations(iff), &
    1410 o_cldtau%flag,o_cldtau%name, "Cloud optical thickness", "1")
    1411  CALL histdef3d(iff,clef_stations(iff), &
    1412 o_cldemi%flag,o_cldemi%name, "Cloud optical emissivity", "1")
    1413 !IM: bug ?? dimensionnement variables (klon,klev+1) pmflxr, pmflxs, prfl, psfl
    1414  CALL histdef3d(iff,clef_stations(iff), &
    1415 o_pr_con_l%flag,o_pr_con_l%name, "Convective precipitation lic", " ")
    1416  CALL histdef3d(iff,clef_stations(iff), &
    1417 o_pr_con_i%flag,o_pr_con_i%name, "Convective precipitation ice", " ")
    1418  CALL histdef3d(iff,clef_stations(iff), &
    1419 o_pr_lsc_l%flag,o_pr_lsc_l%name, "Large scale precipitation lic", " ")
    1420  CALL histdef3d(iff,clef_stations(iff), &
    1421 o_pr_lsc_i%flag,o_pr_lsc_i%name, "Large scale precipitation ice", " ")
    1422 !Cloud droplet effective radius
    1423  CALL histdef3d(iff,clef_stations(iff), &
    1424 o_re%flag,o_re%name, "Cloud droplet effective radius","um")
    1425  CALL histdef3d(iff,clef_stations(iff), &
    1426 o_fl%flag,o_fl%name, "Denominator of Cloud droplet effective radius"," ")
    1427 !FH Sorties pour la couche limite
    1428      if (iflag_pbl>1) then
    1429  CALL histdef3d(iff,clef_stations(iff), &
    1430 o_tke%flag,o_tke%name, "TKE", "m2/s2")
    1431   IF (.NOT.clef_stations(iff)) THEN
    1432 !
    1433 !IM: there is no way to have one single value in a netcdf file
    1434 !
    1435    type_ecri(1) = 't_max(X)'
    1436    type_ecri(2) = 't_max(X)'
    1437    type_ecri(3) = 't_max(X)'
    1438    type_ecri(4) = 't_max(X)'
    1439    type_ecri(5) = 't_max(X)'
    1440    type_ecri(6) = 't_max(X)'
    1441    CALL histdef3d(iff,clef_stations(iff), &
    1442   o_tke_max%flag,o_tke_max%name, "TKE max", "m2/s2")
    1443   ENDIF
    1444    type_ecri(:) = type_ecri_files(:)
    1445      endif
    1446 
    1447  CALL histdef3d(iff,clef_stations(iff), &
    1448 o_kz%flag,o_kz%name, "Kz melange", "m2/s")
    1449   IF (.NOT.clef_stations(iff)) THEN
    1450 !
    1451 !IM: there is no way to have one single value in a netcdf file
    1452 !
    1453    type_ecri(1) = 't_max(X)'
    1454    type_ecri(2) = 't_max(X)'
    1455    type_ecri(3) = 't_max(X)'
    1456    type_ecri(4) = 't_max(X)'
    1457    type_ecri(5) = 't_max(X)'
    1458    type_ecri(6) = 't_max(X)'
    1459    CALL histdef3d(iff,clef_stations(iff), &
    1460    o_kz_max%flag,o_kz_max%name, "Kz melange max", "m2/s" )
    1461   ENDIF
    1462    type_ecri(:) = type_ecri_files(:)
    1463  CALL histdef3d(iff,clef_stations(iff), &
    1464 o_clwcon%flag,o_clwcon%name, "Convective Cloud Liquid water content", "kg/kg")
    1465  CALL histdef3d(iff,clef_stations(iff), &
    1466 o_dtdyn%flag,o_dtdyn%name, "Dynamics dT", "K/s")
    1467  CALL histdef3d(iff,clef_stations(iff), &
    1468 o_dqdyn%flag,o_dqdyn%name, "Dynamics dQ", "(kg/kg)/s")
    1469  CALL histdef3d(iff,clef_stations(iff), &
    1470 o_dudyn%flag,o_dudyn%name, "Dynamics dU", "m/s2")
    1471  CALL histdef3d(iff,clef_stations(iff), &
    1472 o_dvdyn%flag,o_dvdyn%name, "Dynamics dV", "m/s2")
    1473  CALL histdef3d(iff,clef_stations(iff), &
    1474 o_dtcon%flag,o_dtcon%name, "Convection dT", "K/s")
    1475  CALL histdef3d(iff,clef_stations(iff), &
    1476 o_ducon%flag,o_ducon%name, "Convection du", "m/s2")
    1477  CALL histdef3d(iff,clef_stations(iff), &
    1478 o_dqcon%flag,o_dqcon%name, "Convection dQ", "(kg/kg)/s")
    1479 
    1480 ! Wakes
    1481  IF(iflag_con.EQ.3) THEN
    1482  IF (iflag_wake >= 1) THEN
    1483    CALL histdef2d(iff,clef_stations(iff), &
    1484 o_ale_wk%flag,o_ale_wk%name, "ALE WK", "m2/s2")
    1485    CALL histdef2d(iff,clef_stations(iff), &
    1486 o_alp_wk%flag,o_alp_wk%name, "ALP WK", "m2/s2")
    1487    CALL histdef2d(iff,clef_stations(iff), &
    1488 o_ale%flag,o_ale%name, "ALE", "m2/s2")
    1489    CALL histdef2d(iff,clef_stations(iff), &
    1490 o_alp%flag,o_alp%name, "ALP", "W/m2")
    1491    CALL histdef2d(iff,clef_stations(iff),o_cin%flag,o_cin%name, "Convective INhibition", "m2/s2")
    1492    CALL histdef2d(iff,clef_stations(iff),o_wape%flag,o_WAPE%name, "WAPE", "m2/s2")
    1493    CALL histdef2d(iff,clef_stations(iff),o_wake_h%flag,o_wake_h%name, "wake_h", "-")
    1494    CALL histdef2d(iff,clef_stations(iff),o_wake_s%flag,o_wake_s%name, "wake_s", "-")
    1495    CALL histdef3d(iff,clef_stations(iff),o_dtwak%flag,o_dtwak%name, "Wake dT", "K/s")
    1496    CALL histdef3d(iff,clef_stations(iff),o_dqwak%flag,o_dqwak%name, "Wake dQ", "(kg/kg)/s")
    1497    CALL histdef3d(iff,clef_stations(iff),o_wake_deltat%flag,o_wake_deltat%name, "wake_deltat", " ")
    1498    CALL histdef3d(iff,clef_stations(iff),o_wake_deltaq%flag,o_wake_deltaq%name, "wake_deltaq", " ")
    1499    CALL histdef3d(iff,clef_stations(iff),o_wake_omg%flag,o_wake_omg%name, "wake_omg", " ")
    1500  ENDIF
    1501    CALL histdef3d(iff,clef_stations(iff),o_Vprecip%flag,o_Vprecip%name, "precipitation vertical profile", "-")
    1502    CALL histdef3d(iff,clef_stations(iff),o_ftd%flag,o_ftd%name, "tend temp due aux descentes precip", "-")
    1503    CALL histdef3d(iff,clef_stations(iff),o_fqd%flag,o_fqd%name,"tend vap eau due aux descentes precip", "-")
    1504  ENDIF !(iflag_con.EQ.3)
    1505 
    1506  CALL histdef3d(iff,clef_stations(iff),o_dtlsc%flag,o_dtlsc%name, "Condensation dT", "K/s")
    1507  CALL histdef3d(iff,clef_stations(iff),o_dtlschr%flag,o_dtlschr%name,"Large-scale condensational heating rate","K/s")
    1508  CALL histdef3d(iff,clef_stations(iff),o_dqlsc%flag,o_dqlsc%name, "Condensation dQ", "(kg/kg)/s")
    1509  CALL histdef3d(iff,clef_stations(iff),o_dtvdf%flag,o_dtvdf%name, "Boundary-layer dT", "K/s")
    1510  CALL histdef3d(iff,clef_stations(iff),o_dqvdf%flag,o_dqvdf%name, "Boundary-layer dQ", "(kg/kg)/s")
    1511  CALL histdef3d(iff,clef_stations(iff),o_dteva%flag,o_dteva%name, "Reevaporation dT", "K/s")
    1512  CALL histdef3d(iff,clef_stations(iff),o_dqeva%flag,o_dqeva%name, "Reevaporation dQ", "(kg/kg)/s")
    1513  CALL histdef3d(iff,clef_stations(iff),o_ptconv%flag,o_ptconv%name, "POINTS CONVECTIFS", " ")
    1514  CALL histdef3d(iff,clef_stations(iff),o_ratqs%flag,o_ratqs%name, "RATQS", " ")
    1515  CALL histdef3d(iff,clef_stations(iff),o_dtthe%flag,o_dtthe%name, "Thermal dT", "K/s")
    1516 
    1517 if(iflag_thermals.gt.1) THEN
    1518  CALL histdef3d(iff,clef_stations(iff),o_dqlscth%flag,o_dqlscth%name, "dQ therm.", "(kg/kg)/s")
    1519  CALL histdef3d(iff,clef_stations(iff),o_dqlscst%flag,o_dqlscst%name, "dQ strat.", "(kg/kg)/s")
    1520  CALL histdef3d(iff,clef_stations(iff),o_dtlscth%flag,o_dtlscth%name, "dQ therm.", "K/s")
    1521  CALL histdef3d(iff,clef_stations(iff),o_dtlscst%flag,o_dtlscst%name, "dQ strat.", "K/s")
    1522  CALL histdef2d(iff,clef_stations(iff),o_plulth%flag,o_plulth%name, "Rainfall therm.", "K/s")
    1523  CALL histdef2d(iff,clef_stations(iff),o_plulst%flag,o_plulst%name, "Rainfall strat.", "K/s")
    1524  CALL histdef2d(iff,clef_stations(iff),o_lmaxth%flag,o_lmaxth%name, "Upper level thermals", "")
    1525  CALL histdef3d(iff,clef_stations(iff),o_ptconvth%flag,o_ptconvth%name, "POINTS CONVECTIFS therm.", " ")
    1526  CALL histdef3d(iff,clef_stations(iff),o_f_th%flag,o_f_th%name, "Thermal plume mass flux", "kg/(m2*s)")
    1527  CALL histdef3d(iff,clef_stations(iff),o_e_th%flag,o_e_th%name,"Thermal plume entrainment","K/s")
    1528  CALL histdef3d(iff,clef_stations(iff),o_w_th%flag,o_w_th%name,"Thermal plume vertical velocity","m/s")
    1529  CALL histdef3d(iff,clef_stations(iff), &
    1530 o_lambda_th%flag,o_lambda_th%name,"Thermal plume vertical velocity","m/s")
    1531  CALL histdef2d(iff,clef_stations(iff), &
    1532 o_ftime_th%flag,o_ftime_th%name,"Fraction of time Shallow convection occurs"," ")
    1533  CALL histdef3d(iff,clef_stations(iff), &
    1534 o_q_th%flag,o_q_th%name, "Thermal plume total humidity", "kg/kg")
    1535  CALL histdef3d(iff,clef_stations(iff), &
    1536 o_a_th%flag,o_a_th%name, "Thermal plume fraction", "")
    1537  CALL histdef3d(iff,clef_stations(iff), &
    1538 o_d_th%flag,o_d_th%name, "Thermal plume detrainment", "K/s")
    1539 
    1540  CALL histdef2d(iff,clef_stations(iff), &
    1541 o_f0_th%flag,o_f0_th%name, "Thermal closure mass flux", "K/s")
    1542  CALL histdef2d(iff,clef_stations(iff), &
    1543 o_zmax_th%flag,o_zmax_th%name, "Thermal plume height", "K/s")
    1544  CALL histdef3d(iff,clef_stations(iff), &
    1545 o_dqthe%flag,o_dqthe%name, "Thermal dQ", "(kg/kg)/s")
    1546 endif !iflag_thermals.gt.1
    1547  CALL histdef3d(iff,clef_stations(iff), &
    1548 o_dtajs%flag,o_dtajs%name, "Dry adjust. dT", "K/s")
    1549  CALL histdef3d(iff,clef_stations(iff), &
    1550 o_dqajs%flag,o_dqajs%name, "Dry adjust. dQ", "(kg/kg)/s")
    1551  CALL histdef3d(iff,clef_stations(iff), &
    1552 o_dtswr%flag,o_dtswr%name, "SW radiation dT", "K/s")
    1553  CALL histdef3d(iff,clef_stations(iff), &
    1554 o_dtsw0%flag,o_dtsw0%name, "CS SW radiation dT", "K/s")
    1555  CALL histdef3d(iff,clef_stations(iff), &
    1556 o_dtlwr%flag,o_dtlwr%name, "LW radiation dT", "K/s")
    1557  CALL histdef3d(iff,clef_stations(iff), &
    1558 o_dtlw0%flag,o_dtlw0%name, "CS LW radiation dT", "K/s")
    1559  CALL histdef3d(iff,clef_stations(iff), &
    1560 o_dtec%flag,o_dtec%name, "Cinetic dissip dT", "K/s")
    1561  CALL histdef3d(iff,clef_stations(iff), &
    1562 o_duvdf%flag,o_duvdf%name, "Boundary-layer dU", "m/s2")
    1563  CALL histdef3d(iff,clef_stations(iff), &
    1564 o_dvvdf%flag,o_dvvdf%name, "Boundary-layer dV", "m/s2")
    1565 
    1566      IF (ok_orodr) THEN
    1567  CALL histdef3d(iff,clef_stations(iff), &
    1568 o_duoro%flag,o_duoro%name, "Orography dU", "m/s2")
    1569  CALL histdef3d(iff,clef_stations(iff), &
    1570 o_dvoro%flag,o_dvoro%name, "Orography dV", "m/s2")
    1571  CALL histdef3d(iff,clef_stations(iff), &
    1572 o_dtoro%flag,o_dtoro%name, "Orography dT", "K/s")
    1573      ENDIF
    1574 
    1575      IF (ok_orolf) THEN
    1576  CALL histdef3d(iff,clef_stations(iff), &
    1577 o_dulif%flag,o_dulif%name, "Orography dU", "m/s2")
    1578  CALL histdef3d(iff,clef_stations(iff), &
    1579 o_dvlif%flag,o_dvlif%name, "Orography dV", "m/s2")
    1580  CALL histdef3d(iff,clef_stations(iff), &
    1581 o_dtlif%flag,o_dtlif%name, "Orography dT", "K/s")
    1582      ENDIF
    1583 
    1584      IF (ok_hines) then
    1585  CALL histdef3d(iff,clef_stations(iff), &
    1586 o_duhin%flag,o_duhin%name, "Hines GWD dU", "m/s2")
    1587  CALL histdef3d(iff,clef_stations(iff), &
    1588 o_dvhin%flag,o_dvhin%name, "Hines GWD dV", "m/s2")
    1589 
    1590  CALL histdef3d(iff,clef_stations(iff), &
    1591 o_dthin%flag,o_dthin%name, "Hines GWD dT", "K/s")
    1592      ENDIF
    1593 
    1594  CALL histdef3d(iff,clef_stations(iff), &
    1595 o_rsu%flag,o_rsu%name, "SW upward radiation", "W m-2")
    1596  CALL histdef3d(iff,clef_stations(iff), &
    1597 o_rsd%flag,o_rsd%name, "SW downward radiation", "W m-2")
    1598  CALL histdef3d(iff,clef_stations(iff), &
    1599 o_rlu%flag,o_rlu%name, "LW upward radiation", "W m-2")
    1600  CALL histdef3d(iff,clef_stations(iff), &
    1601 o_rld%flag,o_rld%name, "LW downward radiation", "W m-2")
    1602 
    1603  CALL histdef3d(iff,clef_stations(iff), &
    1604 o_rsucs%flag,o_rsucs%name, "SW CS upward radiation", "W m-2")
    1605  CALL histdef3d(iff,clef_stations(iff), &
    1606 o_rsdcs%flag,o_rsdcs%name, "SW CS downward radiation", "W m-2")
    1607  CALL histdef3d(iff,clef_stations(iff), &
    1608 o_rlucs%flag,o_rlucs%name, "LW CS upward radiation", "W m-2")
    1609  CALL histdef3d(iff,clef_stations(iff), &
    1610 o_rldcs%flag,o_rldcs%name, "LW CS downward radiation", "W m-2")
    1611  
    1612  CALL histdef3d(iff,clef_stations(iff), &
    1613 o_tnt%flag,o_tnt%name, "Tendency of air temperature", "K s-1")
    1614 
    1615  CALL histdef3d(iff,clef_stations(iff), &
    1616 o_tntc%flag,o_tntc%name, "Tendency of air temperature due to Moist Convection", &
    1617 "K s-1")
    1618 
    1619  CALL histdef3d(iff,clef_stations(iff), &
    1620 o_tntr%flag,o_tntr%name, "Air temperature tendency due to Radiative heating", &
    1621 "K s-1")
    1622 
    1623  CALL histdef3d(iff,clef_stations(iff), &
    1624 o_tntscpbl%flag,o_tntscpbl%name, "Air temperature tendency due to St cloud and precipitation and BL mixing", &
    1625 "K s-1")
    1626 
    1627  CALL histdef3d(iff,clef_stations(iff), &
    1628 o_tnhus%flag,o_tnhus%name, "Tendency of specific humidity", "s-1")
    1629 
    1630  CALL histdef3d(iff,clef_stations(iff), &
    1631 o_tnhusc%flag,o_tnhusc%name, "Tendency of specific humidity due to convection", "s-1")
    1632 
    1633  CALL histdef3d(iff,clef_stations(iff), &
    1634 o_tnhusscpbl%flag,o_tnhusscpbl%name, "Tendency of Specific humidity due to ST cl, precip and BL mixing", &
    1635 "s-1")
    1636 
    1637  CALL histdef3d(iff,clef_stations(iff), &
    1638 o_evu%flag,o_evu%name, "Eddy viscosity coefficient for Momentum Variables", "m2 s-1")
    1639 
    1640  CALL histdef3d(iff,clef_stations(iff), &
    1641 o_h2o%flag,o_h2o%name, "Mass Fraction of Water", "1")
    1642 
    1643  CALL histdef3d(iff,clef_stations(iff), &
    1644 o_mcd%flag,o_mcd%name, "Downdraft COnvective Mass Flux", "kg/(m2*s)")
    1645 
    1646  CALL histdef3d(iff,clef_stations(iff), &
    1647 o_dmc%flag,o_dmc%name, "Deep COnvective Mass Flux", "kg/(m2*s)")
    1648 
    1649  CALL histdef3d(iff,clef_stations(iff), &
    1650 o_ref_liq%flag,o_ref_liq%name, "Effective radius of convective cloud liquid water particle", "m")
    1651 
    1652  CALL histdef3d(iff,clef_stations(iff), &
    1653 o_ref_ice%flag,o_ref_ice%name, "Effective radius of startiform cloud ice particle", "m")
    1654 
    1655    if (RCO2_per.NE.RCO2_act.OR.RCH4_per.NE.RCH4_act.OR. &
    1656     RN2O_per.NE.RN2O_act.OR.RCFC11_per.NE.RCFC11_act.OR. &
    1657     RCFC12_per.NE.RCFC12_act) THEN
    1658 
    1659  CALL histdef2d(iff,clef_stations(iff),o_rsut4co2%flag,o_rsut4co2%name, &
    1660  "TOA Out SW in 4xCO2 atmosphere", "W/m2")
    1661 CALL histdef2d(iff,clef_stations(iff),o_rlut4co2%flag,o_rlut4co2%name, &
    1662 "TOA Out LW in 4xCO2 atmosphere", "W/m2")
    1663 CALL histdef2d(iff,clef_stations(iff),o_rsutcs4co2%flag,o_rsutcs4co2%name, &
    1664 "TOA Out CS SW in 4xCO2 atmosphere", "W/m2")
    1665 CALL histdef2d(iff,clef_stations(iff),o_rlutcs4co2%flag,o_rlutcs4co2%name, &
    1666 "TOA Out CS LW in 4xCO2 atmosphere", "W/m2")
    1667 
    1668 CALL histdef3d(iff,clef_stations(iff),o_rsu4co2%flag,o_rsu4co2%name, &
    1669 "Upwelling SW 4xCO2 atmosphere", "W/m2")
    1670 CALL histdef3d(iff,clef_stations(iff),o_rlu4co2%flag,o_rlu4co2%name, &
    1671 "Upwelling LW 4xCO2 atmosphere", "W/m2")
    1672 CALL histdef3d(iff,clef_stations(iff),o_rsucs4co2%flag,o_rsucs4co2%name, &
    1673 "Upwelling CS SW 4xCO2 atmosphere", "W/m2")
    1674 CALL histdef3d(iff,clef_stations(iff),o_rlucs4co2%flag,o_rlucs4co2%name, &
    1675 "Upwelling CS LW 4xCO2 atmosphere", "W/m2")
    1676 
    1677  CALL histdef3d(iff,clef_stations(iff),o_rsd4co2%flag,o_rsd4co2%name, &
    1678  "Downwelling SW 4xCO2 atmosphere", "W/m2")
    1679  CALL histdef3d(iff,clef_stations(iff),o_rld4co2%flag,o_rld4co2%name, &
    1680 "Downwelling LW 4xCO2 atmosphere", "W/m2")
    1681  CALL histdef3d(iff,clef_stations(iff),o_rsdcs4co2%flag,o_rsdcs4co2%name, &
    1682 "Downwelling CS SW 4xCO2 atmosphere", "W/m2")
    1683  CALL histdef3d(iff,clef_stations(iff),o_rldcs4co2%flag,o_rldcs4co2%name, &
    1684 "Downwelling CS LW 4xCO2 atmosphere", "W/m2")
    1685 
    1686    endif
    1687 
    1688 
    1689     IF (nqtot>=3) THEN
    1690      DO iq=3,nqtot 
    1691        iiq=niadv(iq)
    1692        o_trac(iq-2) = ctrl_out((/ 4, 5, 1, 1, 1, 10 /),tname(iiq))
    1693        CALL histdef3d (iff,clef_stations(iff), &
    1694  o_trac(iq-2)%flag,o_trac(iq-2)%name,'Tracer '//ttext(iiq), "-" )
    1695      ENDDO
    1696     ENDIF
    1697 
    1698         CALL histend(nid_files(iff))
    1699 
    1700          ndex2d = 0
    1701          ndex3d = 0
    1702 
    1703          ENDIF ! clef_files
    1704 
    1705          ENDDO !  iff
    1706      print*,'Fin phys_output_mod.F90'
    1707       end subroutine phys_output_open
    1708 
    1709       SUBROUTINE histdef2d (iff,lpoint,flag_var,nomvar,titrevar,unitvar)
    1710      
    1711        use ioipsl
    1712        USE dimphy
    1713        USE mod_phys_lmdz_para
    1714        USE iophy
    1715 
    1716        IMPLICIT NONE
    1717        
    1718        include "dimensions.h"
    1719        include "temps.h"
    1720        include "indicesol.h"
    1721        include "clesphys.h"
    1722 
    1723        integer                          :: iff
    1724        logical                          :: lpoint
    1725        integer, dimension(nfiles)       :: flag_var
    1726        character(len=20)                 :: nomvar
    1727        character(len=*)                 :: titrevar
    1728        character(len=*)                 :: unitvar
    1729 
    1730        real zstophym
    1731 
    1732        if (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') then
    1733          zstophym=zoutm(iff)
    1734        else
    1735          zstophym=zdtime
    1736        endif
    1737 
    1738 ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def
    1739        call conf_physoutputs(nomvar,flag_var)
    1740      
    1741        if(.NOT.lpoint) THEN 
     900          CALL histdef2d(iff,clef_stations(iff),o_phis%flag,o_phis%name,"Surface geop.height", "m2/s2" )
     901          CALL histdef2d(iff,clef_stations(iff),o_contfracOR%flag,o_contfracOR%name,"% sfce terre OR", "-" )
     902          CALL histdef2d(iff,clef_stations(iff),o_aireTER%flag,o_aireTER%name,"Grid area CONT", "-" )
     903          CALL histdef2d(iff,clef_stations(iff),o_flat%flag,o_flat%name, "Latent heat flux", "W/m2")
     904          CALL histdef2d(iff,clef_stations(iff),o_slp%flag,o_slp%name, "Sea Level Pressure", "Pa" )
     905          CALL histdef2d(iff,clef_stations(iff),o_tsol%flag,o_tsol%name, "Surface Temperature", "K")
     906          CALL histdef2d(iff,clef_stations(iff),o_t2m%flag,o_t2m%name, "Temperature 2m", "K" )
     907          IF (.NOT.clef_stations(iff)) THEN
     908             !
     909             !IM: there is no way to have one single value in a netcdf file
     910             !
     911             type_ecri(1) = 't_min(X)'
     912             type_ecri(2) = 't_min(X)'
     913             type_ecri(3) = 't_min(X)'
     914             type_ecri(4) = 't_min(X)'
     915             type_ecri(5) = 't_min(X)'
     916             type_ecri(6) = 't_min(X)'
     917             CALL histdef2d(iff,clef_stations(iff),o_t2m_min%flag,o_t2m_min%name, "Temp 2m min", "K" )
     918             type_ecri(1) = 't_max(X)'
     919             type_ecri(2) = 't_max(X)'
     920             type_ecri(3) = 't_max(X)'
     921             type_ecri(4) = 't_max(X)'
     922             type_ecri(5) = 't_max(X)'
     923             type_ecri(6) = 't_max(X)'
     924             CALL histdef2d(iff,clef_stations(iff),o_t2m_max%flag,o_t2m_max%name, "Temp 2m max", "K" )
     925          ENDIF
     926          type_ecri(:) = type_ecri_files(:)
     927          CALL histdef2d(iff,clef_stations(iff),o_wind10m%flag,o_wind10m%name, "10-m wind speed", "m/s")
     928          CALL histdef2d(iff,clef_stations(iff),o_wind10max%flag,o_wind10max%name, "10m wind speed max", "m/s")
     929          CALL histdef2d(iff,clef_stations(iff),o_sicf%flag,o_sicf%name, "Sea-ice fraction", "-" )
     930          CALL histdef2d(iff,clef_stations(iff),o_q2m%flag,o_q2m%name, "Specific humidity 2m", "kg/kg")
     931          CALL histdef2d(iff,clef_stations(iff),o_u10m%flag,o_u10m%name, "Vent zonal 10m", "m/s" )
     932          CALL histdef2d(iff,clef_stations(iff),o_v10m%flag,o_v10m%name, "Vent meridien 10m", "m/s")
     933          CALL histdef2d(iff,clef_stations(iff),o_psol%flag,o_psol%name, "Surface Pressure", "Pa" )
     934          CALL histdef2d(iff,clef_stations(iff),o_qsurf%flag,o_qsurf%name, "Surface Air humidity", "kg/kg")
     935
     936          if (.not. ok_veget) then
     937             CALL histdef2d(iff,clef_stations(iff),o_qsol%flag,o_qsol%name, "Soil watter content", "mm" )
     938          endif
     939
     940          CALL histdef2d(iff,clef_stations(iff),o_ndayrain%flag,o_ndayrain%name, "Number of dayrain(liq+sol)", "-")
     941          CALL histdef2d(iff,clef_stations(iff),o_precip%flag,o_precip%name, "Precip Totale liq+sol", "kg/(s*m2)" )
     942          CALL histdef2d(iff,clef_stations(iff),o_plul%flag,o_plul%name, "Large-scale Precip.", "kg/(s*m2)")
     943          CALL histdef2d(iff,clef_stations(iff),o_pluc%flag,o_pluc%name, "Convective Precip.", "kg/(s*m2)")
     944          CALL histdef2d(iff,clef_stations(iff),o_snow%flag,o_snow%name, "Snow fall", "kg/(s*m2)" )
     945          CALL histdef2d(iff,clef_stations(iff),o_msnow%flag,o_msnow%name, "Surface snow amount", "kg/m2" )
     946          CALL histdef2d(iff,clef_stations(iff),o_fsnow%flag,o_fsnow%name, "Surface snow area fraction", "-" )
     947          CALL histdef2d(iff,clef_stations(iff),o_evap%flag,o_evap%name, "Evaporat", "kg/(s*m2)" )
     948          CALL histdef2d(iff,clef_stations(iff),o_tops%flag,o_tops%name, "Solar rad. at TOA", "W/m2")
     949          CALL histdef2d(iff,clef_stations(iff),o_tops0%flag,o_tops0%name, "CS Solar rad. at TOA", "W/m2")
     950          CALL histdef2d(iff,clef_stations(iff),o_topl%flag,o_topl%name, "IR rad. at TOA", "W/m2" )
     951          CALL histdef2d(iff,clef_stations(iff),o_topl0%flag,o_topl0%name, "IR rad. at TOA", "W/m2")
     952          CALL histdef2d(iff,clef_stations(iff),o_SWupTOA%flag,o_SWupTOA%name, "SWup at TOA", "W/m2")
     953          CALL histdef2d(iff,clef_stations(iff),o_SWupTOAclr%flag,o_SWupTOAclr%name, "SWup clear sky at TOA", "W/m2")
     954          CALL histdef2d(iff,clef_stations(iff),o_SWdnTOA%flag,o_SWdnTOA%name, "SWdn at TOA", "W/m2" )
     955          CALL histdef2d(iff,clef_stations(iff),o_SWdnTOAclr%flag,o_SWdnTOAclr%name, "SWdn clear sky at TOA", "W/m2")
     956          CALL histdef2d(iff,clef_stations(iff),o_nettop%flag,o_nettop%name, "Net dn radiatif flux at TOA", "W/m2")
     957          CALL histdef2d(iff,clef_stations(iff),o_SWup200%flag,o_SWup200%name, "SWup at 200mb", "W/m2" )
     958          CALL histdef2d(iff,clef_stations(iff),o_SWup200clr%flag,o_SWup200clr%name, "SWup clear sky at 200mb", "W/m2")
     959          CALL histdef2d(iff,clef_stations(iff),o_SWdn200%flag,o_SWdn200%name, "SWdn at 200mb", "W/m2" )
     960          CALL histdef2d(iff,clef_stations(iff),o_SWdn200clr%flag,o_SWdn200clr%name, "SWdn clear sky at 200mb", "W/m2")
     961          CALL histdef2d(iff,clef_stations(iff),o_LWup200%flag,o_LWup200%name, "LWup at 200mb", "W/m2")
     962          CALL histdef2d(iff,clef_stations(iff),o_LWup200clr%flag,o_LWup200clr%name, "LWup clear sky at 200mb", "W/m2")
     963          CALL histdef2d(iff,clef_stations(iff),o_LWdn200%flag,o_LWdn200%name, "LWdn at 200mb", "W/m2")
     964          CALL histdef2d(iff,clef_stations(iff),o_LWdn200clr%flag,o_LWdn200clr%name, "LWdn clear sky at 200mb", "W/m2")
     965          CALL histdef2d(iff,clef_stations(iff),o_sols%flag,o_sols%name, "Solar rad. at surf.", "W/m2")
     966          CALL histdef2d(iff,clef_stations(iff),o_sols0%flag,o_sols0%name, "Solar rad. at surf.", "W/m2")
     967          CALL histdef2d(iff,clef_stations(iff),o_soll%flag,o_soll%name, "IR rad. at surface", "W/m2") 
     968          CALL histdef2d(iff,clef_stations(iff),o_radsol%flag,o_radsol%name, "Rayonnement au sol", "W/m2")
     969          CALL histdef2d(iff,clef_stations(iff),o_soll0%flag,o_soll0%name, "IR rad. at surface", "W/m2")
     970          CALL histdef2d(iff,clef_stations(iff),o_SWupSFC%flag,o_SWupSFC%name, "SWup at surface", "W/m2")
     971          CALL histdef2d(iff,clef_stations(iff),o_SWupSFCclr%flag,o_SWupSFCclr%name, "SWup clear sky at surface", "W/m2")
     972          CALL histdef2d(iff,clef_stations(iff),o_SWdnSFC%flag,o_SWdnSFC%name, "SWdn at surface", "W/m2")
     973          CALL histdef2d(iff,clef_stations(iff),o_SWdnSFCclr%flag,o_SWdnSFCclr%name, "SWdn clear sky at surface", "W/m2")
     974          CALL histdef2d(iff,clef_stations(iff),o_LWupSFC%flag,o_LWupSFC%name, "Upwd. IR rad. at surface", "W/m2")
     975          CALL histdef2d(iff,clef_stations(iff),o_LWdnSFC%flag,o_LWdnSFC%name, "Down. IR rad. at surface", "W/m2")
     976          CALL histdef2d(iff,clef_stations(iff),o_LWupSFCclr%flag,o_LWupSFCclr%name, "CS Upwd. IR rad. at surface", "W/m2")
     977          CALL histdef2d(iff,clef_stations(iff),o_LWdnSFCclr%flag,o_LWdnSFCclr%name, "Down. CS IR rad. at surface", "W/m2")
     978          CALL histdef2d(iff,clef_stations(iff),o_bils%flag,o_bils%name, "Surf. total heat flux", "W/m2")
     979          CALL histdef2d(iff,clef_stations(iff),o_sens%flag,o_sens%name, "Sensible heat flux", "W/m2")
     980          CALL histdef2d(iff,clef_stations(iff),o_fder%flag,o_fder%name, "Heat flux derivation", "W/m2")
     981          CALL histdef2d(iff,clef_stations(iff),o_ffonte%flag,o_ffonte%name, "Thermal flux for snow melting", "W/m2")
     982          CALL histdef2d(iff,clef_stations(iff),o_fqcalving%flag,o_fqcalving%name, "Ice Calving", "kg/m2/s")
     983          CALL histdef2d(iff,clef_stations(iff),o_fqfonte%flag,o_fqfonte%name, "Land ice melt", "kg/m2/s")
     984
     985          CALL histdef2d(iff,clef_stations(iff),o_taux%flag,o_taux%name, "Zonal wind stress","Pa")
     986          CALL histdef2d(iff,clef_stations(iff),o_tauy%flag,o_tauy%name, "Meridional wind stress","Pa")
     987
     988          DO nsrf = 1, nbsrf
     989             CALL histdef2d(iff,clef_stations(iff),o_pourc_srf(nsrf)%flag,o_pourc_srf(nsrf)%name,"% "//clnsurf(nsrf),"%")
     990             CALL histdef2d(iff,clef_stations(iff),o_fract_srf(nsrf)%flag,o_fract_srf(nsrf)%name,"Fraction "//clnsurf(nsrf),"1")
     991             CALL histdef2d(iff,clef_stations(iff), &
     992                  o_taux_srf(nsrf)%flag,o_taux_srf(nsrf)%name,"Zonal wind stress"//clnsurf(nsrf),"Pa")
     993             CALL histdef2d(iff,clef_stations(iff), &
     994                  o_tauy_srf(nsrf)%flag,o_tauy_srf(nsrf)%name,"Meridional wind stress "//clnsurf(nsrf),"Pa")
     995             CALL histdef2d(iff,clef_stations(iff), &
     996                  o_tsol_srf(nsrf)%flag,o_tsol_srf(nsrf)%name,"Temperature "//clnsurf(nsrf),"K")
     997             CALL histdef2d(iff,clef_stations(iff), &
     998                  o_u10m_srf(nsrf)%flag,o_u10m_srf(nsrf)%name,"Vent Zonal 10m "//clnsurf(nsrf),"m/s")
     999             CALL histdef2d(iff,clef_stations(iff), &
     1000                  o_evap_srf(nsrf)%flag,o_evap_srf(nsrf)%name,"evaporation at surface "//clnsurf(nsrf),"kg/(s*m2)")
     1001             CALL histdef2d(iff,clef_stations(iff), &
     1002                  o_v10m_srf(nsrf)%flag,o_v10m_srf(nsrf)%name,"Vent meredien 10m "//clnsurf(nsrf),"m/s")
     1003             CALL histdef2d(iff,clef_stations(iff), &
     1004                  o_t2m_srf(nsrf)%flag,o_t2m_srf(nsrf)%name,"Temp 2m "//clnsurf(nsrf),"K")
     1005             CALL histdef2d(iff,clef_stations(iff), &
     1006                  o_sens_srf(nsrf)%flag,o_sens_srf(nsrf)%name,"Sensible heat flux "//clnsurf(nsrf),"W/m2")
     1007             CALL histdef2d(iff,clef_stations(iff), &
     1008                  o_lat_srf(nsrf)%flag,o_lat_srf(nsrf)%name,"Latent heat flux "//clnsurf(nsrf),"W/m2")
     1009             CALL histdef2d(iff,clef_stations(iff), &
     1010                  o_flw_srf(nsrf)%flag,o_flw_srf(nsrf)%name,"LW "//clnsurf(nsrf),"W/m2")
     1011             CALL histdef2d(iff,clef_stations(iff), &
     1012                  o_fsw_srf(nsrf)%flag,o_fsw_srf(nsrf)%name,"SW "//clnsurf(nsrf),"W/m2")
     1013             CALL histdef2d(iff,clef_stations(iff), &
     1014                  o_wbils_srf(nsrf)%flag,o_wbils_srf(nsrf)%name,"Bilan sol "//clnsurf(nsrf),"W/m2" )
     1015             CALL histdef2d(iff,clef_stations(iff), &
     1016                  o_wbilo_srf(nsrf)%flag,o_wbilo_srf(nsrf)%name,"Bilan eau "//clnsurf(nsrf),"kg/(m2*s)")
     1017             if (iflag_pbl>1 .and. lev_files(iff).gt.10 ) then
     1018                CALL histdef2d(iff,clef_stations(iff), &
     1019                     o_tke_srf(nsrf)%flag,o_tke_srf(nsrf)%name,"Max Turb. Kinetic Energy "//clnsurf(nsrf),"-")
     1020
     1021                IF (.NOT.clef_stations(iff)) THEN
     1022                   !
     1023                   !IM: there is no way to have one single value in a netcdf file
     1024                   !
     1025                   type_ecri(1) = 't_max(X)'
     1026                   type_ecri(2) = 't_max(X)'
     1027                   type_ecri(3) = 't_max(X)'
     1028                   type_ecri(4) = 't_max(X)'
     1029                   type_ecri(5) = 't_max(X)'
     1030                   type_ecri(6) = 't_max(X)'
     1031                   CALL histdef2d(iff,clef_stations(iff), &
     1032                        o_tke_max_srf(nsrf)%flag,o_tke_max_srf(nsrf)%name,"Max Turb. Kinetic Energy "//clnsurf(nsrf),"-")
     1033                   type_ecri(:) = type_ecri_files(:)
     1034                ENDIF
     1035
     1036             endif
     1037
     1038             CALL histdef2d(iff,clef_stations(iff), &
     1039                  o_albe_srf(nsrf)%flag,o_albe_srf(nsrf)%name,"Albedo VIS surf. "//clnsurf(nsrf),"-")
     1040             CALL histdef2d(iff,clef_stations(iff), &
     1041                  o_rugs_srf(nsrf)%flag,o_rugs_srf(nsrf)%name,"Surface roughness "//clnsurf(nsrf),"m")
     1042             CALL histdef2d(iff,clef_stations(iff), &
     1043                  o_ages_srf(nsrf)%flag,o_ages_srf(nsrf)%name,"Snow age", "day")
     1044          END DO
     1045
     1046          IF (new_aod .AND. (.NOT. aerosol_couple)) THEN
     1047             IF (ok_ade.OR.ok_aie) THEN
     1048
     1049                CALL histdef2d(iff,clef_stations(iff), &
     1050                     o_od550aer%flag,o_od550aer%name, "Total aerosol optical depth at 550nm", "-")
     1051                CALL histdef2d(iff,clef_stations(iff), &
     1052                     o_od865aer%flag,o_od865aer%name, "Total aerosol optical depth at 870nm", "-")
     1053                CALL histdef2d(iff,clef_stations(iff), &
     1054                     o_absvisaer%flag,o_absvisaer%name, "Absorption aerosol visible optical depth", "-")
     1055                CALL histdef2d(iff,clef_stations(iff), &
     1056                     o_od550lt1aer%flag,o_od550lt1aer%name, "Fine mode optical depth", "-")
     1057
     1058
     1059                CALL histdef2d(iff,clef_stations(iff), &
     1060                     o_sconcso4%flag,o_sconcso4%name,"Surface Concentration of Sulfate ","kg/m3")
     1061                CALL histdef2d(iff,clef_stations(iff), &
     1062                     o_sconcoa%flag,o_sconcoa%name,"Surface Concentration of Organic Aerosol ","kg/m3")
     1063                CALL histdef2d(iff,clef_stations(iff), &
     1064                     o_sconcbc%flag,o_sconcbc%name,"Surface Concentration of Black Carbon ","kg/m3")
     1065                CALL histdef2d(iff,clef_stations(iff), &
     1066                     o_sconcss%flag,o_sconcss%name,"Surface Concentration of Sea Salt ","kg/m3")
     1067                CALL histdef2d(iff,clef_stations(iff), &
     1068                     o_sconcdust%flag,o_sconcdust%name,"Surface Concentration of Dust ","kg/m3")
     1069                CALL histdef3d(iff,clef_stations(iff), &
     1070                     o_concso4%flag,o_concso4%name,"Concentration of Sulfate ","kg/m3")
     1071                CALL histdef3d(iff,clef_stations(iff), &
     1072                     o_concoa%flag,o_concoa%name,"Concentration of Organic Aerosol ","kg/m3")
     1073                CALL histdef3d(iff,clef_stations(iff), &
     1074                     o_concbc%flag,o_concbc%name,"Concentration of Black Carbon ","kg/m3")
     1075                CALL histdef3d(iff,clef_stations(iff), &
     1076                     o_concss%flag,o_concss%name,"Concentration of Sea Salt ","kg/m3")
     1077                CALL histdef3d(iff,clef_stations(iff), &
     1078                     o_concdust%flag,o_concdust%name,"Concentration of Dust ","kg/m3")
     1079                CALL histdef2d(iff,clef_stations(iff), &
     1080                     o_loadso4%flag,o_loadso4%name,"Column Load of Sulfate ","kg/m2")
     1081                CALL histdef2d(iff,clef_stations(iff), &
     1082                     o_loadoa%flag,o_loadoa%name,"Column Load of Organic Aerosol ","kg/m2")
     1083                CALL histdef2d(iff,clef_stations(iff), &
     1084                     o_loadbc%flag,o_loadbc%name,"Column Load of Black Carbon ","kg/m2")
     1085                CALL histdef2d(iff,clef_stations(iff), &
     1086                     o_loadss%flag,o_loadss%name,"Column Load of Sea Salt ","kg/m2")
     1087                CALL histdef2d(iff,clef_stations(iff), &
     1088                     o_loaddust%flag,o_loaddust%name,"Column Load of Dust ","kg/m2")
     1089
     1090                DO naero = 1, naero_spc
     1091                   CALL histdef2d(iff,clef_stations(iff), &
     1092                        o_tausumaero(naero)%flag,o_tausumaero(naero)%name,"Aerosol Optical depth at 550 nm "//name_aero(naero),"1")
     1093                END DO
     1094             ENDIF
     1095          ENDIF
     1096
     1097          IF (ok_ade) THEN
     1098             CALL histdef2d(iff,clef_stations(iff), &
     1099                  o_topswad%flag,o_topswad%name, "ADE at TOA", "W/m2")
     1100             CALL histdef2d(iff,clef_stations(iff), &
     1101                  o_solswad%flag,o_solswad%name, "ADE at SRF", "W/m2")
     1102
     1103             CALL histdef2d(iff,clef_stations(iff), &
     1104                  o_swtoaas_nat%flag,o_swtoaas_nat%name, "Natural aerosol radiative forcing all-sky at TOA", "W/m2")
     1105             CALL histdef2d(iff,clef_stations(iff), &
     1106                  o_swsrfas_nat%flag,o_swsrfas_nat%name, "Natural aerosol radiative forcing all-sky at SRF", "W/m2")
     1107             CALL histdef2d(iff,clef_stations(iff), &
     1108                  o_swtoacs_nat%flag,o_swtoacs_nat%name, "Natural aerosol radiative forcing clear-sky at TOA", "W/m2")
     1109             CALL histdef2d(iff,clef_stations(iff), &
     1110                  o_swsrfcs_nat%flag,o_swsrfcs_nat%name, "Natural aerosol radiative forcing clear-sky at SRF", "W/m2")
     1111
     1112             CALL histdef2d(iff,clef_stations(iff), &
     1113                  o_swtoaas_ant%flag,o_swtoaas_ant%name, "Anthropogenic aerosol radiative forcing all-sky at TOA", "W/m2")
     1114             CALL histdef2d(iff,clef_stations(iff), &
     1115                  o_swsrfas_ant%flag,o_swsrfas_ant%name, "Anthropogenic aerosol radiative forcing all-sky at SRF", "W/m2")
     1116             CALL histdef2d(iff,clef_stations(iff), &
     1117                  o_swtoacs_ant%flag,o_swtoacs_ant%name, "Anthropogenic aerosol radiative forcing clear-sky at TOA", "W/m2")
     1118             CALL histdef2d(iff,clef_stations(iff), &
     1119                  o_swsrfcs_ant%flag,o_swsrfcs_ant%name, "Anthropogenic aerosol radiative forcing clear-sky at SRF", "W/m2")
     1120
     1121             IF (.NOT. aerosol_couple) THEN
     1122                CALL histdef2d(iff,clef_stations(iff), &
     1123                     o_swtoacf_nat%flag,o_swtoacf_nat%name, "Natural aerosol impact on cloud radiative forcing at TOA", "W/m2")
     1124                CALL histdef2d(iff,clef_stations(iff), &
     1125                     o_swsrfcf_nat%flag,o_swsrfcf_nat%name, "Natural aerosol impact on cloud radiative forcing  at SRF", "W/m2")
     1126                CALL histdef2d(iff, clef_stations(iff), o_swtoacf_ant%flag, &
     1127                     o_swtoacf_ant%name, &
     1128                     "Anthropogenic aerosol impact on cloud radiative forcing at TOA", &
     1129                     "W/m2")
     1130                CALL histdef2d(iff, clef_stations(iff), o_swsrfcf_ant%flag, &
     1131                     o_swsrfcf_ant%name, &
     1132                     "Anthropogenic aerosol impact on cloud radiative forcing at SRF", &
     1133                     "W/m2")
     1134                CALL histdef2d(iff,clef_stations(iff), &
     1135                     o_swtoacf_zero%flag,o_swtoacf_zero%name, "Cloud radiative forcing (allsky-clearsky fluxes) at TOA", "W/m2")
     1136                CALL histdef2d(iff,clef_stations(iff), &
     1137                     o_swsrfcf_zero%flag,o_swsrfcf_zero%name, "Cloud radiative forcing (allsky-clearsky fluxes) at SRF", "W/m2")
     1138             ENDIF
     1139          ENDIF
     1140
     1141          IF (ok_aie) THEN
     1142             CALL histdef2d(iff,clef_stations(iff), &
     1143                  o_topswai%flag,o_topswai%name, "AIE at TOA", "W/m2")
     1144             CALL histdef2d(iff,clef_stations(iff), &
     1145                  o_solswai%flag,o_solswai%name, "AIE at SFR", "W/m2")
     1146             !Cloud droplet number concentration
     1147             CALL histdef3d(iff,clef_stations(iff), &
     1148                  o_scdnc%flag,o_scdnc%name, "Cloud droplet number concentration","m-3")
     1149             CALL histdef2d(iff,clef_stations(iff), &
     1150                  o_cldncl%flag,o_cldncl%name, "CDNC at top of liquid water cloud", "m-3")
     1151             CALL histdef3d(iff,clef_stations(iff), &
     1152                  o_reffclws%flag,o_reffclws%name, "Stratiform Cloud Droplet Effective Radius (aerosol diags.)","m")
     1153             CALL histdef3d(iff,clef_stations(iff), &
     1154                  o_reffclwc%flag,o_reffclwc%name, "Convective Cloud Droplet Effective Radius (aerosol diags.)","m")
     1155             CALL histdef2d(iff,clef_stations(iff), &
     1156                  o_cldnvi%flag,o_cldnvi%name, "Column Integrated Cloud Droplet Number", "m-2")
     1157             CALL histdef3d(iff,clef_stations(iff), &
     1158                  o_lcc3d%flag,o_lcc3d%name, "Cloud liquid fraction","1")
     1159             CALL histdef3d(iff,clef_stations(iff), &
     1160                  o_lcc3dcon%flag,o_lcc3dcon%name, "Convective cloud liquid fraction","1")
     1161             CALL histdef3d(iff,clef_stations(iff), &
     1162                  o_lcc3dstra%flag,o_lcc3dstra%name, "Stratiform cloud liquid fraction","1")
     1163             CALL histdef2d(iff,clef_stations(iff), &
     1164                  o_lcc%flag,o_lcc%name, "Cloud liquid fraction at top of cloud","1")
     1165             CALL histdef2d(iff,clef_stations(iff), &
     1166                  o_reffclwtop%flag,o_reffclwtop%name, "Droplet effective radius at top of liquid water cloud", "m")
     1167          ENDIF
     1168
     1169
     1170          CALL histdef2d(iff,clef_stations(iff), &
     1171               o_alb1%flag,o_alb1%name, "Surface VIS albedo", "-")
     1172          CALL histdef2d(iff,clef_stations(iff), &
     1173               o_alb2%flag,o_alb2%name, "Surface Near IR albedo", "-")
     1174          CALL histdef2d(iff,clef_stations(iff), &
     1175               o_cdrm%flag,o_cdrm%name, "Momentum drag coef.", "-")
     1176          CALL histdef2d(iff,clef_stations(iff), &
     1177               o_cdrh%flag,o_cdrh%name, "Heat drag coef.", "-" )
     1178          CALL histdef2d(iff,clef_stations(iff), &
     1179               o_cldl%flag,o_cldl%name, "Low-level cloudiness", "-")
     1180          CALL histdef2d(iff,clef_stations(iff), &
     1181               o_cldm%flag,o_cldm%name, "Mid-level cloudiness", "-")
     1182          CALL histdef2d(iff,clef_stations(iff), &
     1183               o_cldh%flag,o_cldh%name, "High-level cloudiness", "-")
     1184          CALL histdef2d(iff,clef_stations(iff), &
     1185               o_cldt%flag,o_cldt%name, "Total cloudiness", "-")
     1186          CALL histdef2d(iff,clef_stations(iff), &
     1187               o_cldq%flag,o_cldq%name, "Cloud liquid water path", "kg/m2")
     1188          CALL histdef2d(iff,clef_stations(iff), &
     1189               o_lwp%flag,o_lwp%name, "Cloud water path", "kg/m2")
     1190          CALL histdef2d(iff,clef_stations(iff), &
     1191               o_iwp%flag,o_iwp%name, "Cloud ice water path", "kg/m2" )
     1192          CALL histdef2d(iff,clef_stations(iff), &
     1193               o_ue%flag,o_ue%name, "Zonal energy transport", "-")
     1194          CALL histdef2d(iff,clef_stations(iff), &
     1195               o_ve%flag,o_ve%name, "Merid energy transport", "-")
     1196          CALL histdef2d(iff,clef_stations(iff), &
     1197               o_uq%flag,o_uq%name, "Zonal humidity transport", "-")
     1198          CALL histdef2d(iff,clef_stations(iff), &
     1199               o_vq%flag,o_vq%name, "Merid humidity transport", "-")
     1200
     1201          IF(iflag_con.GE.3) THEN ! sb
     1202             CALL histdef2d(iff,clef_stations(iff), &
     1203                  o_cape%flag,o_cape%name, "Conv avlbl pot ener", "J/kg")
     1204             CALL histdef2d(iff,clef_stations(iff), &
     1205                  o_pbase%flag,o_pbase%name, "Cld base pressure", "Pa")
     1206             CALL histdef2d(iff,clef_stations(iff), &
     1207                  o_ptop%flag,o_ptop%name, "Cld top pressure", "Pa")
     1208             CALL histdef2d(iff,clef_stations(iff), &
     1209                  o_fbase%flag,o_fbase%name, "Cld base mass flux", "kg/m2/s")
     1210             if (iflag_con /= 30) then
     1211                CALL histdef2d(iff,clef_stations(iff), &
     1212                     o_plcl%flag,o_plcl%name, "Lifting Condensation Level", "hPa")
     1213                CALL histdef2d(iff,clef_stations(iff), &
     1214                     o_plfc%flag,o_plfc%name, "Level of Free Convection", "hPa")
     1215                CALL histdef2d(iff,clef_stations(iff), &
     1216                     o_wbeff%flag,o_wbeff%name, "Conv. updraft velocity at LFC (<100)", "m/s")
     1217             end if
     1218             CALL histdef2d(iff,clef_stations(iff), &
     1219                  o_prw%flag,o_prw%name, "Precipitable water", "kg/m2")
     1220             IF (.NOT.clef_stations(iff)) THEN
     1221                !
     1222                !IM: there is no way to have one single value in a netcdf file
     1223                !
     1224                type_ecri(1) = 't_max(X)'
     1225                type_ecri(2) = 't_max(X)'
     1226                type_ecri(3) = 't_max(X)'
     1227                type_ecri(4) = 't_max(X)'
     1228                type_ecri(5) = 't_max(X)'
     1229                type_ecri(6) = 't_max(X)'
     1230                CALL histdef2d(iff,clef_stations(iff), &
     1231                     o_cape_max%flag,o_cape_max%name, "CAPE max.", "J/kg")
     1232             ENDIF
     1233             type_ecri(:) = type_ecri_files(:)
     1234             CALL histdef3d(iff,clef_stations(iff), &
     1235                  o_upwd%flag,o_upwd%name, "saturated updraft", "kg/m2/s")
     1236             CALL histdef3d(iff,clef_stations(iff), &
     1237                  o_Ma%flag,o_Ma%name, "undilute adiab updraft", "kg/m2/s")
     1238             CALL histdef3d(iff,clef_stations(iff), &
     1239                  o_dnwd%flag,o_dnwd%name, "saturated downdraft", "kg/m2/s")
     1240             CALL histdef3d(iff,clef_stations(iff), &
     1241                  o_dnwd0%flag,o_dnwd0%name, "unsat. downdraft", "kg/m2/s")
     1242             CALL histdef3d(iff,clef_stations(iff), &
     1243                  o_mc%flag,o_mc%name, "Convective mass flux", "kg/m2/s")
     1244             type_ecri(1) = 'inst(X)'
     1245             type_ecri(2) = 'inst(X)'
     1246             type_ecri(3) = 'inst(X)'
     1247             type_ecri(4) = 'inst(X)'
     1248             type_ecri(5) = 'inst(X)'
     1249             type_ecri(6) = 'inst(X)'
     1250             CALL histdef2d(iff,clef_stations(iff), &
     1251                  o_ftime_con%flag,o_ftime_con%name, "Fraction of time convection Occurs", " ")
     1252             type_ecri(:) = type_ecri_files(:)
     1253          ENDIF !iflag_con .GE. 3
     1254
     1255          CALL histdef2d(iff,clef_stations(iff), &
     1256               o_s_pblh%flag,o_s_pblh%name, "Boundary Layer Height", "m")
     1257          CALL histdef2d(iff,clef_stations(iff), &
     1258               o_s_pblt%flag,o_s_pblt%name, "t at Boundary Layer Height", "K")
     1259          CALL histdef2d(iff,clef_stations(iff), &
     1260               o_s_lcl%flag,o_s_lcl%name, "Condensation level", "m")
     1261          CALL histdef2d(iff,clef_stations(iff), &
     1262               o_s_therm%flag,o_s_therm%name, "Exces du thermique", "K")
     1263          !IM : Les champs suivants (s_oliqCL, s_cteiCL, s_trmb1, s_trmb2, s_trmb3) ne sont pas definis dans HBTM.F
     1264          !CALL histdef2d(iff,clef_stations(iff), &
     1265          !o_s_capCL%flag,o_s_capCL%name, "Conv avlbl pot enerfor ABL", "J/m2" )
     1266          !CALL histdef2d(iff,clef_stations(iff), &
     1267          !o_s_oliqCL%flag,o_s_oliqCL%name, "Liq Water in BL", "kg/m2")
     1268          !CALL histdef2d(iff,clef_stations(iff), &
     1269          !o_s_cteiCL%flag,o_s_cteiCL%name, "Instability criteria(ABL)", "K")
     1270          !CALL histdef2d(iff,clef_stations(iff), &
     1271          !o_s_trmb1%flag,o_s_trmb1%name, "deep_cape(HBTM2)", "J/m2")
     1272          !CALL histdef2d(iff,clef_stations(iff), &
     1273          !o_s_trmb2%flag,o_s_trmb2%name, "inhibition (HBTM2)", "J/m2")
     1274          !CALL histdef2d(iff,clef_stations(iff), &
     1275          !o_s_trmb3%flag,o_s_trmb3%name, "Point Omega (HBTM2)", "m")
     1276
     1277          ! Champs interpolles sur des niveaux de pression
     1278
     1279          type_ecri(1) = 'inst(X)'
     1280          type_ecri(2) = 'inst(X)'
     1281          type_ecri(3) = 'inst(X)'
     1282          type_ecri(4) = 'inst(X)'
     1283          type_ecri(5) = 'inst(X)'
     1284          type_ecri(6) = 'inst(X)'
     1285
     1286          ! Attention a reverifier
     1287
     1288          ilev=0       
     1289          DO k=1, nlevSTD
     1290             bb2=clevSTD(k)
     1291             IF(bb2.EQ."850".OR.bb2.EQ."700".OR.bb2.EQ."500".OR.bb2.EQ."200" &
     1292                  .OR.bb2.EQ."100".OR.bb2.EQ."50".OR.bb2.EQ."10")THEN
     1293                ilev=ilev+1
     1294                !     print*,'ilev k bb2 flag name ',ilev,k, bb2,o_uSTDlevs(ilev)%flag,o_uSTDlevs(ilev)%name
     1295                CALL histdef2d(iff,clef_stations(iff), &
     1296                     o_uSTDlevs(ilev)%flag,o_uSTDlevs(ilev)%name,"Zonal wind "//bb2//"hPa", "m/s")
     1297                CALL histdef2d(iff,clef_stations(iff), &
     1298                     o_vSTDlevs(ilev)%flag,o_vSTDlevs(ilev)%name,"Meridional wind "//bb2//"hPa", "m/s")
     1299                CALL histdef2d(iff,clef_stations(iff), &
     1300                     o_wSTDlevs(ilev)%flag,o_wSTDlevs(ilev)%name,"Vertical wind "//bb2//"hPa", "Pa/s")
     1301                CALL histdef2d(iff,clef_stations(iff), &
     1302                     o_zSTDlevs(ilev)%flag,o_zSTDlevs(ilev)%name,"Geopotential height "//bb2//"hPa", "m")
     1303                CALL histdef2d(iff,clef_stations(iff), &
     1304                     o_qSTDlevs(ilev)%flag,o_qSTDlevs(ilev)%name,"Specific humidity "//bb2//"hPa", "kg/kg" )
     1305                CALL histdef2d(iff,clef_stations(iff), &
     1306                     o_tSTDlevs(ilev)%flag,o_tSTDlevs(ilev)%name,"Temperature "//bb2//"hPa", "K")
     1307             ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR."500".OR.bb2.EQ."200".OR.bb2.EQ."50".OR.bb2.EQ."10")
     1308          ENDDO
     1309          type_ecri(:) = type_ecri_files(:)
     1310
     1311          CALL histdef2d(iff,clef_stations(iff), &
     1312               o_t_oce_sic%flag,o_t_oce_sic%name, "Temp mixte oce-sic", "K")
     1313
     1314          IF (type_ocean=='slab') &
     1315               CALL histdef2d(iff,clef_stations(iff), &
     1316               o_slab_bils%flag, o_slab_bils%name,"Bilan au sol sur ocean slab", "W/m2")
     1317
     1318          ! Couplage conv-CL
     1319          IF (iflag_con.GE.3) THEN
     1320             IF (iflag_coupl>=1) THEN
     1321                CALL histdef2d(iff,clef_stations(iff), &
     1322                     o_ale_bl%flag,o_ale_bl%name, "ALE BL", "m2/s2")
     1323                CALL histdef2d(iff,clef_stations(iff), &
     1324                     o_alp_bl%flag,o_alp_bl%name, "ALP BL", "m2/s2")
     1325             ENDIF
     1326          ENDIF !(iflag_con.GE.3)
     1327
     1328          CALL histdef2d(iff,clef_stations(iff), &
     1329               o_weakinv%flag,o_weakinv%name, "Weak inversion", "-")
     1330          CALL histdef2d(iff,clef_stations(iff), &
     1331               o_dthmin%flag,o_dthmin%name, "dTheta mini", "K/m")
     1332          CALL histdef2d(iff,clef_stations(iff), &
     1333               o_rh2m%flag,o_rh2m%name, "Relative humidity at 2m", "%" )
     1334
     1335          IF (.NOT.clef_stations(iff)) THEN
     1336             !
     1337             !IM: there is no way to have one single value in a netcdf file
     1338             !
     1339             type_ecri(1) = 't_min(X)'
     1340             type_ecri(2) = 't_min(X)'
     1341             type_ecri(3) = 't_min(X)'
     1342             type_ecri(4) = 't_min(X)'
     1343             type_ecri(5) = 't_min(X)'
     1344             type_ecri(6) = 't_min(X)'
     1345             CALL histdef2d(iff,clef_stations(iff),o_rh2m_min%flag,o_rh2m_min%name, "Min Relative humidity at 2m", "%" )
     1346             type_ecri(1) = 't_max(X)'
     1347             type_ecri(2) = 't_max(X)'
     1348             type_ecri(3) = 't_max(X)'
     1349             type_ecri(4) = 't_max(X)'
     1350             type_ecri(5) = 't_max(X)'
     1351             type_ecri(6) = 't_max(X)'
     1352             CALL histdef2d(iff,clef_stations(iff),o_rh2m_max%flag,o_rh2m_max%name, "Max Relative humidity at 2m", "%" )
     1353          ENDIF
     1354
     1355          type_ecri(:) = type_ecri_files(:)
     1356          CALL histdef2d(iff,clef_stations(iff),o_qsat2m%flag,o_qsat2m%name, "Saturant humidity at 2m", "%")
     1357          CALL histdef2d(iff,clef_stations(iff),o_tpot%flag,o_tpot%name, "Surface air potential temperature", "K")
     1358          CALL histdef2d(iff,clef_stations(iff), &
     1359               o_tpote%flag,o_tpote%name, "Surface air equivalent potential temperature", "K")
     1360          CALL histdef2d(iff,clef_stations(iff),o_SWnetOR%flag,o_SWnetOR%name, "Sfce net SW radiation OR", "W/m2")
     1361          CALL histdef2d(iff,clef_stations(iff),o_SWdownOR%flag,o_SWdownOR%name, "Sfce incident SW radiation OR", "W/m2")
     1362          CALL histdef2d(iff,clef_stations(iff),o_LWdownOR%flag,o_LWdownOR%name, "Sfce incident LW radiation OR", "W/m2")
     1363          CALL histdef2d(iff,clef_stations(iff),o_snowl%flag,o_snowl%name, "Solid Large-scale Precip.", "kg/(m2*s)")
     1364
     1365          CALL histdef2d(iff,clef_stations(iff),o_solldown%flag,o_solldown%name, "Down. IR rad. at surface", "W/m2")
     1366          CALL histdef2d(iff,clef_stations(iff),o_dtsvdfo%flag,o_dtsvdfo%name, "Boundary-layer dTs(o)", "K/s")
     1367          CALL histdef2d(iff,clef_stations(iff),o_dtsvdft%flag,o_dtsvdft%name, "Boundary-layer dTs(t)", "K/s")
     1368          CALL histdef2d(iff,clef_stations(iff),o_dtsvdfg%flag,o_dtsvdfg%name, "Boundary-layer dTs(g)", "K/s")
     1369          CALL histdef2d(iff,clef_stations(iff),o_dtsvdfi%flag,o_dtsvdfi%name, "Boundary-layer dTs(g)", "K/s")
     1370          CALL histdef2d(iff,clef_stations(iff),o_rugs%flag,o_rugs%name, "rugosity", "-" )
     1371
     1372          ! Champs 3D:
     1373          CALL histdef3d(iff,clef_stations(iff),o_ec550aer%flag,o_ec550aer%name, "Extinction at 550nm", "m^-1")
     1374          CALL histdef3d(iff,clef_stations(iff),o_lwcon%flag,o_lwcon%name, "Cloud liquid water content", "kg/kg")
     1375          CALL histdef3d(iff,clef_stations(iff),o_iwcon%flag,o_iwcon%name, "Cloud ice water content", "kg/kg")
     1376          CALL histdef3d(iff,clef_stations(iff),o_temp%flag,o_temp%name, "Air temperature", "K" )
     1377          CALL histdef3d(iff,clef_stations(iff),o_theta%flag,o_theta%name, "Potential air temperature", "K" )
     1378          CALL histdef3d(iff,clef_stations(iff),o_ovap%flag,o_ovap%name, "Specific humidity", "kg/kg" )
     1379          CALL histdef3d(iff,clef_stations(iff), &
     1380               o_ovapinit%flag,o_ovapinit%name, "Specific humidity (begin of timestep)", "kg/kg" )
     1381          CALL histdef3d(iff,clef_stations(iff), &
     1382               o_geop%flag,o_geop%name, "Geopotential height", "m2/s2")
     1383          CALL histdef3d(iff,clef_stations(iff), &
     1384               o_vitu%flag,o_vitu%name, "Zonal wind", "m/s" )
     1385          CALL histdef3d(iff,clef_stations(iff), &
     1386               o_vitv%flag,o_vitv%name, "Meridional wind", "m/s" )
     1387          CALL histdef3d(iff,clef_stations(iff), &
     1388               o_vitw%flag,o_vitw%name, "Vertical wind", "Pa/s" )
     1389          CALL histdef3d(iff,clef_stations(iff), &
     1390               o_pres%flag,o_pres%name, "Air pressure", "Pa" )
     1391          CALL histdef3d(iff,clef_stations(iff), &
     1392               o_paprs%flag,o_paprs%name, "Air pressure Inter-Couches", "Pa" )
     1393          CALL histdef3d(iff,clef_stations(iff), &
     1394               o_mass%flag,o_mass%name, "Masse Couches", "kg/m2" )
     1395          CALL histdef3d(iff,clef_stations(iff), &
     1396               o_zfull%flag,o_zfull%name, "Altitude of full pressure levels", "m" )
     1397          CALL histdef3d(iff,clef_stations(iff), &
     1398               o_zhalf%flag,o_zhalf%name, "Altitude of half pressure levels", "m" )
     1399          CALL histdef3d(iff,clef_stations(iff), &
     1400               o_rneb%flag,o_rneb%name, "Cloud fraction", "-")
     1401          CALL histdef3d(iff,clef_stations(iff), &
     1402               o_rnebcon%flag,o_rnebcon%name, "Convective Cloud Fraction", "-")
     1403          CALL histdef3d(iff,clef_stations(iff), &
     1404               o_rhum%flag,o_rhum%name, "Relative humidity", "-")
     1405          CALL histdef3d(iff,clef_stations(iff), &
     1406               o_ozone%flag,o_ozone%name, "Ozone mole fraction", "-")
     1407          if (read_climoz == 2) &
     1408               CALL histdef3d(iff,clef_stations(iff), &
     1409               o_ozone_light%flag,o_ozone_light%name, &
     1410               "Daylight ozone mole fraction", "-")
     1411          CALL histdef3d(iff,clef_stations(iff), &
     1412               o_dtphy%flag,o_dtphy%name, "Physics dT", "K/s")
     1413          CALL histdef3d(iff,clef_stations(iff), &
     1414               o_dqphy%flag,o_dqphy%name, "Physics dQ", "(kg/kg)/s")
     1415          CALL histdef3d(iff,clef_stations(iff), &
     1416               o_cldtau%flag,o_cldtau%name, "Cloud optical thickness", "1")
     1417          CALL histdef3d(iff,clef_stations(iff), &
     1418               o_cldemi%flag,o_cldemi%name, "Cloud optical emissivity", "1")
     1419          !IM: bug ?? dimensionnement variables (klon,klev+1) pmflxr, pmflxs, prfl, psfl
     1420          CALL histdef3d(iff,clef_stations(iff), &
     1421               o_pr_con_l%flag,o_pr_con_l%name, "Convective precipitation lic", " ")
     1422          CALL histdef3d(iff,clef_stations(iff), &
     1423               o_pr_con_i%flag,o_pr_con_i%name, "Convective precipitation ice", " ")
     1424          CALL histdef3d(iff,clef_stations(iff), &
     1425               o_pr_lsc_l%flag,o_pr_lsc_l%name, "Large scale precipitation lic", " ")
     1426          CALL histdef3d(iff,clef_stations(iff), &
     1427               o_pr_lsc_i%flag,o_pr_lsc_i%name, "Large scale precipitation ice", " ")
     1428          !Cloud droplet effective radius
     1429          CALL histdef3d(iff,clef_stations(iff), &
     1430               o_re%flag,o_re%name, "Cloud droplet effective radius","um")
     1431          CALL histdef3d(iff,clef_stations(iff), &
     1432               o_fl%flag,o_fl%name, "Denominator of Cloud droplet effective radius"," ")
     1433          !FH Sorties pour la couche limite
     1434          if (iflag_pbl>1) then
     1435             CALL histdef3d(iff,clef_stations(iff), &
     1436                  o_tke%flag,o_tke%name, "TKE", "m2/s2")
     1437             IF (.NOT.clef_stations(iff)) THEN
     1438                !
     1439                !IM: there is no way to have one single value in a netcdf file
     1440                !
     1441                type_ecri(1) = 't_max(X)'
     1442                type_ecri(2) = 't_max(X)'
     1443                type_ecri(3) = 't_max(X)'
     1444                type_ecri(4) = 't_max(X)'
     1445                type_ecri(5) = 't_max(X)'
     1446                type_ecri(6) = 't_max(X)'
     1447                CALL histdef3d(iff,clef_stations(iff), &
     1448                     o_tke_max%flag,o_tke_max%name, "TKE max", "m2/s2")
     1449             ENDIF
     1450             type_ecri(:) = type_ecri_files(:)
     1451          endif
     1452
     1453          CALL histdef3d(iff,clef_stations(iff), &
     1454               o_kz%flag,o_kz%name, "Kz melange", "m2/s")
     1455          IF (.NOT.clef_stations(iff)) THEN
     1456             !
     1457             !IM: there is no way to have one single value in a netcdf file
     1458             !
     1459             type_ecri(1) = 't_max(X)'
     1460             type_ecri(2) = 't_max(X)'
     1461             type_ecri(3) = 't_max(X)'
     1462             type_ecri(4) = 't_max(X)'
     1463             type_ecri(5) = 't_max(X)'
     1464             type_ecri(6) = 't_max(X)'
     1465             CALL histdef3d(iff,clef_stations(iff), &
     1466                  o_kz_max%flag,o_kz_max%name, "Kz melange max", "m2/s" )
     1467          ENDIF
     1468          type_ecri(:) = type_ecri_files(:)
     1469          CALL histdef3d(iff,clef_stations(iff), &
     1470               o_clwcon%flag,o_clwcon%name, "Convective Cloud Liquid water content", "kg/kg")
     1471          CALL histdef3d(iff,clef_stations(iff), &
     1472               o_dtdyn%flag,o_dtdyn%name, "Dynamics dT", "K/s")
     1473          CALL histdef3d(iff,clef_stations(iff), &
     1474               o_dqdyn%flag,o_dqdyn%name, "Dynamics dQ", "(kg/kg)/s")
     1475          CALL histdef3d(iff,clef_stations(iff), &
     1476               o_dudyn%flag,o_dudyn%name, "Dynamics dU", "m/s2")
     1477          CALL histdef3d(iff,clef_stations(iff), &
     1478               o_dvdyn%flag,o_dvdyn%name, "Dynamics dV", "m/s2")
     1479          CALL histdef3d(iff,clef_stations(iff), &
     1480               o_dtcon%flag,o_dtcon%name, "Convection dT", "K/s")
     1481          CALL histdef3d(iff,clef_stations(iff), &
     1482               o_ducon%flag,o_ducon%name, "Convection du", "m/s2")
     1483          CALL histdef3d(iff,clef_stations(iff), &
     1484               o_dqcon%flag,o_dqcon%name, "Convection dQ", "(kg/kg)/s")
     1485
     1486          ! Wakes
     1487          IF(iflag_con.EQ.3) THEN
     1488             IF (iflag_wake >= 1) THEN
     1489                CALL histdef2d(iff,clef_stations(iff), &
     1490                     o_ale_wk%flag,o_ale_wk%name, "ALE WK", "m2/s2")
     1491                CALL histdef2d(iff,clef_stations(iff), &
     1492                     o_alp_wk%flag,o_alp_wk%name, "ALP WK", "m2/s2")
     1493                CALL histdef2d(iff,clef_stations(iff), &
     1494                     o_ale%flag,o_ale%name, "ALE", "m2/s2")
     1495                CALL histdef2d(iff,clef_stations(iff), &
     1496                     o_alp%flag,o_alp%name, "ALP", "W/m2")
     1497                CALL histdef2d(iff,clef_stations(iff),o_cin%flag,o_cin%name, "Convective INhibition", "m2/s2")
     1498                CALL histdef2d(iff,clef_stations(iff),o_wape%flag,o_WAPE%name, "WAPE", "m2/s2")
     1499                CALL histdef2d(iff,clef_stations(iff),o_wake_h%flag,o_wake_h%name, "wake_h", "-")
     1500                CALL histdef2d(iff,clef_stations(iff),o_wake_s%flag,o_wake_s%name, "wake_s", "-")
     1501                CALL histdef3d(iff,clef_stations(iff),o_dtwak%flag,o_dtwak%name, "Wake dT", "K/s")
     1502                CALL histdef3d(iff,clef_stations(iff),o_dqwak%flag,o_dqwak%name, "Wake dQ", "(kg/kg)/s")
     1503                CALL histdef3d(iff,clef_stations(iff),o_wake_deltat%flag,o_wake_deltat%name, "wake_deltat", " ")
     1504                CALL histdef3d(iff,clef_stations(iff),o_wake_deltaq%flag,o_wake_deltaq%name, "wake_deltaq", " ")
     1505                CALL histdef3d(iff,clef_stations(iff),o_wake_omg%flag,o_wake_omg%name, "wake_omg", " ")
     1506             ENDIF
     1507             CALL histdef3d(iff,clef_stations(iff),o_Vprecip%flag,o_Vprecip%name, "precipitation vertical profile", "-")
     1508             CALL histdef3d(iff,clef_stations(iff),o_ftd%flag,o_ftd%name, "tend temp due aux descentes precip", "-")
     1509             CALL histdef3d(iff,clef_stations(iff),o_fqd%flag,o_fqd%name,"tend vap eau due aux descentes precip", "-")
     1510          ENDIF !(iflag_con.EQ.3)
     1511
     1512          CALL histdef3d(iff,clef_stations(iff),o_dtlsc%flag,o_dtlsc%name, "Condensation dT", "K/s")
     1513          CALL histdef3d(iff,clef_stations(iff),o_dtlschr%flag,o_dtlschr%name,"Large-scale condensational heating rate","K/s")
     1514          CALL histdef3d(iff,clef_stations(iff),o_dqlsc%flag,o_dqlsc%name, "Condensation dQ", "(kg/kg)/s")
     1515          CALL histdef3d(iff,clef_stations(iff),o_dtvdf%flag,o_dtvdf%name, "Boundary-layer dT", "K/s")
     1516          CALL histdef3d(iff,clef_stations(iff),o_dqvdf%flag,o_dqvdf%name, "Boundary-layer dQ", "(kg/kg)/s")
     1517          CALL histdef3d(iff,clef_stations(iff),o_dteva%flag,o_dteva%name, "Reevaporation dT", "K/s")
     1518          CALL histdef3d(iff,clef_stations(iff),o_dqeva%flag,o_dqeva%name, "Reevaporation dQ", "(kg/kg)/s")
     1519          CALL histdef3d(iff,clef_stations(iff),o_ptconv%flag,o_ptconv%name, "POINTS CONVECTIFS", " ")
     1520          CALL histdef3d(iff,clef_stations(iff),o_ratqs%flag,o_ratqs%name, "RATQS", " ")
     1521          CALL histdef3d(iff,clef_stations(iff),o_dtthe%flag,o_dtthe%name, "Thermal dT", "K/s")
     1522
     1523          if(iflag_thermals.gt.1) THEN
     1524             CALL histdef3d(iff,clef_stations(iff),o_dqlscth%flag,o_dqlscth%name, "dQ therm.", "(kg/kg)/s")
     1525             CALL histdef3d(iff,clef_stations(iff),o_dqlscst%flag,o_dqlscst%name, "dQ strat.", "(kg/kg)/s")
     1526             CALL histdef3d(iff,clef_stations(iff),o_dtlscth%flag,o_dtlscth%name, "dQ therm.", "K/s")
     1527             CALL histdef3d(iff,clef_stations(iff),o_dtlscst%flag,o_dtlscst%name, "dQ strat.", "K/s")
     1528             CALL histdef2d(iff,clef_stations(iff),o_plulth%flag,o_plulth%name, "Rainfall therm.", "K/s")
     1529             CALL histdef2d(iff,clef_stations(iff),o_plulst%flag,o_plulst%name, "Rainfall strat.", "K/s")
     1530             CALL histdef2d(iff,clef_stations(iff),o_lmaxth%flag,o_lmaxth%name, "Upper level thermals", "")
     1531             CALL histdef3d(iff,clef_stations(iff),o_ptconvth%flag,o_ptconvth%name, "POINTS CONVECTIFS therm.", " ")
     1532             CALL histdef3d(iff,clef_stations(iff),o_f_th%flag,o_f_th%name, "Thermal plume mass flux", "kg/(m2*s)")
     1533             CALL histdef3d(iff,clef_stations(iff),o_e_th%flag,o_e_th%name,"Thermal plume entrainment","K/s")
     1534             CALL histdef3d(iff,clef_stations(iff),o_w_th%flag,o_w_th%name,"Thermal plume vertical velocity","m/s")
     1535             CALL histdef3d(iff,clef_stations(iff), &
     1536                  o_lambda_th%flag,o_lambda_th%name,"Thermal plume vertical velocity","m/s")
     1537             CALL histdef2d(iff,clef_stations(iff), &
     1538                  o_ftime_th%flag,o_ftime_th%name,"Fraction of time Shallow convection occurs"," ")
     1539             CALL histdef3d(iff,clef_stations(iff), &
     1540                  o_q_th%flag,o_q_th%name, "Thermal plume total humidity", "kg/kg")
     1541             CALL histdef3d(iff,clef_stations(iff), &
     1542                  o_a_th%flag,o_a_th%name, "Thermal plume fraction", "")
     1543             CALL histdef3d(iff,clef_stations(iff), &
     1544                  o_d_th%flag,o_d_th%name, "Thermal plume detrainment", "K/s")
     1545
     1546             CALL histdef2d(iff,clef_stations(iff), &
     1547                  o_f0_th%flag,o_f0_th%name, "Thermal closure mass flux", "K/s")
     1548             CALL histdef2d(iff,clef_stations(iff), &
     1549                  o_zmax_th%flag,o_zmax_th%name, "Thermal plume height", "K/s")
     1550             CALL histdef3d(iff,clef_stations(iff), &
     1551                  o_dqthe%flag,o_dqthe%name, "Thermal dQ", "(kg/kg)/s")
     1552          endif !iflag_thermals.gt.1
     1553          CALL histdef3d(iff,clef_stations(iff), &
     1554               o_dtajs%flag,o_dtajs%name, "Dry adjust. dT", "K/s")
     1555          CALL histdef3d(iff,clef_stations(iff), &
     1556               o_dqajs%flag,o_dqajs%name, "Dry adjust. dQ", "(kg/kg)/s")
     1557          CALL histdef3d(iff,clef_stations(iff), &
     1558               o_dtswr%flag,o_dtswr%name, "SW radiation dT", "K/s")
     1559          CALL histdef3d(iff,clef_stations(iff), &
     1560               o_dtsw0%flag,o_dtsw0%name, "CS SW radiation dT", "K/s")
     1561          CALL histdef3d(iff,clef_stations(iff), &
     1562               o_dtlwr%flag,o_dtlwr%name, "LW radiation dT", "K/s")
     1563          CALL histdef3d(iff,clef_stations(iff), &
     1564               o_dtlw0%flag,o_dtlw0%name, "CS LW radiation dT", "K/s")
     1565          CALL histdef3d(iff,clef_stations(iff), &
     1566               o_dtec%flag,o_dtec%name, "Cinetic dissip dT", "K/s")
     1567          CALL histdef3d(iff,clef_stations(iff), &
     1568               o_duvdf%flag,o_duvdf%name, "Boundary-layer dU", "m/s2")
     1569          CALL histdef3d(iff,clef_stations(iff), &
     1570               o_dvvdf%flag,o_dvvdf%name, "Boundary-layer dV", "m/s2")
     1571
     1572          IF (ok_orodr) THEN
     1573             CALL histdef3d(iff,clef_stations(iff), &
     1574                  o_duoro%flag,o_duoro%name, "Orography dU", "m/s2")
     1575             CALL histdef3d(iff,clef_stations(iff), &
     1576                  o_dvoro%flag,o_dvoro%name, "Orography dV", "m/s2")
     1577             CALL histdef3d(iff,clef_stations(iff), &
     1578                  o_dtoro%flag,o_dtoro%name, "Orography dT", "K/s")
     1579          ENDIF
     1580
     1581          IF (ok_orolf) THEN
     1582             CALL histdef3d(iff,clef_stations(iff), &
     1583                  o_dulif%flag,o_dulif%name, "Orography dU", "m/s2")
     1584             CALL histdef3d(iff,clef_stations(iff), &
     1585                  o_dvlif%flag,o_dvlif%name, "Orography dV", "m/s2")
     1586             CALL histdef3d(iff,clef_stations(iff), &
     1587                  o_dtlif%flag,o_dtlif%name, "Orography dT", "K/s")
     1588          ENDIF
     1589
     1590          IF (ok_hines) then
     1591             CALL histdef3d(iff,clef_stations(iff), &
     1592                  o_duhin%flag,o_duhin%name, "Hines GWD dU", "m/s2")
     1593             CALL histdef3d(iff,clef_stations(iff), &
     1594                  o_dvhin%flag,o_dvhin%name, "Hines GWD dV", "m/s2")
     1595
     1596             CALL histdef3d(iff,clef_stations(iff), &
     1597                  o_dthin%flag,o_dthin%name, "Hines GWD dT", "K/s")
     1598          ENDIF
     1599
     1600          CALL histdef3d(iff,clef_stations(iff), &
     1601               o_rsu%flag,o_rsu%name, "SW upward radiation", "W m-2")
     1602          CALL histdef3d(iff,clef_stations(iff), &
     1603               o_rsd%flag,o_rsd%name, "SW downward radiation", "W m-2")
     1604          CALL histdef3d(iff,clef_stations(iff), &
     1605               o_rlu%flag,o_rlu%name, "LW upward radiation", "W m-2")
     1606          CALL histdef3d(iff,clef_stations(iff), &
     1607               o_rld%flag,o_rld%name, "LW downward radiation", "W m-2")
     1608
     1609          CALL histdef3d(iff,clef_stations(iff), &
     1610               o_rsucs%flag,o_rsucs%name, "SW CS upward radiation", "W m-2")
     1611          CALL histdef3d(iff,clef_stations(iff), &
     1612               o_rsdcs%flag,o_rsdcs%name, "SW CS downward radiation", "W m-2")
     1613          CALL histdef3d(iff,clef_stations(iff), &
     1614               o_rlucs%flag,o_rlucs%name, "LW CS upward radiation", "W m-2")
     1615          CALL histdef3d(iff,clef_stations(iff), &
     1616               o_rldcs%flag,o_rldcs%name, "LW CS downward radiation", "W m-2")
     1617
     1618          CALL histdef3d(iff,clef_stations(iff), &
     1619               o_tnt%flag,o_tnt%name, "Tendency of air temperature", "K s-1")
     1620
     1621          CALL histdef3d(iff,clef_stations(iff), &
     1622               o_tntc%flag,o_tntc%name, "Tendency of air temperature due to Moist Convection", &
     1623               "K s-1")
     1624
     1625          CALL histdef3d(iff,clef_stations(iff), &
     1626               o_tntr%flag,o_tntr%name, "Air temperature tendency due to Radiative heating", &
     1627               "K s-1")
     1628
     1629          CALL histdef3d(iff,clef_stations(iff), &
     1630               o_tntscpbl%flag,o_tntscpbl%name, "Air temperature tendency due to St cloud and precipitation and BL mixing", &
     1631               "K s-1")
     1632
     1633          CALL histdef3d(iff,clef_stations(iff), &
     1634               o_tnhus%flag,o_tnhus%name, "Tendency of specific humidity", "s-1")
     1635
     1636          CALL histdef3d(iff,clef_stations(iff), &
     1637               o_tnhusc%flag,o_tnhusc%name, "Tendency of specific humidity due to convection", "s-1")
     1638
     1639          CALL histdef3d(iff,clef_stations(iff), &
     1640               o_tnhusscpbl%flag,o_tnhusscpbl%name, "Tendency of Specific humidity due to ST cl, precip and BL mixing", &
     1641               "s-1")
     1642
     1643          CALL histdef3d(iff,clef_stations(iff), &
     1644               o_evu%flag,o_evu%name, "Eddy viscosity coefficient for Momentum Variables", "m2 s-1")
     1645
     1646          CALL histdef3d(iff,clef_stations(iff), &
     1647               o_h2o%flag,o_h2o%name, "Mass Fraction of Water", "1")
     1648
     1649          CALL histdef3d(iff,clef_stations(iff), &
     1650               o_mcd%flag,o_mcd%name, "Downdraft COnvective Mass Flux", "kg/(m2*s)")
     1651
     1652          CALL histdef3d(iff,clef_stations(iff), &
     1653               o_dmc%flag,o_dmc%name, "Deep COnvective Mass Flux", "kg/(m2*s)")
     1654
     1655          CALL histdef3d(iff,clef_stations(iff), &
     1656               o_ref_liq%flag,o_ref_liq%name, "Effective radius of convective cloud liquid water particle", "m")
     1657
     1658          CALL histdef3d(iff,clef_stations(iff), &
     1659               o_ref_ice%flag,o_ref_ice%name, "Effective radius of startiform cloud ice particle", "m")
     1660
     1661          if (RCO2_per.NE.RCO2_act.OR.RCH4_per.NE.RCH4_act.OR. &
     1662               RN2O_per.NE.RN2O_act.OR.RCFC11_per.NE.RCFC11_act.OR. &
     1663               RCFC12_per.NE.RCFC12_act) THEN
     1664
     1665             CALL histdef2d(iff,clef_stations(iff),o_rsut4co2%flag,o_rsut4co2%name, &
     1666                  "TOA Out SW in 4xCO2 atmosphere", "W/m2")
     1667             CALL histdef2d(iff,clef_stations(iff),o_rlut4co2%flag,o_rlut4co2%name, &
     1668                  "TOA Out LW in 4xCO2 atmosphere", "W/m2")
     1669             CALL histdef2d(iff,clef_stations(iff),o_rsutcs4co2%flag,o_rsutcs4co2%name, &
     1670                  "TOA Out CS SW in 4xCO2 atmosphere", "W/m2")
     1671             CALL histdef2d(iff,clef_stations(iff),o_rlutcs4co2%flag,o_rlutcs4co2%name, &
     1672                  "TOA Out CS LW in 4xCO2 atmosphere", "W/m2")
     1673
     1674             CALL histdef3d(iff,clef_stations(iff),o_rsu4co2%flag,o_rsu4co2%name, &
     1675                  "Upwelling SW 4xCO2 atmosphere", "W/m2")
     1676             CALL histdef3d(iff,clef_stations(iff),o_rlu4co2%flag,o_rlu4co2%name, &
     1677                  "Upwelling LW 4xCO2 atmosphere", "W/m2")
     1678             CALL histdef3d(iff,clef_stations(iff),o_rsucs4co2%flag,o_rsucs4co2%name, &
     1679                  "Upwelling CS SW 4xCO2 atmosphere", "W/m2")
     1680             CALL histdef3d(iff,clef_stations(iff),o_rlucs4co2%flag,o_rlucs4co2%name, &
     1681                  "Upwelling CS LW 4xCO2 atmosphere", "W/m2")
     1682
     1683             CALL histdef3d(iff,clef_stations(iff),o_rsd4co2%flag,o_rsd4co2%name, &
     1684                  "Downwelling SW 4xCO2 atmosphere", "W/m2")
     1685             CALL histdef3d(iff,clef_stations(iff),o_rld4co2%flag,o_rld4co2%name, &
     1686                  "Downwelling LW 4xCO2 atmosphere", "W/m2")
     1687             CALL histdef3d(iff,clef_stations(iff),o_rsdcs4co2%flag,o_rsdcs4co2%name, &
     1688                  "Downwelling CS SW 4xCO2 atmosphere", "W/m2")
     1689             CALL histdef3d(iff,clef_stations(iff),o_rldcs4co2%flag,o_rldcs4co2%name, &
     1690                  "Downwelling CS LW 4xCO2 atmosphere", "W/m2")
     1691
     1692          endif
     1693
     1694
     1695          IF (nqtot>=3) THEN
     1696             DO iq=3,nqtot 
     1697                iiq=niadv(iq)
     1698                o_trac(iq-2) = ctrl_out((/ 4, 5, 1, 1, 1, 10 /),tname(iiq))
     1699                CALL histdef3d (iff,clef_stations(iff), &
     1700                     o_trac(iq-2)%flag,o_trac(iq-2)%name,'Tracer '//ttext(iiq), "-" )
     1701             ENDDO
     1702          ENDIF
     1703
     1704          CALL histend(nid_files(iff))
     1705
     1706          ndex2d = 0
     1707          ndex3d = 0
     1708
     1709       ENDIF ! clef_files
     1710
     1711    ENDDO !  iff
     1712    write(lunout,*)'Fin phys_output_mod.F90'
     1713  end subroutine phys_output_open
     1714
     1715  SUBROUTINE histdef2d (iff,lpoint,flag_var,nomvar,titrevar,unitvar)
     1716
     1717    use ioipsl
     1718    USE dimphy
     1719    USE mod_phys_lmdz_para
     1720    USE iophy
     1721
     1722    IMPLICIT NONE
     1723
     1724    include "dimensions.h"
     1725    include "temps.h"
     1726    include "indicesol.h"
     1727    include "clesphys.h"
     1728
     1729    integer                          :: iff
     1730    logical                          :: lpoint
     1731    integer, dimension(nfiles)       :: flag_var
     1732    character(len=20)                 :: nomvar
     1733    character(len=*)                 :: titrevar
     1734    character(len=*)                 :: unitvar
     1735
     1736    real zstophym
     1737
     1738    if (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') then
     1739       zstophym=zoutm(iff)
     1740    else
     1741       zstophym=zdtime
     1742    endif
     1743
     1744    ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def
     1745    call conf_physoutputs(nomvar,flag_var)
     1746
     1747    if(.NOT.lpoint) THEN 
    17421748       if ( flag_var(iff)<=lev_files(iff) ) then
    1743  call histdef (nid_files(iff),nomvar,titrevar,unitvar, &
     1749          call histdef (nid_files(iff),nomvar,titrevar,unitvar, &
    17441750               iim,jj_nb,nhorim(iff), 1,1,1, -99, 32, &
    17451751               type_ecri(iff), zstophym,zoutm(iff))               
    1746        endif                     
    1747        else
     1752       endif
     1753    else
    17481754       if ( flag_var(iff)<=lev_files(iff) ) then
    1749  call histdef (nid_files(iff),nomvar,titrevar,unitvar, &
     1755          call histdef (nid_files(iff),nomvar,titrevar,unitvar, &
    17501756               npstn,1,nhorim(iff), 1,1,1, -99, 32, &
    17511757               type_ecri(iff), zstophym,zoutm(iff))               
    1752        endif                     
    1753        endif                     
    1754       end subroutine histdef2d
    1755 
    1756       SUBROUTINE histdef3d (iff,lpoint,flag_var,nomvar,titrevar,unitvar)
    1757 
    1758        use ioipsl
    1759        USE dimphy
    1760        USE mod_phys_lmdz_para
    1761        USE iophy
    1762 
    1763        IMPLICIT NONE
    1764 
    1765        include "dimensions.h"
    1766        include "temps.h"
    1767        include "indicesol.h"
    1768        include "clesphys.h"
    1769 
    1770        integer                          :: iff
    1771        logical                          :: lpoint
    1772        integer, dimension(nfiles)       :: flag_var
    1773        character(len=20)                 :: nomvar
    1774        character(len=*)                 :: titrevar
    1775        character(len=*)                 :: unitvar
    1776 
    1777        real zstophym
    1778 
    1779 ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def
    1780        call conf_physoutputs(nomvar,flag_var)
    1781 
    1782        if (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') then
    1783          zstophym=zoutm(iff)
    1784        else
    1785          zstophym=zdtime
    17861758       endif
    1787 
    1788        if(.NOT.lpoint) THEN
     1759    endif
     1760  end subroutine histdef2d
     1761
     1762  SUBROUTINE histdef3d (iff,lpoint,flag_var,nomvar,titrevar,unitvar)
     1763
     1764    use ioipsl
     1765    USE dimphy
     1766    USE mod_phys_lmdz_para
     1767    USE iophy
     1768
     1769    IMPLICIT NONE
     1770
     1771    include "dimensions.h"
     1772    include "temps.h"
     1773    include "indicesol.h"
     1774    include "clesphys.h"
     1775
     1776    integer                          :: iff
     1777    logical                          :: lpoint
     1778    integer, dimension(nfiles)       :: flag_var
     1779    character(len=20)                 :: nomvar
     1780    character(len=*)                 :: titrevar
     1781    character(len=*)                 :: unitvar
     1782
     1783    real zstophym
     1784
     1785    ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def
     1786    call conf_physoutputs(nomvar,flag_var)
     1787
     1788    if (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') then
     1789       zstophym=zoutm(iff)
     1790    else
     1791       zstophym=zdtime
     1792    endif
     1793
     1794    if(.NOT.lpoint) THEN
    17891795       if ( flag_var(iff)<=lev_files(iff) ) then
    17901796          call histdef (nid_files(iff), nomvar, titrevar, unitvar, &
     
    17931799               zstophym, zoutm(iff))
    17941800       endif
    1795        else
     1801    else
    17961802       if ( flag_var(iff)<=lev_files(iff) ) then
    17971803          call histdef (nid_files(iff), nomvar, titrevar, unitvar, &
     
    18001806               type_ecri(iff), zstophym,zoutm(iff))
    18011807       endif
    1802        endif
    1803       end subroutine histdef3d
    1804 
    1805       SUBROUTINE conf_physoutputs(nam_var,flag_var)
     1808    endif
     1809  end subroutine histdef3d
     1810
     1811  SUBROUTINE conf_physoutputs(nam_var,flag_var)
    18061812!!! Lecture des noms et niveau de sortie des variables dans output.def
    1807 !   en utilisant les routines getin de IOIPSL 
    1808        use ioipsl
    1809 
    1810        IMPLICIT NONE
    1811 
    1812        include 'iniprint.h'
    1813 
    1814        character(len=20)                :: nam_var
    1815        integer, dimension(nfiles)      :: flag_var
    1816 
    1817         IF(prt_level>10) WRITE(lunout,*)'Avant getin: nam_var flag_var ',nam_var,flag_var(:)
    1818         call getin('flag_'//nam_var,flag_var)
    1819         call getin('name_'//nam_var,nam_var)
    1820         IF(prt_level>10) WRITE(lunout,*)'Apres getin: nam_var flag_var ',nam_var,flag_var(:)
    1821 
    1822       END SUBROUTINE conf_physoutputs
    1823 
    1824       SUBROUTINE convers_timesteps(str,dtime,timestep)
    1825 
    1826         use ioipsl
    1827         USE phys_cal_mod
    1828 
    1829         IMPLICIT NONE
    1830 
    1831         character(len=20)   :: str
    1832         character(len=10)   :: type
    1833         integer             :: ipos,il
    1834         real                :: ttt,xxx,timestep,dayseconde,dtime
    1835         parameter (dayseconde=86400.)
    1836         include "temps.h"
    1837         include "comconst.h"
    1838 
    1839         ipos=scan(str,'0123456789.',.true.)
    1840 
    1841         il=len_trim(str)
    1842         print*,ipos,il
    1843         read(str(1:ipos),*) ttt
    1844         print*,ttt
    1845         type=str(ipos+1:il)
    1846 
    1847 
    1848         if ( il == ipos ) then
    1849         type='day'
    1850         endif
    1851 
    1852         if ( type == 'day'.or.type == 'days'.or.type == 'jours'.or.type == 'jour' ) timestep = ttt * dayseconde
    1853         if ( type == 'mounths'.or.type == 'mth'.or.type == 'mois' ) then
    1854            print*,'annee_ref,day_ref mon_len',annee_ref,day_ref,ioget_mon_len(annee_ref,day_ref)
    1855            timestep = ttt * dayseconde * mth_len
    1856         endif
    1857         if ( type == 'hours'.or.type == 'hr'.or.type == 'heurs') timestep = ttt * dayseconde / 24.
    1858         if ( type == 'mn'.or.type == 'minutes'  ) timestep = ttt * 60.
    1859         if ( type == 's'.or.type == 'sec'.or.type == 'secondes'   ) timestep = ttt
    1860         if ( type == 'TS' ) timestep = dtime
    1861 
    1862         print*,'type =      ',type
    1863         print*,'nb j/h/m =  ',ttt
    1864         print*,'timestep(s)=',timestep
    1865 
    1866         END SUBROUTINE convers_timesteps
     1813    !   en utilisant les routines getin de IOIPSL 
     1814    use ioipsl
     1815
     1816    IMPLICIT NONE
     1817
     1818    include 'iniprint.h'
     1819
     1820    character(len=20)                :: nam_var
     1821    integer, dimension(nfiles)      :: flag_var
     1822
     1823    IF(prt_level>10) WRITE(lunout,*)'Avant getin: nam_var flag_var ',nam_var,flag_var(:)
     1824    call getin('flag_'//nam_var,flag_var)
     1825    call getin('name_'//nam_var,nam_var)
     1826    IF(prt_level>10) WRITE(lunout,*)'Apres getin: nam_var flag_var ',nam_var,flag_var(:)
     1827
     1828  END SUBROUTINE conf_physoutputs
     1829
     1830  SUBROUTINE convers_timesteps(str,dtime,timestep)
     1831
     1832    use ioipsl
     1833    USE phys_cal_mod
     1834
     1835    IMPLICIT NONE
     1836
     1837    character(len=20)   :: str
     1838    character(len=10)   :: type
     1839    integer             :: ipos,il
     1840    real                :: ttt,xxx,timestep,dayseconde,dtime
     1841    parameter (dayseconde=86400.)
     1842    include "temps.h"
     1843    include "comconst.h"
     1844    include "iniprint.h"
     1845
     1846    ipos=scan(str,'0123456789.',.true.)
     1847    ! 
     1848    il=len_trim(str)
     1849    write(lunout,*)ipos,il
     1850    read(str(1:ipos),*) ttt
     1851    write(lunout,*)ttt
     1852    type=str(ipos+1:il)
     1853
     1854
     1855    if ( il == ipos ) then
     1856       type='day'
     1857    endif
     1858
     1859    if ( type == 'day'.or.type == 'days'.or.type == 'jours'.or.type == 'jour' ) timestep = ttt * dayseconde
     1860    if ( type == 'mounths'.or.type == 'mth'.or.type == 'mois' ) then
     1861       write(lunout,*)'annee_ref,day_ref mon_len',annee_ref,day_ref,ioget_mon_len(annee_ref,day_ref)
     1862       timestep = ttt * dayseconde * mth_len
     1863    endif
     1864    if ( type == 'hours'.or.type == 'hr'.or.type == 'heurs') timestep = ttt * dayseconde / 24.
     1865    if ( type == 'mn'.or.type == 'minutes'  ) timestep = ttt * 60.
     1866    if ( type == 's'.or.type == 'sec'.or.type == 'secondes'   ) timestep = ttt
     1867    if ( type == 'TS' ) timestep = ttt * dtime
     1868
     1869    write(lunout,*)'type =      ',type
     1870    write(lunout,*)'nb j/h/m =  ',ttt
     1871    write(lunout,*)'timestep(s)=',timestep
     1872
     1873  END SUBROUTINE convers_timesteps
    18671874
    18681875END MODULE phys_output_mod
  • LMDZ5/branches/testing/libf/phylmd/phys_output_write.h

    r1539 r1664  
    614614        ENDIF
    615615
    616         IF (o_plcl%flag(iff)<=lev_files(iff)) THEN
    617       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    618      $o_plcl%name,itau_w,plcl)
    619         ENDIF
    620 
    621         IF (o_plfc%flag(iff)<=lev_files(iff)) THEN
    622       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    623      $o_plfc%name,itau_w,plfc)
    624         ENDIF
    625 
    626         IF (o_wbeff%flag(iff)<=lev_files(iff)) THEN
    627       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    628      $o_wbeff%name,itau_w,wbeff)
    629         ENDIF
    630 
     616        if (iflag_con /= 30) then
     617           if (o_plcl%flag(iff)<=lev_files(iff)) THEN
     618              CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     619     $             o_plcl%name,itau_w,plcl)
     620           ENDIF
     621
     622           IF (o_plfc%flag(iff)<=lev_files(iff)) THEN
     623              CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     624     $             o_plfc%name,itau_w,plfc)
     625           ENDIF
     626
     627           IF (o_wbeff%flag(iff)<=lev_files(iff)) THEN
     628              CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     629     $             o_wbeff%name,itau_w,wbeff)
     630           ENDIF
     631        end if
    631632
    632633        IF (o_prw%flag(iff)<=lev_files(iff)) THEN
  • LMDZ5/branches/testing/libf/phylmd/physiq.F

    r1539 r1664  
    4242      use radlwsw_m, only: radlwsw
    4343      USE control_mod
     44#ifdef REPROBUS
     45      USE CHEM_REP, ONLY : Init_chem_rep_xjour
     46#endif
    4447
    4548
     
    12151218      REAL, dimension(klon, klev) :: cldtaurad  ! epaisseur optique pour radlwsw,COSP
    12161219      REAL, dimension(klon, klev) :: cldemirad  ! emissivite pour radlwsw,COSP
     1220      INTEGER :: nbtr_tmp ! Number of tracer inside concvl
     1221      REAL, dimension(klon,klev) :: sh_in ! Specific humidity entering in phytrac
    12171222
    12181223cIM for NMC files
     
    13551360         tau_overturning_th(:)=0.
    13561361
    1357          IF (config_inca /= 'none') THEN
     1362         IF (type_trac == 'inca') THEN
    13581363            ! jg : initialisation jusqu'au ces variables sont dans restart
    13591364            ccm(:,:,:) = 0.
     
    16191624#endif
    16201625
    1621          ecrit_hf2mth = ecrit_mth/ecrit_hf
    16221626
    16231627         ecrit_hf = ecrit_hf * un_jour
     
    16331637         ecrit_LES = ecrit_LES * un_jour
    16341638c
    1635          PRINT*,'physiq ecrit_ hf day mth reg tra ISCCP hf2mth',
    1636      .   ecrit_hf,ecrit_day,ecrit_mth,ecrit_reg,ecrit_tra,ecrit_ISCCP,
    1637      .   ecrit_hf2mth
    16381639
    16391640cXXXPB Positionner date0 pour initialisation de ORCHIDEE
     
    16521653cc         ENDDO
    16531654c
    1654       IF (config_inca /= 'none') THEN
     1655      IF (type_trac == 'inca') THEN
    16551656#ifdef INCA
    16561657         CALL VTe(VTphysiq)
     
    17401741      CALL change_srf_frac(itap, dtime, days_elapsed+1,
    17411742     *     pctsrf, falb1, falb2, ftsol, u10m, v10m, pbl_tke)
     1743
     1744
     1745! Update time and other variables in Reprobus
     1746      IF (type_trac == 'repr') THEN
     1747#ifdef REPROBUS
     1748         CALL Init_chem_rep_xjour(jD_cur-jD_ref+day_ref)
     1749         print*,'xjour equivalent rjourvrai',jD_cur-jD_ref+day_ref
     1750         CALL Rtime(debut)
     1751#endif
     1752      END IF
     1753
    17421754
    17431755! Tendances bidons pour les processus qui n'affectent pas certaines
     
    22922304          IF (ok_cvl) THEN ! new driver for convectL
    22932305
     2306             IF (type_trac == 'repr') THEN
     2307                nbtr_tmp=ntra
     2308             ELSE
     2309                nbtr_tmp=nbtr
     2310             END IF
    22942311          CALL concvl (iflag_con,iflag_clos,
    22952312     .        dtime,paprs,pplay,t_undi,q_undi,
    22962313     .        t_wake,q_wake,wake_s,
    2297      .        u_seri,v_seri,tr_seri,nbtr,
     2314     .        u_seri,v_seri,tr_seri,nbtr_tmp,
    22982315     .        ALE,ALP,
    22992316     .        ema_work1,ema_work2,
     
    31503167      ENDDO
    31513168
    3152       IF (config_inca /= 'none') THEN
     3169      IF (type_trac == 'inca') THEN
    31533170#ifdef INCA
    31543171         CALL VTe(VTphysiq)
     
    32043221         CALL VTb(VTphysiq)
    32053222#endif
    3206       END IF !config_inca /= 'none'
     3223      END IF !type_trac = inca
    32073224c     
    32083225c Calculer les parametres optiques des nuages et quelques
     
    36683685C
    36693686
     3687       IF (type_trac=='repr') THEN
     3688          sh_in(:,:) = q_seri(:,:)
     3689       ELSE
     3690          sh_in(:,:) = qx(:,:,ivap)
     3691       END IF
     3692
    36703693      call phytrac (
    36713694     I     itap,     days_elapsed+1,    jH_cur,   debut,
     
    36773700     I     rlat,     frac_impa, frac_nucl,rlon,
    36783701     I     presnivs, pphis,     pphi,     albsol1,
    3679      I     qx(:,:,ivap),rhcl,   cldfra,   rneb,
     3702     I     sh_in,    rhcl,      cldfra,   rneb,
    36803703     I     diafra,   cldliq,    itop_con, ibas_con,
    36813704     I     pmflxr,   pmflxs,    prfl,     psfl,
     
    38603883#include "calcul_divers.h"
    38613884c
    3862       IF (config_inca /= 'none') THEN
     3885      IF (type_trac == 'inca') THEN
    38633886#ifdef INCA
    38643887         CALL VTe(VTphysiq)
  • LMDZ5/branches/testing/libf/phylmd/phytrac.F90

    r1454 r1664  
    3333  USE traclmdz_mod
    3434  USE tracinca_mod
     35  USE tracreprobus_mod
    3536  USE control_mod
    36 
    3737
    3838
     
    4646  INCLUDE "paramet.h"
    4747  INCLUDE "thermcell.h"
     48  INCLUDE "iniprint.h"
    4849!==========================================================================
    4950!                   -- ARGUMENT DESCRIPTION --
     
    5556  INTEGER,INTENT(IN) :: nstep      ! Appel physique
    5657  INTEGER,INTENT(IN) :: julien     ! Jour julien
    57   REAL,INTENT(IN)    :: gmtime
     58  REAL,INTENT(IN)    :: gmtime     ! Heure courante
    5859  REAL,INTENT(IN)    :: pdtphys    ! Pas d'integration pour la physique (seconde)
    5960  LOGICAL,INTENT(IN) :: debutphy   ! le flag de l'initialisation de la physique
     
    202203!######################################################################
    203204  IF (debutphy) THEN
    204      WRITE(*,*) 'FIRST TIME IN PHYTRAC : pdtphys(sec) = ',pdtphys,'ecrit_tra (sec) = ',ecrit_tra
     205     IF (prt_level >9) WRITE(lunout,*) 'FIRST TIME IN PHYTRAC : pdtphys(sec) = ',pdtphys,'ecrit_tra (sec) = ',ecrit_tra
    205206     ALLOCATE( source(klon,nbtr), stat=ierr)
    206207     IF (ierr /= 0) CALL abort_gcm('phytrac', 'pb in allocation 1',1)
     
    217218        source(:,:)=0.
    218219        CALL tracinca_init(aerosol,lessivage)
     220     CASE('repr')
     221        source(:,:)=0.
    219222     END SELECT
    220223!
     
    222225! ----------------------------
    223226#ifdef CPP_IOIPSL
    224 !     INCLUDE "ini_histrac.h"
     227     INCLUDE "ini_histrac.h"
    225228#endif
    226229  END IF
     
    257260          rfname,                                        &
    258261          tr_seri,  source,   solsym)     
     262
     263  CASE('repr')
     264     !   -- CHIMIE REPROBUS --
     265
     266     CALL tracreprobus(pdtphys, gmtime, debutphy, julien, &
     267          presnivs, xlat, xlon, pphis, pphi, &
     268          t_seri, pplay, paprs, sh , &
     269          tr_seri, solsym)
     270     
    259271  END SELECT
    260272
     
    403415!=============================================================
    404416#ifdef CPP_IOIPSL
    405 !  INCLUDE "write_histrac.h"
     417  INCLUDE "write_histrac.h"
    406418#endif
    407419
  • LMDZ5/branches/testing/libf/phylmd/press_coefoz_m.F90

    r1403 r1664  
    6060       press_in_edg(1) = 0.
    6161       ! We choose edges halfway in logarithm:
    62        forall (k = 2:n_plev) press_in_edg(k) = sqrt(plev(k - 1) * plev(k))
     62       DO k = 2,n_plev
     63          press_in_edg(k) = SQRT(plev(k - 1) * plev(k))
     64       ENDDO
    6365       press_in_edg(n_plev + 1) = huge(0.)
    6466       ! (infinity, but any value guaranteed to be greater than the
  • LMDZ5/branches/testing/libf/phylmd/radiation_AR4.F

    r1279 r1664  
    1919cym#include "raddim.h"
    2020#include "YOMCST.h"
     21#include "iniprint.h"
    2122C
    2223C     ------------------------------------------------------------------
     
    163164        allocate(ZFSUPAI(KDLON,KFLEV+1))
    164165        allocate(ZFSDNAI(KDLON,KFLEV+1))
    165         DO JK = 1 , KDLON*(KFLEV+1)
    166           ZFSUPAD(JK,1) = 0.0     ! ZFSUPAD(:,:)=0.
    167           ZFSDNAD(JK,1) = 0.0     ! ZFSDNAD(:,:)=0.
    168           ZFSUPAI(JK,1) = 0.0     ! ZFSUPAI(:,:)=0.
    169           ZFSDNAI(JK,1) = 0.0     ! ZFSDNAI(:,:)=0.
    170         END DO
     166
     167        ZFSUPAD(:,:)=0.
     168        ZFSDNAD(:,:)=0.
     169        ZFSUPAI(:,:)=0.
     170        ZFSDNAI(:,:)=0.
    171171      endif
    172 !rv
    173      
    174 c
     172
    175173      IF (appel1er) THEN
    176          PRINT*, 'SW calling frequency : ', swpas
    177          PRINT*, "   In general, it should be 1"
     174         WRITE(lunout,*) 'SW calling frequency : ', swpas
     175         WRITE(lunout,*) "   In general, it should be 1"
    178176         appel1er = .FALSE.
    179177      ENDIF
     
    526524      USE dimphy
    527525      USE radiation_AR4_param, only : RSUN, RRAY
     526      USE infotrac, ONLY : type_trac
     527#ifdef REPROBUS
     528      USE CHEM_REP, ONLY : RSUNTIME, ok_SUNTIME
     529#endif
     530
    528531      IMPLICIT none
    529532cym#include "dimensions.h"
    530533cym#include "dimphy.h"
    531 cym#include "raddim.h"
     534cym#include "raddim.h"i
     535#include "iniprint.h"
    532536C
    533537C     ------------------------------------------------------------------
     
    613617      INTEGER jl, jk, k, jaj, ikm1, ikl
    614618
     619C If running with Reporbus, overwrite default values of RSUN.
     620C Otherwise keep default values from radiation_AR4_param module. 
     621      IF (type_trac == 'repr') THEN
     622#ifdef REPROBUS
     623         IF (ok_SUNTIME) THEN
     624            RSUN(1) = RSUNTIME(1)
     625            RSUN(2) = RSUNTIME(2)
     626         ENDIF
     627         WRITE(lunout,*)'RSUN(1): ',RSUN(1)
     628#endif
     629      END IF
     630
    615631C     ------------------------------------------------------------------
    616632C
     
    754770      USE dimphy
    755771      USE radiation_AR4_param, only : RSUN, RRAY
     772      USE infotrac, ONLY : type_trac
     773#ifdef REPROBUS
     774      use CHEM_REP, only : RSUNTIME, ok_SUNTIME
     775#endif
     776
    756777      IMPLICIT none
    757778cym#include "dimensions.h"
     
    873894      INTEGER jref, jkl, jklp1, jajp, jkki, jkkp4, jn2j, iabs
    874895      REAL(KIND=8) ZRMUM1, ZWH2O, ZCNEB, ZAA, ZBB, ZRKI, ZRE11
     896
     897C If running with Reporbus, overwrite default values of RSUN.
     898C Otherwise keep default values from radiation_AR4_param module. 
     899      IF (type_trac == 'repr') THEN
     900#ifdef REPROBUS
     901         IF (ok_SUNTIME) THEN
     902            RSUN(1)=RSUNTIME(1)
     903            RSUN(2)=RSUNTIME(2)
     904         END IF
     905#endif
     906      END IF
     907
    875908C
    876909
     
    23072340#include "raddimlw.h"
    23082341#include "YOMCST.h"
     2342#include "iniprint.h"
    23092343C
    23102344C-----------------------------------------------------------------------
     
    24122446C     ------------------------------------------------------------------
    24132447      IF (appel1er) THEN
    2414          PRINT*, "LW clear-sky calling frequency: ", lw0pas
    2415          PRINT*, "LW cloudy-sky calling frequency: ", lwpas
    2416          PRINT*, "   In general, they should be 1"
     2448         WRITE(lunout,*) "LW clear-sky calling frequency: ", lw0pas
     2449         WRITE(lunout,*) "LW cloudy-sky calling frequency: ", lwpas
     2450         WRITE(lunout,*) "   In general, they should be 1"
    24172451cym
    24182452         allocate(ZFLUX(KDLON,2,KFLEV+1) )
     
    24852519      USE dimphy
    24862520      USE radiation_AR4_param, only : TREF, RT1, RAER, AT, BT, OCT
     2521      USE infotrac, ONLY : type_trac
     2522#ifdef REPROBUS
     2523      USE CHEM_REP, ONLY: RCH42D,
     2524     $                    RN2O2D,
     2525     $                    RCFC112D,
     2526     $                    RCFC122D,
     2527     $                    ok_Rtime2D
     2528#endif
     2529
    24872530      IMPLICIT none
    24882531cym#include "dimensions.h"
     
    28002843     S                +ZUAER(JL,5)    *ZDUC(JL,JC)*ZDIFF
    28012844C
    2802       PABCU(JL,19,JC)=PABCU(JL,19,JCP1)
    2803      S               +ZABLY(JL,8,JC)*RCH4/RCO2*ZPHM6(JL)*ZDIFF
    2804       PABCU(JL,20,JC)=PABCU(JL,20,JCP1)
     2845C
     2846
     2847      IF (type_trac == 'repr') THEN
     2848#ifdef REPROBUS
     2849         IF (ok_Rtime2D) THEN
     2850            PABCU(JL,19,JC)=PABCU(JL,19,JCP1)
     2851     S           +ZABLY(JL,8,JC)*RCH42D(JL,JC)/RCO2*ZPHM6(JL)*ZDIFF
     2852            PABCU(JL,20,JC)=PABCU(JL,20,JCP1)
     2853     S           +ZABLY(JL,9,JC)*RCH42D(JL,JC)/RCO2*ZPSM6(JL)*ZDIFF
     2854            PABCU(JL,21,JC)=PABCU(JL,21,JCP1)
     2855     S           +ZABLY(JL,8,JC)*RN2O2D(JL,JC)/RCO2*ZPHN6(JL)*ZDIFF
     2856            PABCU(JL,22,JC)=PABCU(JL,22,JCP1)
     2857     S           +ZABLY(JL,9,JC)*RN2O2D(JL,JC)/RCO2*ZPSN6(JL)*ZDIFF
     2858C
     2859            PABCU(JL,23,JC)=PABCU(JL,23,JCP1)
     2860     S           +ZABLY(JL,8,JC)*RCFC112D(JL,JC)/RCO2         *ZDIFF
     2861            PABCU(JL,24,JC)=PABCU(JL,24,JCP1)
     2862     S           +ZABLY(JL,8,JC)*RCFC122D(JL,JC)/RCO2         *ZDIFF
     2863         ELSE
     2864            ! Same calculation as for type_trac /= repr
     2865            PABCU(JL,19,JC)=PABCU(JL,19,JCP1)
     2866     S           +ZABLY(JL,8,JC)*RCH4/RCO2*ZPHM6(JL)*ZDIFF
     2867            PABCU(JL,20,JC)=PABCU(JL,20,JCP1)
     2868     S           +ZABLY(JL,9,JC)*RCH4/RCO2*ZPSM6(JL)*ZDIFF
     2869            PABCU(JL,21,JC)=PABCU(JL,21,JCP1)
     2870     S           +ZABLY(JL,8,JC)*RN2O/RCO2*ZPHN6(JL)*ZDIFF
     2871            PABCU(JL,22,JC)=PABCU(JL,22,JCP1)
     2872     S           +ZABLY(JL,9,JC)*RN2O/RCO2*ZPSN6(JL)*ZDIFF
     2873C     
     2874            PABCU(JL,23,JC)=PABCU(JL,23,JCP1)
     2875     S               +ZABLY(JL,8,JC)*RCFC11/RCO2         *ZDIFF
     2876            PABCU(JL,24,JC)=PABCU(JL,24,JCP1)
     2877     S           +ZABLY(JL,8,JC)*RCFC12/RCO2         *ZDIFF
     2878         END IF
     2879#endif
     2880      ELSE
     2881         PABCU(JL,19,JC)=PABCU(JL,19,JCP1)
     2882     S        +ZABLY(JL,8,JC)*RCH4/RCO2*ZPHM6(JL)*ZDIFF
     2883         PABCU(JL,20,JC)=PABCU(JL,20,JCP1)
    28052884     S               +ZABLY(JL,9,JC)*RCH4/RCO2*ZPSM6(JL)*ZDIFF
    2806       PABCU(JL,21,JC)=PABCU(JL,21,JCP1)
    2807      S               +ZABLY(JL,8,JC)*RN2O/RCO2*ZPHN6(JL)*ZDIFF
    2808       PABCU(JL,22,JC)=PABCU(JL,22,JCP1)
    2809      S               +ZABLY(JL,9,JC)*RN2O/RCO2*ZPSN6(JL)*ZDIFF
    2810 C
    2811       PABCU(JL,23,JC)=PABCU(JL,23,JCP1)
    2812      S               +ZABLY(JL,8,JC)*RCFC11/RCO2         *ZDIFF
    2813       PABCU(JL,24,JC)=PABCU(JL,24,JCP1)
    2814      S               +ZABLY(JL,8,JC)*RCFC12/RCO2         *ZDIFF
     2885         PABCU(JL,21,JC)=PABCU(JL,21,JCP1)
     2886     S        +ZABLY(JL,8,JC)*RN2O/RCO2*ZPHN6(JL)*ZDIFF
     2887         PABCU(JL,22,JC)=PABCU(JL,22,JCP1)
     2888     S        +ZABLY(JL,9,JC)*RN2O/RCO2*ZPSN6(JL)*ZDIFF
     2889C     
     2890         PABCU(JL,23,JC)=PABCU(JL,23,JCP1)
     2891     S        +ZABLY(JL,8,JC)*RCFC11/RCO2         *ZDIFF
     2892         PABCU(JL,24,JC)=PABCU(JL,24,JCP1)
     2893     S        +ZABLY(JL,8,JC)*RCFC12/RCO2         *ZDIFF
     2894      END IF
     2895     
    28152896 523  CONTINUE
    28162897 524  CONTINUE
  • LMDZ5/branches/testing/libf/phylmd/radiation_AR4_param.F90

    r1279 r1664  
    159159      0.90811926E+01,  0.75073923E+02,  0.24654438E+03,  0.39332612E+03,  0.29385281E+03,  0.89107921E+02 /) , (/ 6,6 /) )
    160160
    161       REAL*8, dimension(2), parameter :: RSUN = (/ 0.441676 , 0.558324 /)
     161! If running with Reporbus type_trac=repr, values of RSUN might be overritten in radiation_AR4
     162      REAL*8, dimension(2) :: RSUN = (/ 0.441676 , 0.558324 /)
    162163      REAL*8, dimension(2,6), parameter :: RRAY = reshape ( &
    163164         (/ .428937E-01, .697200E-02,&
  • LMDZ5/branches/testing/libf/phylmd/radlwsw.F90

    r1279 r1664  
    3030
    3131  USE DIMPHY
    32   use assert_m, only: assert
     32  USE assert_m, ONLY : assert
     33  USE infotrac, ONLY : type_trac
     34#ifdef REPROBUS
     35  USE CHEM_REP, ONLY : solaireTIME, ok_SUNTIME, ndimozon
     36#endif
    3337
    3438  !======================================================================
     
    229233  !
    230234  PSCT = solaire/zdist/zdist
     235
     236  IF (type_trac == 'repr') THEN
     237#ifdef REPROBUS
     238     if(ok_SUNTIME) PSCT = solaireTIME/zdist/zdist
     239     print*,'Constante solaire: ',PSCT*zdist*zdist
     240#endif
     241  END IF
     242
    231243  DO j = 1, nb_gr
    232244    iof = kdlon*(j-1)
     
    281293      ENDDO
    282294    ENDDO
     295
     296    IF (type_trac == 'repr') THEN
     297#ifdef REPROBUS
     298       ndimozon = size(wo, 3)
     299       CALL RAD_INTERACTIF(POZON,iof)
     300#endif
     301    END IF
     302
    283303    !
    284304    DO k = 1, kflev+1
  • LMDZ5/branches/testing/libf/phylmd/soil.F90

    r996 r1664  
    5454  INCLUDE "indicesol.h"
    5555  INCLUDE "comsoil.h"
     56  INCLUDE "iniprint.h"
    5657!-----------------------------------------------------------------------
    5758! Arguments
     
    111112           READ(99,*) min_period
    112113           READ(99,*) dalph_soil
    113            PRINT*,'Discretization for the soil model'
    114            PRINT*,'First level e-folding depth',min_period, &
     114           WRITE(lunout,*)'Discretization for the soil model'
     115           WRITE(lunout,*)'First level e-folding depth',min_period, &
    115116                '   dalph',dalph_soil
    116117           CLOSE(99)
     
    135136     ENDDO
    136137     lambda=fz(.5)*dz1(1)
    137      PRINT*,'full layers, intermediate layers (seconds)'
     138     WRITE(lunout,*)'full layers, intermediate layers (seconds)'
    138139     DO jk=1,nsoilmx
    139140        rk=jk
    140141        rk1=jk+.5
    141142        rk2=jk-.5
    142         PRINT *,'fz=', &
     143        WRITE(lunout,*)'fz=', &
    143144             fz(rk1)*fz(rk2)*3.14,fz(rk)*fz(rk)*3.14
    144145     ENDDO
     
    175176     ENDDO
    176177  ELSE
    177      PRINT*, "valeur d indice non prevue", indice
     178     WRITE(lunout,*) "valeur d indice non prevue", indice
    178179     CALL abort
    179180  ENDIF
  • LMDZ5/branches/testing/libf/phylmd/sw_aeroAR4.F90

    r1307 r1664  
    2626#include "YOMCST.h"
    2727#include "clesphys.h"
     28#include "iniprint.h"
    2829  !
    2930  !     ------------------------------------------------------------------
     
    225226
    226227  IF (appel1er) THEN
    227      PRINT*, 'SW calling frequency : ', swpas
    228      PRINT*, "   In general, it should be 1"
     228     WRITE(lunout,*) 'SW calling frequency : ', swpas
     229     WRITE(lunout,*) "   In general, it should be 1"
    229230     appel1er = .FALSE.
    230231  ENDIF
  • LMDZ5/branches/testing/libf/phylmd/write_histrac.h

    r1403 r1664  
    33!  ECRITURE DU FICHIER :  histrac.nc
    44!***************************************
    5   IF (ecrit_tra > 0. .AND. config_inca == 'none') THEN
     5  IF (ecrit_tra > 0.) THEN
    66     
    77     itau_w = itau_phy + nstep
    88     
    9      CALL histwrite_phy(nid_tra,"phis",itau_w,pphis)
    10      CALL histwrite_phy(nid_tra,"aire",itau_w,airephy)
    11      CALL histwrite_phy(nid_tra,"zmasse",itau_w,zmasse)
     9     CALL histwrite_phy(nid_tra,.FALSE.,"phis",itau_w,pphis)
     10     CALL histwrite_phy(nid_tra,.FALSE.,"aire",itau_w,airephy)
     11     CALL histwrite_phy(nid_tra,.FALSE.,"zmasse",itau_w,zmasse)
    1212
    1313!TRACEURS
     
    1717
    1818! CONCENTRATIONS
    19         CALL histwrite_phy(nid_tra,tname(iiq),itau_w,tr_seri(:,:,it))
     19        CALL histwrite_phy(nid_tra,.FALSE.,tname(iiq),itau_w,tr_seri(:,:,it))
    2020
    2121! TD LESSIVAGE       
    2222        IF (lessivage .AND. aerosol(it)) THEN
    23            CALL histwrite_phy(nid_tra,"fl"//tname(iiq),itau_w,flestottr(:,:,it))
     23           CALL histwrite_phy(nid_tra,.FALSE.,"fl"//tname(iiq),itau_w,flestottr(:,:,it))
    2424        ENDIF
    2525
    2626! TD THERMIQUES
    2727        IF (iflag_thermals.gt.0) THEN
    28            CALL histwrite_phy(nid_tra,"d_tr_th_"//tname(iiq),itau_w,d_tr_th(:,:,it))
     28           CALL histwrite_phy(nid_tra,.FALSE.,"d_tr_th_"//tname(iiq),itau_w,d_tr_th(:,:,it))
    2929        ENDIF
    3030
    3131! TD CONVECTION
    3232        IF (iflag_con.GE.2) THEN
    33            CALL histwrite_phy(nid_tra,"d_tr_cv_"//tname(iiq),itau_w,d_tr_cv(:,:,it))
     33           CALL histwrite_phy(nid_tra,.FALSE.,"d_tr_cv_"//tname(iiq),itau_w,d_tr_cv(:,:,it))
    3434        ENDIF
    3535
    3636! TD COUCHE-LIMITE
    37         CALL histwrite_phy(nid_tra,"d_tr_cl_"//tname(iiq),itau_w,d_tr_cl(:,:,it))
     37        CALL histwrite_phy(nid_tra,.FALSE.,"d_tr_cl_"//tname(iiq),itau_w,d_tr_cl(:,:,it))
    3838     ENDDO
    3939!---------------
     
    4141!
    4242! VENT (niveau 1)   
    43      CALL histwrite_phy(nid_tra,"pyu1",itau_w,yu1)
    44      CALL histwrite_phy(nid_tra,"pyv1",itau_w,yv1)
     43     CALL histwrite_phy(nid_tra,.FALSE.,"pyu1",itau_w,yu1)
     44     CALL histwrite_phy(nid_tra,.FALSE.,"pyv1",itau_w,yv1)
    4545!
    4646! TEMPERATURE DU SOL
    4747     zx_tmp_fi2d(:)=ftsol(:,1)         
    48      CALL histwrite_phy(nid_tra,"ftsol1",itau_w,zx_tmp_fi2d)
     48     CALL histwrite_phy(nid_tra,.FALSE.,"ftsol1",itau_w,zx_tmp_fi2d)
    4949     zx_tmp_fi2d(:)=ftsol(:,2)
    50      CALL histwrite_phy(nid_tra,"ftsol2",itau_w,zx_tmp_fi2d)
     50     CALL histwrite_phy(nid_tra,.FALSE.,"ftsol2",itau_w,zx_tmp_fi2d)
    5151     zx_tmp_fi2d(:)=ftsol(:,3)
    52      CALL histwrite_phy(nid_tra,"ftsol3",itau_w,zx_tmp_fi2d)
     52     CALL histwrite_phy(nid_tra,.FALSE.,"ftsol3",itau_w,zx_tmp_fi2d)
    5353     zx_tmp_fi2d(:)=ftsol(:,4)
    54      CALL histwrite_phy(nid_tra,"ftsol4",itau_w,zx_tmp_fi2d)
     54     CALL histwrite_phy(nid_tra,.FALSE.,"ftsol4",itau_w,zx_tmp_fi2d)
    5555!     
    5656! NATURE DU SOL
    5757     zx_tmp_fi2d(:)=pctsrf(:,1)
    58      CALL histwrite_phy(nid_tra,"psrf1",itau_w,zx_tmp_fi2d)
     58     CALL histwrite_phy(nid_tra,.FALSE.,"psrf1",itau_w,zx_tmp_fi2d)
    5959     zx_tmp_fi2d(:)=pctsrf(:,2)
    60      CALL histwrite_phy(nid_tra,"psrf2",itau_w,zx_tmp_fi2d)
     60     CALL histwrite_phy(nid_tra,.FALSE.,"psrf2",itau_w,zx_tmp_fi2d)
    6161     zx_tmp_fi2d(:)=pctsrf(:,3)
    62      CALL histwrite_phy(nid_tra,"psrf3",itau_w,zx_tmp_fi2d)
     62     CALL histwrite_phy(nid_tra,.FALSE.,"psrf3",itau_w,zx_tmp_fi2d)
    6363     zx_tmp_fi2d(:)=pctsrf(:,4)
    64      CALL histwrite_phy(nid_tra,"psrf4",itau_w,zx_tmp_fi2d)
     64     CALL histwrite_phy(nid_tra,.FALSE.,"psrf4",itau_w,zx_tmp_fi2d)
    6565 
    6666! DIVERS   
    67      CALL histwrite_phy(nid_tra,"pplay",itau_w,pplay)     
    68      CALL histwrite_phy(nid_tra,"T",itau_w,t_seri)     
    69      CALL histwrite_phy(nid_tra,"mfu",itau_w,pmfu)
    70      CALL histwrite_phy(nid_tra,"mfd",itau_w,pmfd)
    71      CALL histwrite_phy(nid_tra,"en_u",itau_w,pen_u)
    72      CALL histwrite_phy(nid_tra,"en_d",itau_w,pen_d)
    73      CALL histwrite_phy(nid_tra,"de_d",itau_w,pde_d)
    74      CALL histwrite_phy(nid_tra,"de_u",itau_w,pde_u)
    75      CALL histwrite_phy(nid_tra,"coefh",itau_w,coefh)
     67     CALL histwrite_phy(nid_tra,.FALSE.,"pplay",itau_w,pplay)     
     68     CALL histwrite_phy(nid_tra,.FALSE.,"T",itau_w,t_seri)     
     69     CALL histwrite_phy(nid_tra,.FALSE.,"mfu",itau_w,pmfu)
     70     CALL histwrite_phy(nid_tra,.FALSE.,"mfd",itau_w,pmfd)
     71     CALL histwrite_phy(nid_tra,.FALSE.,"en_u",itau_w,pen_u)
     72     CALL histwrite_phy(nid_tra,.FALSE.,"en_d",itau_w,pen_d)
     73     CALL histwrite_phy(nid_tra,.FALSE.,"de_d",itau_w,pde_d)
     74     CALL histwrite_phy(nid_tra,.FALSE.,"de_u",itau_w,pde_u)
     75     CALL histwrite_phy(nid_tra,.FALSE.,"coefh",itau_w,coefh)
    7676
    7777     IF (ok_sync) THEN
     
    8181     ENDIF
    8282
    83   ENDIF !ecrit_tra>0. .AND. config_inca == 'none'
     83  ENDIF !ecrit_tra>0.
    8484
Note: See TracChangeset for help on using the changeset viewer.