Changeset 1534 for LMDZ4/branches


Ignore:
Timestamp:
Jun 3, 2011, 7:28:17 PM (13 years ago)
Author:
musat
Message:

Ajouts CFMIP2/CMIP5

  • 6eme fichier de sortie "stations" histstn.nc qui necessite 2 fichiers: PARAM/npCFMIP_param.data contenant le nombre de points (120 pour simulations AMIP, 73 pour aqua) PARAM/pointlocations.txt contenat le numero, les coordonnees (lon,lat) et le nom de chaque station
  • flag LOGICAL dans tous les appels histwrite_phy pour pouvoir sortir le fichier histstn.nc

NB: 1) les flags de type phys_ que l'on met dans le physiq.def_L* pour ajouter plus de sorties

necessitent dorenavant 6 valeurs, la 6eme correspondant au fichier histstn.nc

2) par defaut le fichier histstn.nc ne sort pas; pour le sortir ajouter les lignes suivantes

dans physiq.def_L*

### Type de fichier : global (n) ou stations (y)
phys_out_filestations = n n n n n y

  • introduction de 2 jeux de flags pour les taux des GES; taux actuels avec suffixes _act, taux futurs avec "_per" avec 2 appels au rayonnement si taux "_per" different des taux "_act" (utiles pour diags. CFMIP 4CO2)
  • flags "betaCRF" pour calculs CRF pour experiences sensibilite proprietes optiques eau liquide nuageuse avec initialisations par defaut; sinon besoin de fichier beta_crf.data

IM

Location:
LMDZ4/branches/LMDZ4_AR5/libf/phylmd
Files:
13 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4_AR5/libf/phylmd/clesphys.h

    r1500 r1534  
    1414       REAL co2_ppm, co2_ppm0, solaire
    1515       REAL(kind=8) RCO2, RCH4, RN2O, RCFC11, RCFC12 
     16       REAL(kind=8) RCO2_act, RCH4_act, RN2O_act, RCFC11_act, RCFC12_act 
    1617       REAL(kind=8) CH4_ppb, N2O_ppb, CFC11_ppt, CFC12_ppt
     18!IM ajout CFMIP2/CMIP5
     19       REAL co2_ppm_per
     20       REAL(kind=8) RCO2_per,RCH4_per,RN2O_per,RCFC11_per,RCFC12_per
     21       REAL(kind=8) CH4_ppb_per,N2O_ppb_per,CFC11_ppt_per,CFC12_ppt_per
    1722
    1823!OM ---> correction du bilan d'eau global
     
    7378       COMMON/clesphys/cycle_diurne, soil_model, new_oliq,              &
    7479     &     ok_orodr, ok_orolf, ok_limitvrai, nbapp_rad, iflag_con       &
    75      &     , co2_ppm, solaire, RCO2, RCH4, RN2O, RCFC11, RCFC12         &
     80     &     , co2_ppm, solaire                                           &
     81     &     , RCO2, RCH4, RN2O, RCFC11, RCFC12                           &
     82     &     , RCO2_act, RCH4_act, RN2O_act, RCFC11_act, RCFC12_act       &
     83     &     , RCO2_per, RCH4_per, RN2O_per, RCFC11_per, RCFC12_per       &
    7684     &     , CH4_ppb, N2O_ppb, CFC11_ppt, CFC12_ppt                     &
     85     &     , CH4_ppb_per, N2O_ppb_per, CFC11_ppt_per, CFC12_ppt_per     &
    7786     &     , top_height, overlap, cdmmax, cdhmax, ksta, ksta_ter        &
    7887     &     , ok_kzmin, fmagic, pmagic                                   &
  • LMDZ4/branches/LMDZ4_AR5/libf/phylmd/conf_phys.F90

    r1500 r1534  
    117117  real, save :: scut_omp, qqa1_omp, qqa2_omp, gammas_omp, Fmax_omp, alphas_omp
    118118
    119   REAL,SAVE :: R_ecc_omp,R_peri_omp,R_incl_omp,solaire_omp,co2_ppm_omp
    120   REAL,SAVE :: RCO2_omp,CH4_ppb_omp,RCH4_omp,N2O_ppb_omp,RN2O_omp,CFC11_ppt_omp
    121   REAL,SAVE :: RCFC11_omp,CFC12_ppt_omp,RCFC12_omp,epmax_omp
     119  REAL,SAVE :: R_ecc_omp,R_peri_omp,R_incl_omp,solaire_omp
     120  REAL,SAVE :: co2_ppm_omp, RCO2_omp, co2_ppm_per_omp, RCO2_per_omp
     121  REAL,SAVE :: CH4_ppb_omp, RCH4_omp, CH4_ppb_per_omp, RCH4_per_omp
     122  REAL,SAVE :: N2O_ppb_omp, RN2O_omp, N2O_ppb_per_omp, RN2O_per_omp
     123  REAL,SAVE :: CFC11_ppt_omp,RCFC11_omp,CFC11_ppt_per_omp,RCFC11_per_omp
     124  REAL,SAVE :: CFC12_ppt_omp,RCFC12_omp,CFC12_ppt_per_omp,RCFC12_per_omp
     125  REAL,SAVE :: epmax_omp
    122126  LOGICAL,SAVE :: ok_adj_ema_omp
    123127  INTEGER,SAVE :: iflag_clw_omp
     
    495499!OK call getin('RCFC12', RCFC12)
    496500
    497 
     501!ajout CFMIP begin
     502!!
     503!Config Key  = co2_ppm_per
     504!Config Desc = concentration du co2_ppm_per
     505!Config Def  = 348.
     506!Config Help =
     507!               
     508  co2_ppm_per_omp = co2_ppm_omp
     509  call getin('co2_ppm_per', co2_ppm_per_omp)
     510!!
     511!Config Key  = RCO2_per
     512!Config Desc = Concentration du CO2_per
     513!Config Def  = co2_ppm_per * 1.0e-06  * 44.011/28.97
     514!Config Def  = 348. * 1.0e-06  * 44.011/28.97
     515!Config Help =
     516!               
     517  RCO2_per_omp = co2_ppm_per_omp * 1.0e-06  * 44.011/28.97
     518
     519!Config Key  = RCH4_per
     520!Config Desc = Concentration du CH4_per
     521!Config Def  = 1.65E-06* 16.043/28.97
     522!Config Help =
     523!               
     524  zzz = CH4_ppb_omp
     525  call getin('CH4_ppb_per', zzz)
     526  CH4_ppb_per_omp = zzz
     527  RCH4_per_omp = CH4_ppb_per_omp * 1.0E-09 * 16.043/28.97
     528!!
     529!Config Key  = RN2O_per
     530!Config Desc = Concentration du N2O_per
     531!Config Def  = 306.E-09* 44.013/28.97
     532!Config Help =
     533!               
     534  zzz = N2O_ppb_omp
     535  call getin('N2O_ppb_per', zzz)
     536  N2O_ppb_per_omp = zzz
     537  RN2O_per_omp = N2O_ppb_per_omp * 1.0E-09 * 44.013/28.97
     538!!
     539!Config Key  = RCFC11_per
     540!Config Desc = Concentration du CFC11_per
     541!Config Def  = 280.E-12* 137.3686/28.97
     542!Config Help =
     543!               
     544  zzz = CFC11_ppt_omp
     545  call getin('CFC11_ppt_per',zzz)
     546  CFC11_ppt_per_omp = zzz
     547  RCFC11_per_omp=CFC11_ppt_per_omp* 1.0E-12 * 137.3686/28.97
     548!!
     549!Config Key  = RCFC12_per
     550!Config Desc = Concentration du CFC12_per
     551!Config Def  = 484.E-12* 120.9140/28.97
     552!Config Help =
     553!               
     554  zzz = CFC12_ppt_omp
     555  call getin('CFC12_ppt_per',zzz)
     556  CFC12_ppt_per_omp = zzz
     557  RCFC12_per_omp = CFC12_ppt_per_omp * 1.0E-12 * 120.9140/28.97
     558!ajout CFMIP end
    498559
    499560!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    11831244
    11841245!
    1185 !Config Key  = ok_hfCOSP
     1246!Config Key  = ok_precip_fonte
    11861247!Config Desc =
    11871248!Config Def  = .false.
     
    14521513    CFC12_ppt = CFC12_ppt_omp
    14531514    RCFC12 = RCFC12_omp
    1454 
     1515    RCO2_act = RCO2
     1516    RCH4_act = RCH4
     1517    RN2O_act = RN2O
     1518    RCFC11_act = RCFC11
     1519    RCFC12_act = RCFC12
     1520    RCO2_per = RCO2_per_omp
     1521    RCH4_per = RCH4_per_omp
     1522    RN2O_per = RN2O_per_omp
     1523    RCFC11_per = RCFC11_per_omp
     1524    RCFC12_per = RCFC12_per_omp
     1525   
    14551526    cycle_diurne = cycle_diurne_omp
    14561527    soil_model = soil_model_omp
     
    16231694  write(numout,*)' Constante solaire =',solaire
    16241695  write(numout,*)' co2_ppm =',co2_ppm
    1625   write(numout,*)' RCO2 = ',RCO2
    1626   write(numout,*)' CH4_ppb =',CH4_ppb,' RCH4 = ',RCH4
    1627   write(numout,*)' N2O_ppb =',N2O_ppb,' RN2O =  ',RN2O
    1628   write(numout,*)' CFC11_ppt=',CFC11_ppt,' RCFC11 =  ',RCFC11
    1629   write(numout,*)' CFC12_ppt=',CFC12_ppt,' RCFC12 =  ',RCFC12
     1696  write(numout,*)' RCO2_act = ',RCO2_act
     1697  write(numout,*)' CH4_ppb =',CH4_ppb,' RCH4_act = ',RCH4_act
     1698  write(numout,*)' N2O_ppb =',N2O_ppb,' RN2O_act=  ',RN2O_act
     1699  write(numout,*)' CFC11_ppt=',CFC11_ppt,' RCFC11_act=  ',RCFC11_act
     1700  write(numout,*)' CFC12_ppt=',CFC12_ppt,' RCFC12_act=  ',RCFC12_act
     1701  write(numout,*)' RCO2_per = ',RCO2_per,' RCH4_per = ', RCH4_per
     1702  write(numout,*)' RN2O_per = ',RN2O_per,' RCFC11_per = ', RCFC11_per
     1703  write(numout,*)' RCFC12_per = ',RCFC12_per
    16301704  write(numout,*)' cvl_corr=', cvl_corr
    16311705  write(numout,*)'ok_lic_melt=', ok_lic_melt
  • LMDZ4/branches/LMDZ4_AR5/libf/phylmd/iophy.F90

    r1331 r1534  
    99  REAL,allocatable,dimension(:),save :: io_lon
    1010  INTEGER, save :: phys_domain_id
     11  INTEGER, save :: npstn
     12  INTEGER, allocatable, dimension(:), save :: nptabij
    1113 
    1214  INTERFACE histwrite_phy
    1315    MODULE PROCEDURE histwrite2d_phy,histwrite3d_phy
     16  END INTERFACE
     17
     18  INTERFACE histbeg_phy_all
     19    MODULE PROCEDURE histbeg_phy,histbeg_phy_points
    1420  END INTERFACE
    1521
     
    144150 
    145151  end subroutine histbeg_phy
    146  
    147   subroutine histwrite2d_phy(nid,name,itau,field)
     152
     153  subroutine histbeg_phy_points(rlon,rlat,pim,tabij,ipt,jpt, &
     154             plon,plat,plon_bounds,plat_bounds, &
     155             nname,itau0,zjulian,dtime,nnhori,nnid_day)
     156  USE dimphy
     157  USE mod_phys_lmdz_para
     158  USE mod_grid_phy_lmdz
     159  use ioipsl
     160  use write_field
     161  implicit none
     162  include 'dimensions.h'
     163
     164    real,dimension(klon),intent(in) :: rlon
     165    real,dimension(klon),intent(in) :: rlat
     166    integer, intent(in) :: itau0
     167    real,intent(in) :: zjulian
     168    real,intent(in) :: dtime
     169    integer, intent(in) :: pim
     170    integer, intent(out) :: nnhori
     171    character(len=20), intent(in) :: nname
     172    INTEGER, intent(out) :: nnid_day
     173    integer :: i
     174    REAL,dimension(klon_glo)        :: rlat_glo
     175    REAL,dimension(klon_glo)        :: rlon_glo
     176    INTEGER, DIMENSION(pim), intent(in)  :: tabij
     177    REAL,dimension(pim), intent(in) :: plat, plon
     178    INTEGER,dimension(pim), intent(in) :: ipt, jpt
     179    REAL,dimension(pim,2), intent(out) :: plat_bounds, plon_bounds
     180
     181    INTEGER, SAVE :: tabprocbeg, tabprocend
     182!$OMP THREADPRIVATE(tabprocbeg, tabprocend)
     183    INTEGER :: ip
     184    INTEGER, PARAMETER :: nip=1
     185    INTEGER :: npproc
     186    REAL, allocatable, dimension(:) :: npplat, npplon
     187    REAL, allocatable, dimension(:,:) :: npplat_bounds, npplon_bounds
     188    INTEGER, PARAMETER :: jjmp1=jjm+1-1/jjm
     189    REAL, dimension(iim,jjmp1) :: zx_lon, zx_lat
     190
     191    CALL gather(rlat,rlat_glo)
     192    CALL bcast(rlat_glo)
     193    CALL gather(rlon,rlon_glo)
     194    CALL bcast(rlon_glo)
     195
     196!$OMP MASTER
     197    DO i=1,pim
     198
     199!    print*,'CFMIP_iophy i tabij lon lat',i,tabij(i),plon(i),plat(i)
     200
     201     plon_bounds(i,1)=rlon_glo(tabij(i)-1)
     202     plon_bounds(i,2)=rlon_glo(tabij(i)+1)
     203     if(plon_bounds(i,2).LE.0..AND.plon_bounds(i,1).GE.0.) THEN
     204      if(rlon_glo(tabij(i)).GE.0.) THEN
     205       plon_bounds(i,2)=-1*plon_bounds(i,2)
     206      endif
     207     endif
     208     if(plon_bounds(i,2).GE.0..AND.plon_bounds(i,1).LE.0.) THEN
     209      if(rlon_glo(tabij(i)).LE.0.) THEN
     210       plon_bounds(i,2)=-1*plon_bounds(i,2)
     211      endif
     212     endif
     213!
     214     IF ( tabij(i).LE.iim) THEN
     215      plat_bounds(i,1)=rlat_glo(tabij(i))
     216     ELSE
     217      plat_bounds(i,1)=rlat_glo(tabij(i)-iim)
     218     ENDIF
     219     plat_bounds(i,2)=rlat_glo(tabij(i)+iim)
     220!
     221!    print*,'CFMIP_iophy point i lon lon_bds',i,plon_bounds(i,1),rlon_glo(tabij(i)),plon_bounds(i,2)
     222!    print*,'CFMIP_iophy point i lat lat_bds',i,plat_bounds(i,1),rlat_glo(tabij(i)),plat_bounds(i,2)
     223!
     224    ENDDO
     225    if (is_sequential) then
     226
     227     npstn=pim
     228     IF(.NOT. ALLOCATED(nptabij)) THEN
     229      ALLOCATE(nptabij(pim))
     230     ENDIF
     231     DO i=1,pim
     232      nptabij(i)=tabij(i)
     233     ENDDO
     234
     235       CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlon_glo,zx_lon)
     236       if (iim.gt.1) then
     237       DO i = 1, iim
     238         zx_lon(i,1) = rlon_glo(i+1)
     239         zx_lon(i,jjmp1) = rlon_glo(i+1)
     240       ENDDO
     241       endif
     242       CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlat_glo,zx_lat)
     243
     244    DO i=1,pim
     245!    print*,'CFMIP_iophy i tabij lon lat',i,tabij(i),plon(i),plat(i)
     246
     247     plon_bounds(i,1)=zx_lon(ipt(i)-1,jpt(i))
     248     plon_bounds(i,2)=zx_lon(ipt(i)+1,jpt(i))
     249
     250     if (ipt(i).EQ.1) then
     251      plon_bounds(i,1)=zx_lon(iim,jpt(i))
     252      plon_bounds(i,2)=360.+zx_lon(ipt(i)+1,jpt(i))
     253     endif
     254 
     255     if (ipt(i).EQ.iim) then
     256      plon_bounds(i,2)=360.+zx_lon(1,jpt(i))
     257     endif
     258
     259     plat_bounds(i,1)=zx_lat(ipt(i),jpt(i)-1)
     260     plat_bounds(i,2)=zx_lat(ipt(i),jpt(i)+1)
     261
     262     if (jpt(i).EQ.1) then
     263      plat_bounds(i,1)=zx_lat(ipt(i),1)+0.001
     264      plat_bounds(i,2)=zx_lat(ipt(i),1)-0.001
     265     endif
     266 
     267     if (jpt(i).EQ.jjmp1) then
     268      plat_bounds(i,1)=zx_lat(ipt(i),jjmp1)+0.001
     269      plat_bounds(i,2)=zx_lat(ipt(i),jjmp1)-0.001
     270     endif
     271!
     272!    print*,'CFMIP_iophy point i lon lon_bds',i,plon_bounds(i,1),rlon(tabij(i)),plon_bounds(i,2)
     273!    print*,'CFMIP_iophy point i lat lat_bds',i,plat_bounds(i,1),rlat(tabij(i)),plat_bounds(i,2)
     274!
     275    ENDDO
     276!    print*,'iophy is_sequential nname, nnhori, nnid_day=',trim(nname),nnhori,nnid_day
     277     call histbeg(nname,pim,plon,plon_bounds, &
     278                           plat,plat_bounds, &
     279                           itau0, zjulian, dtime, nnhori, nnid_day)
     280    else
     281     npproc=0
     282     DO ip=1, pim
     283      tabprocbeg=klon_mpi_begin
     284      tabprocend=klon_mpi_end
     285      IF(tabij(ip).GE.tabprocbeg.AND.tabij(ip).LE.tabprocend) THEN
     286       npproc=npproc+1
     287       npstn=npproc
     288      ENDIF
     289     ENDDO
     290!    print*,'CFMIP_iophy mpi_rank npstn',mpi_rank,npstn
     291     IF(.NOT. ALLOCATED(nptabij)) THEN
     292      ALLOCATE(nptabij(npstn))
     293      ALLOCATE(npplon(npstn), npplat(npstn))
     294      ALLOCATE(npplon_bounds(npstn,2), npplat_bounds(npstn,2))
     295     ENDIF
     296     npproc=0
     297     DO ip=1, pim
     298      IF(tabij(ip).GE.tabprocbeg.AND.tabij(ip).LE.tabprocend) THEN
     299       npproc=npproc+1
     300       nptabij(npproc)=tabij(ip)
     301!      print*,'mpi_rank npproc ip plon plat tabij=',mpi_rank,npproc,ip, &
     302!      plon(ip),plat(ip),tabij(ip)
     303       npplon(npproc)=plon(ip)
     304       npplat(npproc)=plat(ip)
     305       npplon_bounds(npproc,1)=plon_bounds(ip,1)
     306       npplon_bounds(npproc,2)=plon_bounds(ip,2)
     307       npplat_bounds(npproc,1)=plat_bounds(ip,1)
     308       npplat_bounds(npproc,2)=plat_bounds(ip,2)
     309!!!
     310!!! print qui sert a reordonner les points stations selon l'ordre CFMIP
     311!!! ne pas enlever
     312        print*,'iophy_mpi rank ip lon lat',mpi_rank,ip,plon(ip),plat(ip)
     313!!!
     314      ENDIF
     315     ENDDO
     316     call histbeg(nname,npstn,npplon,npplon_bounds, &
     317                            npplat,npplat_bounds, &
     318                            itau0,zjulian,dtime,nnhori,nnid_day,phys_domain_id)
     319    endif
     320!$OMP END MASTER
     321
     322  end subroutine histbeg_phy_points
     323 
     324  subroutine histwrite2d_phy(nid,lpoint,name,itau,field)
    148325  USE dimphy
    149326  USE mod_phys_lmdz_para
     
    153330   
    154331    integer,intent(in) :: nid
     332    logical,intent(in) :: lpoint
    155333    character*(*), intent(IN) :: name
    156334    integer, intent(in) :: itau
    157335    real,dimension(:),intent(in) :: field
    158336    REAL,dimension(klon_mpi) :: buffer_omp
    159     INTEGER :: index2d(iim*jj_nb)
     337    INTEGER, allocatable, dimension(:) :: index2d
    160338    REAL :: Field2d(iim,jj_nb)
     339
     340    integer :: ip
     341    real,allocatable,dimension(:) :: fieldok
    161342
    162343    IF (size(field)/=klon) CALL abort_gcm('iophy::histwrite2d','Field first dimension not equal to klon',1)
     
    165346!$OMP MASTER
    166347    CALL grid1Dto2D_mpi(buffer_omp,Field2d)
    167     CALL histwrite(nid,name,itau,Field2d,iim*jj_nb,index2d)
     348    if(.NOT.lpoint) THEN
     349     ALLOCATE(index2d(iim*jj_nb))
     350     ALLOCATE(fieldok(iim*jj_nb))
     351     CALL histwrite(nid,name,itau,Field2d,iim*jj_nb,index2d)
     352    else
     353     ALLOCATE(fieldok(npstn))
     354     ALLOCATE(index2d(npstn))
     355
     356     if(is_sequential) then
     357!     klon_mpi_begin=1
     358!     klon_mpi_end=klon
     359      DO ip=1, npstn
     360       fieldok(ip)=buffer_omp(nptabij(ip))
     361      ENDDO
     362     else
     363      DO ip=1, npstn
     364!     print*,'histwrite2d is_sequential npstn ip name nptabij',npstn,ip,name,nptabij(ip)
     365       IF(nptabij(ip).GE.klon_mpi_begin.AND. &
     366          nptabij(ip).LE.klon_mpi_end) THEN
     367         fieldok(ip)=buffer_omp(nptabij(ip)-klon_mpi_begin+1)
     368       ENDIF
     369      ENDDO
     370     endif
     371     CALL histwrite(nid,name,itau,fieldok,npstn,index2d)
     372!
     373    endif
     374    deallocate(index2d)
     375    deallocate(fieldok)
    168376!$OMP END MASTER   
    169377  end subroutine histwrite2d_phy
    170378
    171 
    172  
    173   subroutine histwrite3d_phy(nid,name,itau,field)
     379  subroutine histwrite3d_phy(nid,lpoint,name,itau,field)
    174380  USE dimphy
    175381  USE mod_phys_lmdz_para
     
    180386   
    181387    integer,intent(in) :: nid
     388    logical,intent(in) :: lpoint
    182389    character*(*), intent(IN) :: name
    183390    integer, intent(in) :: itau
    184391    real,dimension(:,:),intent(in) :: field  ! --> field(klon,:)
    185392    REAL,dimension(klon_mpi,size(field,2)) :: buffer_omp
    186     INTEGER :: nlev
    187     INTEGER :: index3d(iim*jj_nb*size(field,2))
    188393    REAL :: Field3d(iim,jj_nb,size(field,2))
    189    
     394    INTEGER :: ip, n, nlev
     395    INTEGER, ALLOCATABLE, dimension(:) :: index3d
     396    real,allocatable, dimension(:,:) :: fieldok
     397
    190398    IF (size(field,1)/=klon) CALL abort_gcm('iophy::histwrite3d','Field first dimension not equal to klon',1)
    191399    nlev=size(field,2)
    192    
     400
     401!   print*,'hist3d_phy mpi_rank npstn=',mpi_rank,npstn
     402
     403!   DO ip=1, npstn
     404!    print*,'hist3d_phy mpi_rank nptabij',mpi_rank,nptabij(ip)
     405!   ENDDO
     406
    193407    CALL Gather_omp(field,buffer_omp)
    194408!$OMP MASTER
    195409    CALL grid1Dto2D_mpi(buffer_omp,field3d)
    196     CALL histwrite(nid,name,itau,Field3d,iim*jj_nb*nlev,index3d)
     410    if(.NOT.lpoint) THEN
     411     ALLOCATE(index3d(iim*jj_nb*nlev))
     412     ALLOCATE(fieldok(iim*jj_nb,nlev))
     413     CALL histwrite(nid,name,itau,Field3d,iim*jj_nb*nlev,index3d)
     414    else
     415      nlev=size(field,2)
     416      ALLOCATE(index3d(npstn*nlev))
     417      ALLOCATE(fieldok(npstn,nlev))
     418
     419      if(is_sequential) then
     420!      klon_mpi_begin=1
     421!      klon_mpi_end=klon
     422       DO n=1, nlev
     423       DO ip=1, npstn
     424        fieldok(ip,n)=buffer_omp(nptabij(ip),n)
     425       ENDDO
     426       ENDDO
     427      else
     428       DO n=1, nlev
     429       DO ip=1, npstn
     430        IF(nptabij(ip).GE.klon_mpi_begin.AND. &
     431         nptabij(ip).LE.klon_mpi_end) THEN
     432         fieldok(ip,n)=buffer_omp(nptabij(ip)-klon_mpi_begin+1,n)
     433        ENDIF
     434       ENDDO
     435       ENDDO
     436      endif
     437      CALL histwrite(nid,name,itau,fieldok,npstn*nlev,index3d)
     438    endif
     439  deallocate(index3d)
     440  deallocate(fieldok)
    197441!$OMP END MASTER   
    198442  end subroutine histwrite3d_phy
    199443 
    200  
    201 
    202444end module iophy
  • LMDZ4/branches/LMDZ4_AR5/libf/phylmd/pbl_surface_mod.F90

    r1282 r1534  
    175175       zxtsol,    zxfluxlat, zt2m,     qsat2m,        &
    176176       d_t,       d_q,       d_u,      d_v,           &
    177        zcoefh,    slab_wfbils,                        &
     177       zcoefh,    zcoefm,    slab_wfbils,             &
    178178       qsol_d,    zq2m,      s_pblh,   s_plcl,        &
    179179       s_capCL,   s_oliqCL,  s_cteiCL, s_pblT,        &
     
    312312    REAL, DIMENSION(klon, klev),  INTENT(OUT)       :: d_v        ! change in v speed
    313313    REAL, DIMENSION(klon, klev),  INTENT(OUT)       :: zcoefh     ! coef for turbulent diffusion of T and Q, mean for each grid point
     314    REAL, DIMENSION(klon, klev),  INTENT(OUT)       :: zcoefm     ! coef for turbulent diffusion of U and V (?), mean for each grid point
    314315
    315316! Output only for diagnostics
     
    546547    zcoefh(:,:) = 0.0
    547548    zcoefh(:,1) = 999999. ! zcoefh(:,k=1) should never be used
     549    zcoefm(:,:) = 0.0
     550    zcoefm(:,1) = 999999. !
    548551    ytsoil = 999999.
    549552
     
    970973             i = ni(j)
    971974             zcoefh(i,k) = zcoefh(i,k) + ycoefh(j,k)*ypct(j)
     975             zcoefm(i,k) = zcoefm(i,k) + ycoefm(j,k)*ypct(j)
    972976          END DO
    973977       END DO
  • LMDZ4/branches/LMDZ4_AR5/libf/phylmd/phys_local_var_mod.F90

    r1337 r1534  
    163163      !$OMP THREADPRIVATE(load_tmp7)
    164164
     165!IM ajout variables CFMIP2/CMIP5
     166      REAL,ALLOCATABLE,SAVE :: topswad_aerop(:), solswad_aerop(:)
     167!$OMP THREADPRIVATE(topswad_aerop, solswad_aerop)
     168      REAL,ALLOCATABLE,SAVE :: topswai_aerop(:), solswai_aerop(:)
     169!$OMP THREADPRIVATE(topswai_aerop, solswai_aerop)
     170      REAL,ALLOCATABLE,SAVE :: topswad0_aerop(:), solswad0_aerop(:)
     171!$OMP THREADPRIVATE(topswad0_aerop, solswad0_aerop)
     172      REAL,ALLOCATABLE,SAVE :: topsw_aerop(:,:), topsw0_aerop(:,:) 
     173!$OMP THREADPRIVATE(topsw_aerop, topsw0_aerop)
     174      REAL,ALLOCATABLE,SAVE :: solsw_aerop(:,:), solsw0_aerop(:,:)
     175!$OMP THREADPRIVATE(solsw_aerop, solsw0_aerop)
     176      REAL,ALLOCATABLE,SAVE :: topswcf_aerop(:,:), solswcf_aerop(:,:)
     177!$OMP THREADPRIVATE(topswcf_aerop, solswcf_aerop)
     178
    165179CONTAINS
    166180
     
    243257      allocate(load_tmp7(klon))
    244258
     259!IM ajout variables CFMIP2/CMIP5
     260      ALLOCATE(topswad_aerop(klon), solswad_aerop(klon))
     261      ALLOCATE(topswai_aerop(klon), solswai_aerop(klon))
     262      ALLOCATE(topswad0_aerop(klon), solswad0_aerop(klon))
     263      ALLOCATE(topsw_aerop(klon,naero_grp), topsw0_aerop(klon,naero_grp))
     264      ALLOCATE(solsw_aerop(klon,naero_grp), solsw0_aerop(klon,naero_grp))
     265      ALLOCATE(topswcf_aerop(klon,naero_grp), solswcf_aerop(klon,naero_grp))
     266
    245267END SUBROUTINE phys_local_var_init
    246268
     
    320342      deallocate(d_u_hin,d_v_hin,d_t_hin)
    321343
     344!IM ajout variables CFMIP2/CMIP5
     345      deallocate(topswad_aerop, solswad_aerop)
     346      deallocate(topswai_aerop, solswai_aerop)
     347      deallocate(topswad0_aerop, solswad0_aerop)
     348      deallocate(topsw_aerop, topsw0_aerop)
     349      deallocate(solsw_aerop, solsw0_aerop)
     350      deallocate(topswcf_aerop, solswcf_aerop)
     351
    322352END SUBROUTINE phys_local_var_end
    323353
  • LMDZ4/branches/LMDZ4_AR5/libf/phylmd/phys_output_mod.F90

    r1419 r1534  
    1717
    1818
    19    integer, parameter                           :: nfiles = 5
     19   integer, parameter                           :: nfiles = 6
    2020   logical, dimension(nfiles), save             :: clef_files
     21   logical, dimension(nfiles), save             :: clef_stations
    2122   integer, dimension(nfiles), save             :: lev_files
    2223   integer, dimension(nfiles), save             :: nid_files
    23 !!$OMP THREADPRIVATE(clef_files, lev_files,nid_files)
     24   integer, dimension(nfiles), save  :: nnid_files
     25!!$OMP THREADPRIVATE(clef_files, clef_stations, lev_files,nid_files,nnid_files)
     26   integer, dimension(nfiles), private, save :: nnhorim
    2427 
    2528   integer, dimension(nfiles), private, save :: nhorim, nvertm
     
    4245
    4346  TYPE ctrl_out
    44    integer,dimension(5) :: flag
     47   integer,dimension(6) :: flag
    4548   character(len=20)     :: name
    4649  END TYPE ctrl_out
     
    4851!!! Comosentes de la coordonnee sigma-hybride
    4952!!! Ap et Bp
    50   type(ctrl_out),save :: o_Ahyb         = ctrl_out((/ 1, 1, 1, 1, 1 /), 'Ap')
    51   type(ctrl_out),save :: o_Bhyb         = ctrl_out((/ 1, 1, 1, 1, 1 /), 'Bp')
    52   type(ctrl_out),save :: o_Alt          = ctrl_out((/ 1, 1, 1, 1, 1 /), 'Alt')
     53  type(ctrl_out),save :: o_Ahyb         = ctrl_out((/ 1, 1, 1, 1, 1, 1 /), 'Ap')
     54  type(ctrl_out),save :: o_Bhyb         = ctrl_out((/ 1, 1, 1, 1, 1, 1 /), 'Bp')
     55  type(ctrl_out),save :: o_Alt          = ctrl_out((/ 1, 1, 1, 1, 1, 1 /), 'Alt')
    5356
    5457!!! 1D
    55   type(ctrl_out),save :: o_phis         = ctrl_out((/ 1, 1, 10, 5, 1 /), 'phis')
    56   type(ctrl_out),save :: o_aire         = ctrl_out((/ 1, 1, 10,  10, 1 /),'aire')
    57   type(ctrl_out),save :: o_contfracATM  = ctrl_out((/ 10, 1,  1, 10, 10 /),'contfracATM')
    58   type(ctrl_out),save :: o_contfracOR   = ctrl_out((/ 10, 1,  1, 10, 10 /),'contfracOR')
    59   type(ctrl_out),save :: o_aireTER      = ctrl_out((/ 10, 10, 1, 10, 10 /),'aireTER')
     58  type(ctrl_out),save :: o_phis         = ctrl_out((/ 1, 1, 10, 5, 1, 1 /), 'phis')
     59  type(ctrl_out),save :: o_aire         = ctrl_out((/ 1, 1, 10,  10, 1, 1 /),'aire')
     60  type(ctrl_out),save :: o_contfracATM  = ctrl_out((/ 10, 1,  1, 10, 10, 10 /),'contfracATM')
     61  type(ctrl_out),save :: o_contfracOR   = ctrl_out((/ 10, 1,  1, 10, 10, 10 /),'contfracOR')
     62  type(ctrl_out),save :: o_aireTER      = ctrl_out((/ 10, 10, 1, 10, 10, 10 /),'aireTER')
    6063 
    6164!!! 2D
    62   type(ctrl_out),save :: o_flat         = ctrl_out((/ 5, 1, 10, 10, 5 /),'flat')
    63   type(ctrl_out),save :: o_slp          = ctrl_out((/ 1, 1, 1, 10, 10 /),'slp')
    64   type(ctrl_out),save :: o_tsol         = ctrl_out((/ 1, 1, 1, 5, 10 /),'tsol')
    65   type(ctrl_out),save :: o_t2m          = ctrl_out((/ 1, 1, 1, 5, 10 /),'t2m')
    66   type(ctrl_out),save :: o_t2m_min      = ctrl_out((/ 1, 1, 10, 10, 10 /),'t2m_min')
    67   type(ctrl_out),save :: o_t2m_max      = ctrl_out((/ 1, 1, 10, 10, 10 /),'t2m_max')
    68   type(ctrl_out),save,dimension(4) :: o_t2m_srf      = (/ ctrl_out((/ 10, 6, 10, 10, 10 /),'t2m_ter'), &
    69                                                  ctrl_out((/ 10, 6, 10, 10, 10 /),'t2m_lic'), &
    70                                                  ctrl_out((/ 10, 6, 10, 10, 10 /),'t2m_oce'), &
    71                                                  ctrl_out((/ 10, 6, 10, 10, 10 /),'t2m_sic') /)
    72 
    73   type(ctrl_out),save :: o_wind10m      = ctrl_out((/ 1, 1, 1, 10, 10 /),'wind10m')
    74   type(ctrl_out),save :: o_wind10max    = ctrl_out((/ 10, 1, 10, 10, 10 /),'wind10max')
    75   type(ctrl_out),save :: o_sicf         = ctrl_out((/ 1, 1, 10, 10, 10 /),'sicf')
    76   type(ctrl_out),save :: o_q2m          = ctrl_out((/ 1, 1, 1, 5, 10 /),'q2m')
    77   type(ctrl_out),save :: o_u10m         = ctrl_out((/ 1, 1, 1, 5, 10 /),'u10m')
    78   type(ctrl_out),save :: o_v10m         = ctrl_out((/ 1, 1, 1, 5, 10 /),'v10m')
    79   type(ctrl_out),save :: o_psol         = ctrl_out((/ 1, 1, 1, 5, 10 /),'psol')
    80   type(ctrl_out),save :: o_qsurf        = ctrl_out((/ 1, 10, 10, 10, 10 /),'qsurf')
    81 
    82   type(ctrl_out),save,dimension(4) :: o_u10m_srf     = (/ ctrl_out((/ 10, 6, 10, 10, 10 /),'u10m_ter'), &
    83                                               ctrl_out((/ 10, 6, 10, 10, 10 /),'u10m_lic'), &
    84                                               ctrl_out((/ 10, 6, 10, 10, 10 /),'u10m_oce'), &
    85                                               ctrl_out((/ 10, 6, 10, 10, 10 /),'u10m_sic') /)
    86 
    87   type(ctrl_out),save,dimension(4) :: o_v10m_srf     = (/ ctrl_out((/ 10, 6, 10, 10, 10 /),'v10m_ter'), &
    88                                               ctrl_out((/ 10, 6, 10, 10, 10 /),'v10m_lic'), &
    89                                               ctrl_out((/ 10, 6, 10, 10, 10 /),'v10m_oce'), &
    90                                               ctrl_out((/ 10, 6, 10, 10, 10 /),'v10m_sic') /)
    91 
    92   type(ctrl_out),save :: o_qsol         = ctrl_out((/ 1, 10, 10, 10, 10 /),'qsol')
    93 
    94   type(ctrl_out),save :: o_ndayrain     = ctrl_out((/ 1, 10, 10, 10, 10 /),'ndayrain')
    95   type(ctrl_out),save :: o_precip       = ctrl_out((/ 1, 1, 1, 10, 5 /),'precip')
    96   type(ctrl_out),save :: o_plul         = ctrl_out((/ 1, 1, 1, 10, 10 /),'plul')
    97 
    98   type(ctrl_out),save :: o_pluc         = ctrl_out((/ 1, 1, 1, 10, 5 /),'pluc')
    99   type(ctrl_out),save :: o_snow         = ctrl_out((/ 1, 1, 10, 10, 5 /),'snow')
    100   type(ctrl_out),save :: o_evap         = ctrl_out((/ 1, 1, 10, 10, 10 /),'evap')
    101   type(ctrl_out),save,dimension(4) :: o_evap_srf     = (/ ctrl_out((/ 1, 6, 10, 10, 10 /),'evap_ter'), &
    102                                            ctrl_out((/ 1, 6, 10, 10, 10 /),'evap_lic'), &
    103                                            ctrl_out((/ 1, 6, 10, 10, 10 /),'evap_oce'), &
    104                                            ctrl_out((/ 1, 6, 10, 10, 10 /),'evap_sic') /)
    105   type(ctrl_out),save :: o_msnow       = ctrl_out((/ 1, 10, 10, 10, 10 /),'msnow')
    106   type(ctrl_out),save :: o_fsnow       = ctrl_out((/ 1, 10, 10, 10, 10 /),'fsnow')
    107 
    108   type(ctrl_out),save :: o_tops         = ctrl_out((/ 1, 1, 10, 10, 10 /),'tops')
    109   type(ctrl_out),save :: o_tops0        = ctrl_out((/ 1, 5, 10, 10, 10 /),'tops0')
    110   type(ctrl_out),save :: o_topl         = ctrl_out((/ 1, 1, 10, 5, 10 /),'topl')
    111   type(ctrl_out),save :: o_topl0        = ctrl_out((/ 1, 5, 10, 10, 10 /),'topl0')
    112   type(ctrl_out),save :: o_SWupTOA      = ctrl_out((/ 1, 4, 10, 10, 10 /),'SWupTOA')
    113   type(ctrl_out),save :: o_SWupTOAclr   = ctrl_out((/ 1, 4, 10, 10, 10 /),'SWupTOAclr')
    114   type(ctrl_out),save :: o_SWdnTOA      = ctrl_out((/ 1, 4, 10, 10, 10 /),'SWdnTOA')
    115   type(ctrl_out),save :: o_SWdnTOAclr   = ctrl_out((/ 1, 4, 10, 10, 10 /),'SWdnTOAclr')
    116   type(ctrl_out),save :: o_nettop       = ctrl_out((/ 1, 4, 10, 10, 10 /),'nettop')
    117 
    118   type(ctrl_out),save :: o_SWup200      = ctrl_out((/ 1, 10, 10, 10, 10 /),'SWup200')
    119   type(ctrl_out),save :: o_SWup200clr   = ctrl_out((/ 10, 1, 10, 10, 10 /),'SWup200clr')
    120   type(ctrl_out),save :: o_SWdn200      = ctrl_out((/ 1, 10, 10, 10, 10 /),'SWdn200')
    121   type(ctrl_out),save :: o_SWdn200clr   = ctrl_out((/ 10, 1, 10, 10, 10 /),'SWdn200clr')
     65  type(ctrl_out),save :: o_flat         = ctrl_out((/ 5, 1, 10, 10, 5, 10 /),'flat')
     66  type(ctrl_out),save :: o_slp          = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'slp')
     67  type(ctrl_out),save :: o_tsol         = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'tsol')
     68  type(ctrl_out),save :: o_t2m          = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'t2m')
     69  type(ctrl_out),save :: o_t2m_min      = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'t2m_min')
     70  type(ctrl_out),save :: o_t2m_max      = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'t2m_max')
     71  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') /)
     75
     76  type(ctrl_out),save :: o_wind10m      = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'wind10m')
     77  type(ctrl_out),save :: o_wind10max    = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'wind10max')
     78  type(ctrl_out),save :: o_sicf         = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'sicf')
     79  type(ctrl_out),save :: o_q2m          = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'q2m')
     80  type(ctrl_out),save :: o_u10m         = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'u10m')
     81  type(ctrl_out),save :: o_v10m         = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'v10m')
     82  type(ctrl_out),save :: o_psol         = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'psol')
     83  type(ctrl_out),save :: o_qsurf        = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'qsurf')
     84
     85  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') /)
     89
     90  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') /)
     94
     95  type(ctrl_out),save :: o_qsol         = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'qsol')
     96
     97  type(ctrl_out),save :: o_ndayrain     = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'ndayrain')
     98  type(ctrl_out),save :: o_precip       = ctrl_out((/ 1, 1, 1, 10, 5, 10 /),'precip')
     99  type(ctrl_out),save :: o_plul         = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'plul')
     100
     101  type(ctrl_out),save :: o_pluc         = ctrl_out((/ 1, 1, 1, 10, 5, 10 /),'pluc')
     102  type(ctrl_out),save :: o_snow         = ctrl_out((/ 1, 1, 10, 10, 5, 10 /),'snow')
     103  type(ctrl_out),save :: o_evap         = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'evap')
     104  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') /)
     108  type(ctrl_out),save :: o_msnow       = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'msnow')
     109  type(ctrl_out),save :: o_fsnow       = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fsnow')
     110
     111  type(ctrl_out),save :: o_tops         = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'tops')
     112  type(ctrl_out),save :: o_tops0        = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'tops0')
     113  type(ctrl_out),save :: o_topl         = ctrl_out((/ 1, 1, 10, 5, 10, 10 /),'topl')
     114  type(ctrl_out),save :: o_topl0        = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'topl0')
     115  type(ctrl_out),save :: o_SWupTOA      = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'SWupTOA')
     116  type(ctrl_out),save :: o_SWupTOAclr   = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'SWupTOAclr')
     117  type(ctrl_out),save :: o_SWdnTOA      = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'SWdnTOA')
     118  type(ctrl_out),save :: o_SWdnTOAclr   = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'SWdnTOAclr')
     119  type(ctrl_out),save :: o_nettop       = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'nettop')
     120
     121  type(ctrl_out),save :: o_SWup200      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'SWup200')
     122  type(ctrl_out),save :: o_SWup200clr   = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'SWup200clr')
     123  type(ctrl_out),save :: o_SWdn200      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'SWdn200')
     124  type(ctrl_out),save :: o_SWdn200clr   = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'SWdn200clr')
    122125
    123126! arajouter
    124 !  type(ctrl_out),save :: o_LWupTOA     = ctrl_out((/ 1, 4, 10, 10, 10 /),'LWupTOA')
    125 !  type(ctrl_out),save :: o_LWupTOAclr  = ctrl_out((/ 1, 4, 10, 10, 10 /),'LWupTOAclr')
    126 !  type(ctrl_out),save :: o_LWdnTOA     = ctrl_out((/ 1, 4, 10, 10, 10 /),'LWdnTOA')
    127 !  type(ctrl_out),save :: o_LWdnTOAclr  = ctrl_out((/ 1, 4, 10, 10, 10 /),'LWdnTOAclr')
    128 
    129   type(ctrl_out),save :: o_LWup200      = ctrl_out((/ 1, 10, 10, 10, 10 /),'LWup200')
    130   type(ctrl_out),save :: o_LWup200clr   = ctrl_out((/ 1, 10, 10, 10, 10 /),'LWup200clr')
    131   type(ctrl_out),save :: o_LWdn200      = ctrl_out((/ 1, 10, 10, 10, 10 /),'LWdn200')
    132   type(ctrl_out),save :: o_LWdn200clr   = ctrl_out((/ 1, 10, 10, 10, 10 /),'LWdn200clr')
    133   type(ctrl_out),save :: o_sols         = ctrl_out((/ 1, 1, 10, 10, 10 /),'sols')
    134   type(ctrl_out),save :: o_sols0        = ctrl_out((/ 1, 5, 10, 10, 10 /),'sols0')
    135   type(ctrl_out),save :: o_soll         = ctrl_out((/ 1, 1, 10, 10, 10 /),'soll')
    136   type(ctrl_out),save :: o_soll0        = ctrl_out((/ 1, 5, 10, 10, 10 /),'soll0')
    137   type(ctrl_out),save :: o_radsol       = ctrl_out((/ 1, 7, 10, 10, 10 /),'radsol')
    138   type(ctrl_out),save :: o_SWupSFC      = ctrl_out((/ 1, 4, 10, 10, 5 /),'SWupSFC')
    139   type(ctrl_out),save :: o_SWupSFCclr   = ctrl_out((/ 1, 4, 10, 10, 5 /),'SWupSFCclr')
    140   type(ctrl_out),save :: o_SWdnSFC      = ctrl_out((/ 1, 1, 10, 10, 5 /),'SWdnSFC')
    141   type(ctrl_out),save :: o_SWdnSFCclr   = ctrl_out((/ 1, 4, 10, 10, 5 /),'SWdnSFCclr')
    142   type(ctrl_out),save :: o_LWupSFC      = ctrl_out((/ 1, 4, 10, 10, 5 /),'LWupSFC')
    143   type(ctrl_out),save :: o_LWupSFCclr   = ctrl_out((/ 1, 4, 10, 10, 5 /),'LWupSFCclr')
    144   type(ctrl_out),save :: o_LWdnSFC      = ctrl_out((/ 1, 4, 10, 10, 5 /),'LWdnSFC')
    145   type(ctrl_out),save :: o_LWdnSFCclr   = ctrl_out((/ 1, 4, 10, 10, 5 /),'LWdnSFCclr')
    146   type(ctrl_out),save :: o_bils         = ctrl_out((/ 1, 2, 10, 5, 10 /),'bils')
    147   type(ctrl_out),save :: o_sens         = ctrl_out((/ 1, 1, 10, 10, 5 /),'sens')
    148   type(ctrl_out),save :: o_fder         = ctrl_out((/ 1, 2, 10, 10, 10 /),'fder')
    149   type(ctrl_out),save :: o_ffonte       = ctrl_out((/ 1, 10, 10, 10, 10 /),'ffonte')
    150   type(ctrl_out),save :: o_fqcalving    = ctrl_out((/ 1, 10, 10, 10, 10 /),'fqcalving')
    151   type(ctrl_out),save :: o_fqfonte      = ctrl_out((/ 1, 10, 10, 10, 10 /),'fqfonte')
    152 
    153   type(ctrl_out),save :: o_taux         = ctrl_out((/ 1, 10, 10, 10, 10 /),'taux')
    154   type(ctrl_out),save :: o_tauy         = ctrl_out((/ 1, 10, 10, 10, 10 /),'tauy')
    155   type(ctrl_out),save,dimension(4) :: o_taux_srf     = (/ ctrl_out((/ 1, 6, 10, 10, 10 /),'taux_ter'), &
    156                                                  ctrl_out((/ 1, 6, 10, 10, 10 /),'taux_lic'), &
    157                                                  ctrl_out((/ 1, 6, 10, 10, 10 /),'taux_oce'), &
    158                                                  ctrl_out((/ 1, 6, 10, 10, 10 /),'taux_sic') /)
    159 
    160   type(ctrl_out),save,dimension(4) :: o_tauy_srf     = (/ ctrl_out((/ 1, 6, 10, 10, 10 /),'tauy_ter'), &
    161                                                  ctrl_out((/ 1, 6, 10, 10, 10 /),'tauy_lic'), &
    162                                                  ctrl_out((/ 1, 6, 10, 10, 10 /),'tauy_oce'), &
    163                                                  ctrl_out((/ 1, 6, 10, 10, 10 /),'tauy_sic') /)
    164 
    165 
    166   type(ctrl_out),save,dimension(4) :: o_pourc_srf    = (/ ctrl_out((/ 1, 7, 10, 10, 10 /),'pourc_ter'), &
    167                                                  ctrl_out((/ 1, 7, 10, 10, 10 /),'pourc_lic'), &
    168                                                  ctrl_out((/ 1, 7, 10, 10, 10 /),'pourc_oce'), &
    169                                                  ctrl_out((/ 1, 7, 10, 10, 10 /),'pourc_sic') /)     
    170 
    171   type(ctrl_out),save,dimension(4) :: o_fract_srf    = (/ ctrl_out((/ 1, 6, 10, 10, 10 /),'fract_ter'), &
    172                                                  ctrl_out((/ 1, 6, 10, 10, 10 /),'fract_lic'), &
    173                                                  ctrl_out((/ 1, 6, 10, 10, 10 /),'fract_oce'), &
    174                                                  ctrl_out((/ 1, 6, 10, 10, 10 /),'fract_sic') /)
    175 
    176   type(ctrl_out),save,dimension(4) :: o_tsol_srf     = (/ ctrl_out((/ 1, 6, 10, 10, 10 /),'tsol_ter'), &
    177                                                  ctrl_out((/ 1, 6, 10, 10, 10 /),'tsol_lic'), &
    178                                                  ctrl_out((/ 1, 6, 10, 10, 10 /),'tsol_oce'), &
    179                                                  ctrl_out((/ 1, 6, 10, 10, 10 /),'tsol_sic') /)
    180 
    181   type(ctrl_out),save,dimension(4) :: o_sens_srf     = (/ ctrl_out((/ 1, 6, 10, 7, 10 /),'sens_ter'), &
    182                                                  ctrl_out((/ 1, 6, 10, 7, 10 /),'sens_lic'), &
    183                                                  ctrl_out((/ 1, 6, 10, 7, 10 /),'sens_oce'), &
    184                                                  ctrl_out((/ 1, 6, 10, 7, 10 /),'sens_sic') /)
    185 
    186   type(ctrl_out),save,dimension(4) :: o_lat_srf      = (/ ctrl_out((/ 1, 6, 10, 7, 10 /),'lat_ter'), &
    187                                                  ctrl_out((/ 1, 6, 10, 7, 10 /),'lat_lic'), &
    188                                                  ctrl_out((/ 1, 6, 10, 7, 10 /),'lat_oce'), &
    189                                                  ctrl_out((/ 1, 6, 10, 7, 10 /),'lat_sic') /)
    190 
    191   type(ctrl_out),save,dimension(4) :: o_flw_srf      = (/ ctrl_out((/ 1, 10, 10, 10, 10 /),'flw_ter'), &
    192                                                  ctrl_out((/ 1, 10, 10, 10, 10 /),'flw_lic'), &
    193                                                  ctrl_out((/ 1, 10, 10, 10, 10 /),'flw_oce'), &
    194                                                  ctrl_out((/ 1, 10, 10, 10, 10 /),'flw_sic') /)
     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')
     131
     132  type(ctrl_out),save :: o_LWup200      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'LWup200')
     133  type(ctrl_out),save :: o_LWup200clr   = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'LWup200clr')
     134  type(ctrl_out),save :: o_LWdn200      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'LWdn200')
     135  type(ctrl_out),save :: o_LWdn200clr   = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'LWdn200clr')
     136  type(ctrl_out),save :: o_sols         = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'sols')
     137  type(ctrl_out),save :: o_sols0        = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'sols0')
     138  type(ctrl_out),save :: o_soll         = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'soll')
     139  type(ctrl_out),save :: o_soll0        = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'soll0')
     140  type(ctrl_out),save :: o_radsol       = ctrl_out((/ 1, 7, 10, 10, 10, 10 /),'radsol')
     141  type(ctrl_out),save :: o_SWupSFC      = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'SWupSFC')
     142  type(ctrl_out),save :: o_SWupSFCclr   = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'SWupSFCclr')
     143  type(ctrl_out),save :: o_SWdnSFC      = ctrl_out((/ 1, 1, 10, 10, 5, 10 /),'SWdnSFC')
     144  type(ctrl_out),save :: o_SWdnSFCclr   = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'SWdnSFCclr')
     145  type(ctrl_out),save :: o_LWupSFC      = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'LWupSFC')
     146  type(ctrl_out),save :: o_LWupSFCclr   = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'LWupSFCclr')
     147  type(ctrl_out),save :: o_LWdnSFC      = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'LWdnSFC')
     148  type(ctrl_out),save :: o_LWdnSFCclr   = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'LWdnSFCclr')
     149  type(ctrl_out),save :: o_bils         = ctrl_out((/ 1, 2, 10, 5, 10, 10 /),'bils')
     150  type(ctrl_out),save :: o_sens         = ctrl_out((/ 1, 1, 10, 10, 5, 10 /),'sens')
     151  type(ctrl_out),save :: o_fder         = ctrl_out((/ 1, 2, 10, 10, 10, 10 /),'fder')
     152  type(ctrl_out),save :: o_ffonte       = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'ffonte')
     153  type(ctrl_out),save :: o_fqcalving    = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fqcalving')
     154  type(ctrl_out),save :: o_fqfonte      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fqfonte')
     155
     156  type(ctrl_out),save :: o_taux         = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'taux')
     157  type(ctrl_out),save :: o_tauy         = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'tauy')
     158  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') /)
     162
     163  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') /)
     167
     168
     169  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') /)     
     173
     174  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') /)
     178
     179  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') /)
     183
     184  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') /)
     188
     189  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') /)
     193
     194  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') /)
    195198                                                 
    196   type(ctrl_out),save,dimension(4) :: o_fsw_srf      = (/ ctrl_out((/ 1, 10, 10, 10, 10 /),'fsw_ter'), &
    197                                                   ctrl_out((/ 1, 10, 10, 10, 10 /),'fsw_lic'), &
    198                                                   ctrl_out((/ 1, 10, 10, 10, 10 /),'fsw_oce'), &
    199                                                   ctrl_out((/ 1, 10, 10, 10, 10 /),'fsw_sic') /)
    200 
    201   type(ctrl_out),save,dimension(4) :: o_wbils_srf    = (/ ctrl_out((/ 1, 10, 10, 10, 10 /),'wbils_ter'), &
    202                                                  ctrl_out((/ 1, 10, 10, 10, 10 /),'wbils_lic'), &
    203                                                  ctrl_out((/ 1, 10, 10, 10, 10 /),'wbils_oce'), &
    204                                                  ctrl_out((/ 1, 10, 10, 10, 10 /),'wbils_sic') /)
    205 
    206   type(ctrl_out),save,dimension(4) :: o_wbilo_srf    = (/ ctrl_out((/ 1, 10, 10, 10, 10 /),'wbilo_ter'), &
    207                                                      ctrl_out((/ 1, 10, 10, 10, 10 /),'wbilo_lic'), &
    208                                                  ctrl_out((/ 1, 10, 10, 10, 10 /),'wbilo_oce'), &
    209                                                  ctrl_out((/ 1, 10, 10, 10, 10 /),'wbilo_sic') /)
    210 
    211 
    212   type(ctrl_out),save :: o_cdrm         = ctrl_out((/ 1, 10, 10, 10, 10 /),'cdrm')
    213   type(ctrl_out),save :: o_cdrh         = ctrl_out((/ 1, 10, 10, 7, 10 /),'cdrh')
    214   type(ctrl_out),save :: o_cldl         = ctrl_out((/ 1, 1, 10, 10, 10 /),'cldl')
    215   type(ctrl_out),save :: o_cldm         = ctrl_out((/ 1, 1, 10, 10, 10 /),'cldm')
    216   type(ctrl_out),save :: o_cldh         = ctrl_out((/ 1, 1, 10, 10, 10 /),'cldh')
    217   type(ctrl_out),save :: o_cldt         = ctrl_out((/ 1, 1, 2, 10, 5 /),'cldt')
    218   type(ctrl_out),save :: o_cldq         = ctrl_out((/ 1, 1, 10, 10, 10 /),'cldq')
    219   type(ctrl_out),save :: o_lwp          = ctrl_out((/ 1, 5, 10, 10, 10 /),'lwp')
    220   type(ctrl_out),save :: o_iwp          = ctrl_out((/ 1, 5, 10, 10, 10 /),'iwp')
    221   type(ctrl_out),save :: o_ue           = ctrl_out((/ 1, 10, 10, 10, 10 /),'ue')
    222   type(ctrl_out),save :: o_ve           = ctrl_out((/ 1, 10, 10, 10, 10 /),'ve')
    223   type(ctrl_out),save :: o_uq           = ctrl_out((/ 1, 10, 10, 10, 10 /),'uq')
    224   type(ctrl_out),save :: o_vq           = ctrl_out((/ 1, 10, 10, 10, 10 /),'vq')
     199  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') /)
     203
     204  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') /)
     208
     209  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') /)
     213
     214
     215  type(ctrl_out),save :: o_cdrm         = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'cdrm')
     216  type(ctrl_out),save :: o_cdrh         = ctrl_out((/ 1, 10, 10, 7, 10, 10 /),'cdrh')
     217  type(ctrl_out),save :: o_cldl         = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'cldl')
     218  type(ctrl_out),save :: o_cldm         = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'cldm')
     219  type(ctrl_out),save :: o_cldh         = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'cldh')
     220  type(ctrl_out),save :: o_cldt         = ctrl_out((/ 1, 1, 2, 10, 5, 10 /),'cldt')
     221  type(ctrl_out),save :: o_cldq         = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'cldq')
     222  type(ctrl_out),save :: o_lwp          = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'lwp')
     223  type(ctrl_out),save :: o_iwp          = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'iwp')
     224  type(ctrl_out),save :: o_ue           = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'ue')
     225  type(ctrl_out),save :: o_ve           = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'ve')
     226  type(ctrl_out),save :: o_uq           = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'uq')
     227  type(ctrl_out),save :: o_vq           = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'vq')
    225228 
    226   type(ctrl_out),save :: o_cape         = ctrl_out((/ 1, 10, 10, 10, 10 /),'cape')
    227   type(ctrl_out),save :: o_pbase        = ctrl_out((/ 1, 5, 10, 10, 10 /),'pbase')
    228   type(ctrl_out),save :: o_ptop         = ctrl_out((/ 1, 5, 10, 10, 10 /),'ptop')
    229   type(ctrl_out),save :: o_fbase        = ctrl_out((/ 1, 10, 10, 10, 10 /),'fbase')
    230   type(ctrl_out),save :: o_prw          = ctrl_out((/ 1, 1, 10, 10, 10 /),'prw')
    231 
    232   type(ctrl_out),save :: o_s_pblh       = ctrl_out((/ 1, 10, 10, 10, 10 /),'s_pblh')
    233   type(ctrl_out),save :: o_s_pblt       = ctrl_out((/ 1, 10, 10, 10, 10 /),'s_pblt')
    234   type(ctrl_out),save :: o_s_lcl        = ctrl_out((/ 1, 10, 10, 10, 10 /),'s_lcl')
    235   type(ctrl_out),save :: o_s_therm      = ctrl_out((/ 1, 10, 10, 10, 10 /),'s_therm')
     229  type(ctrl_out),save :: o_cape         = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'cape')
     230  type(ctrl_out),save :: o_pbase        = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'pbase')
     231  type(ctrl_out),save :: o_ptop         = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'ptop')
     232  type(ctrl_out),save :: o_fbase        = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fbase')
     233  type(ctrl_out),save :: o_prw          = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'prw')
     234
     235  type(ctrl_out),save :: o_s_pblh       = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_pblh')
     236  type(ctrl_out),save :: o_s_pblt       = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_pblt')
     237  type(ctrl_out),save :: o_s_lcl        = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_lcl')
     238  type(ctrl_out),save :: o_s_therm      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_therm')
    236239!IM : Les champs suivants (s_capCL, s_oliqCL, s_cteiCL, s_trmb1, s_trmb2, s_trmb3) ne sont pas definis dans HBTM.F
    237 ! type(ctrl_out),save :: o_s_capCL      = ctrl_out((/ 1, 10, 10, 10, 10 /),'s_capCL')
    238 ! type(ctrl_out),save :: o_s_oliqCL     = ctrl_out((/ 1, 10, 10, 10, 10 /),'s_oliqCL')
    239 ! type(ctrl_out),save :: o_s_cteiCL     = ctrl_out((/ 1, 10, 10, 10, 10 /),'s_cteiCL')
    240 ! type(ctrl_out),save :: o_s_trmb1      = ctrl_out((/ 1, 10, 10, 10, 10 /),'s_trmb1')
    241 ! type(ctrl_out),save :: o_s_trmb2      = ctrl_out((/ 1, 10, 10, 10, 10 /),'s_trmb2')
    242 ! type(ctrl_out),save :: o_s_trmb3      = ctrl_out((/ 1, 10, 10, 10, 10 /),'s_trmb3')
    243 
    244   type(ctrl_out),save :: o_slab_bils    = ctrl_out((/ 1, 1, 10, 10, 10 /),'slab_bils_oce')
    245 
    246   type(ctrl_out),save :: o_ale_bl       = ctrl_out((/ 1, 1, 1, 10, 10 /),'ale_bl')
    247   type(ctrl_out),save :: o_alp_bl       = ctrl_out((/ 1, 1, 1, 10, 10 /),'alp_bl')
    248   type(ctrl_out),save :: o_ale_wk       = ctrl_out((/ 1, 1, 1, 10, 10 /),'ale_wk')
    249   type(ctrl_out),save :: o_alp_wk       = ctrl_out((/ 1, 1, 1, 10, 10 /),'alp_wk')
    250 
    251   type(ctrl_out),save :: o_ale          = ctrl_out((/ 1, 1, 1, 10, 10 /),'ale')
    252   type(ctrl_out),save :: o_alp          = ctrl_out((/ 1, 1, 1, 10, 10 /),'alp')
    253   type(ctrl_out),save :: o_cin          = ctrl_out((/ 1, 1, 1, 10, 10 /),'cin')
    254   type(ctrl_out),save :: o_wape         = ctrl_out((/ 1, 1, 1, 10, 10 /),'wape')
     240! type(ctrl_out),save :: o_s_capCL      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_capCL')
     241! type(ctrl_out),save :: o_s_oliqCL     = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_oliqCL')
     242! type(ctrl_out),save :: o_s_cteiCL     = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_cteiCL')
     243! type(ctrl_out),save :: o_s_trmb1      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_trmb1')
     244! type(ctrl_out),save :: o_s_trmb2      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_trmb2')
     245! type(ctrl_out),save :: o_s_trmb3      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_trmb3')
     246
     247  type(ctrl_out),save :: o_slab_bils    = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'slab_bils_oce')
     248
     249  type(ctrl_out),save :: o_ale_bl       = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'ale_bl')
     250  type(ctrl_out),save :: o_alp_bl       = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'alp_bl')
     251  type(ctrl_out),save :: o_ale_wk       = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'ale_wk')
     252  type(ctrl_out),save :: o_alp_wk       = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'alp_wk')
     253
     254  type(ctrl_out),save :: o_ale          = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'ale')
     255  type(ctrl_out),save :: o_alp          = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'alp')
     256  type(ctrl_out),save :: o_cin          = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'cin')
     257  type(ctrl_out),save :: o_wape         = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'wape')
    255258
    256259
    257260! Champs interpolles sur des niveaux de pression ??? a faire correctement
    258261                                             
    259   type(ctrl_out),save,dimension(6) :: o_uSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10 /),'u850'), &
    260                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'u700'), &
    261                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'u500'), &
    262                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'u200'), &
    263                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'u50'), &
    264                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'u10') /)
     262  type(ctrl_out),save,dimension(7) :: o_uSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u850'), &
     263                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u700'), &
     264                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u500'), &
     265                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u200'), &
     266                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u100'), &
     267                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u50'), &
     268                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u10') /)
    265269                                                     
    266270
    267   type(ctrl_out),save,dimension(6) :: o_vSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10 /),'v850'), &
    268                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'v700'), &
    269                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'v500'), &
    270                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'v200'), &
    271                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'v50'), &
    272                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'v10') /)
    273 
    274   type(ctrl_out),save,dimension(6) :: o_wSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10 /),'w850'), &
    275                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'w700'), &
    276                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'w500'), &
    277                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'w200'), &
    278                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'w50'), &
    279                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'w10') /)
    280 
    281   type(ctrl_out),save,dimension(6) :: o_tSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10 /),'t850'), &
    282                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'t700'), &
    283                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'t500'), &
    284                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'t200'), &
    285                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'t50'), &
    286                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'t10') /)
    287 
    288   type(ctrl_out),save,dimension(6) :: o_qSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10 /),'q850'), &
    289                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'q700'), &
    290                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'q500'), &
    291                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'q200'), &
    292                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'q50'), &
    293                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'q10') /)
    294 
    295   type(ctrl_out),save,dimension(6) :: o_zSTDlevs   = (/ ctrl_out((/ 1, 7, 7, 10, 10 /),'z850'), &
    296                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'z700'), &
    297                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'z500'), &
    298                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'z200'), &
    299                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'z50'), &
    300                                                      ctrl_out((/ 1, 7, 7, 10, 10 /),'z10') /)
    301 
    302 
    303   type(ctrl_out),save :: o_t_oce_sic    = ctrl_out((/ 1, 10, 10, 10, 10 /),'t_oce_sic')
    304 
    305   type(ctrl_out),save :: o_weakinv      = ctrl_out((/ 10, 1, 10, 10, 10 /),'weakinv')
    306   type(ctrl_out),save :: o_dthmin       = ctrl_out((/ 10, 1, 10, 10, 10 /),'dthmin')
    307   type(ctrl_out),save,dimension(4) :: o_u10_srf      = (/ ctrl_out((/ 10, 4, 10, 10, 10 /),'u10_ter'), &
    308                                                      ctrl_out((/ 10, 4, 10, 10, 10 /),'u10_lic'), &
    309                                                      ctrl_out((/ 10, 4, 10, 10, 10 /),'u10_oce'), &
    310                                                      ctrl_out((/ 10, 4, 10, 10, 10 /),'u10_sic') /)
    311 
    312   type(ctrl_out),save,dimension(4) :: o_v10_srf      = (/ ctrl_out((/ 10, 4, 10, 10, 10 /),'v10_ter'), &
    313                                                      ctrl_out((/ 10, 4, 10, 10, 10 /),'v10_lic'), &
    314                                                      ctrl_out((/ 10, 4, 10, 10, 10 /),'v10_oce'), &
    315                                                      ctrl_out((/ 10, 4, 10, 10, 10 /),'v10_sic') /)
    316 
    317   type(ctrl_out),save :: o_cldtau       = ctrl_out((/ 10, 5, 10, 10, 10 /),'cldtau')                     
    318   type(ctrl_out),save :: o_cldemi       = ctrl_out((/ 10, 5, 10, 10, 10 /),'cldemi')
    319   type(ctrl_out),save :: o_rh2m         = ctrl_out((/ 5, 5, 10, 10, 10 /),'rh2m')
    320   type(ctrl_out),save :: o_rh2m_min     = ctrl_out((/ 10, 5, 10, 10, 10 /),'rh2m_min')
    321   type(ctrl_out),save :: o_rh2m_max     = ctrl_out((/ 10, 5, 10, 10, 10 /),'rh2m_max')
    322   type(ctrl_out),save :: o_qsat2m       = ctrl_out((/ 10, 5, 10, 10, 10 /),'qsat2m')
    323   type(ctrl_out),save :: o_tpot         = ctrl_out((/ 10, 5, 10, 10, 10 /),'tpot')
    324   type(ctrl_out),save :: o_tpote        = ctrl_out((/ 10, 5, 10, 10, 10 /),'tpote')
    325   type(ctrl_out),save :: o_tke          = ctrl_out((/ 4, 10, 10, 10, 10 /),'tke ')
    326   type(ctrl_out),save :: o_tke_max      = ctrl_out((/ 4, 10, 10, 10, 10 /),'tke_max')
    327 
    328   type(ctrl_out),save,dimension(4) :: o_tke_srf      = (/ ctrl_out((/ 10, 4, 10, 10, 10 /),'tke_ter'), &
    329                                                      ctrl_out((/ 10, 4, 10, 10, 10 /),'tke_lic'), &
    330                                                      ctrl_out((/ 10, 4, 10, 10, 10 /),'tke_oce'), &
    331                                                      ctrl_out((/ 10, 4, 10, 10, 10 /),'tke_sic') /)
    332 
    333   type(ctrl_out),save,dimension(4) :: o_tke_max_srf  = (/ ctrl_out((/ 10, 4, 10, 10, 10 /),'tke_max_ter'), &
    334                                                      ctrl_out((/ 10, 4, 10, 10, 10 /),'tke_max_lic'), &
    335                                                      ctrl_out((/ 10, 4, 10, 10, 10 /),'tke_max_oce'), &
    336                                                      ctrl_out((/ 10, 4, 10, 10, 10 /),'tke_max_sic') /)
    337 
    338   type(ctrl_out),save :: o_kz           = ctrl_out((/ 4, 10, 10, 10, 10 /),'kz')
    339   type(ctrl_out),save :: o_kz_max       = ctrl_out((/ 4, 10, 10, 10, 10 /),'kz_max')
    340   type(ctrl_out),save :: o_SWnetOR      = ctrl_out((/ 10, 10, 2, 10, 10 /),'SWnetOR')
    341   type(ctrl_out),save :: o_SWdownOR     = ctrl_out((/ 10, 10, 2, 10, 10 /),'SWdownOR')
    342   type(ctrl_out),save :: o_LWdownOR     = ctrl_out((/ 10, 10, 2, 10, 10 /),'LWdownOR')
    343 
    344   type(ctrl_out),save :: o_snowl        = ctrl_out((/ 10, 1, 10, 10, 10 /),'snowl')
    345   type(ctrl_out),save :: o_cape_max     = ctrl_out((/ 10, 1, 10, 10, 10 /),'cape_max')
    346   type(ctrl_out),save :: o_solldown     = ctrl_out((/ 10, 1, 10, 10, 10 /),'solldown')
    347 
    348   type(ctrl_out),save :: o_dtsvdfo      = ctrl_out((/ 10, 10, 10, 10, 10 /),'dtsvdfo')
    349   type(ctrl_out),save :: o_dtsvdft      = ctrl_out((/ 10, 10, 10, 10, 10 /),'dtsvdft')
    350   type(ctrl_out),save :: o_dtsvdfg      = ctrl_out((/ 10, 10, 10, 10, 10 /),'dtsvdfg')
    351   type(ctrl_out),save :: o_dtsvdfi      = ctrl_out((/ 10, 10, 10, 10, 10 /),'dtsvdfi')
    352   type(ctrl_out),save :: o_rugs         = ctrl_out((/ 10, 10, 10, 10, 10 /),'rugs')
    353 
    354   type(ctrl_out),save :: o_topswad      = ctrl_out((/ 2, 10, 10, 10, 10 /),'topswad')
    355   type(ctrl_out),save :: o_topswai      = ctrl_out((/ 2, 10, 10, 10, 10 /),'topswai')
    356   type(ctrl_out),save :: o_solswad      = ctrl_out((/ 2, 10, 10, 10, 10 /),'solswad')
    357   type(ctrl_out),save :: o_solswai      = ctrl_out((/ 2, 10, 10, 10, 10 /),'solswai')
    358 
    359   type(ctrl_out),save,dimension(10) :: o_tausumaero  = (/ ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_ASBCM'), &
    360                                                      ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_ASPOMM'), &
    361                                                      ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_ASSO4M'), &
    362                                                      ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_CSSO4M'), &
    363                                                      ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_SSSSM'), &
    364                                                      ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_ASSSM'), &
    365                                                      ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_CSSSM'), &
    366                                                      ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_CIDUSTM'), &
    367                                                      ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_AIBCM'), &
    368                                                      ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_AIPOMM') /)
    369 
    370   type(ctrl_out),save :: o_od550aer     = ctrl_out((/ 2, 6, 10, 10, 10 /),'od550aer')
    371   type(ctrl_out),save :: o_od865aer     = ctrl_out((/ 2, 6, 10, 10, 10 /),'od865aer')
    372   type(ctrl_out),save :: o_absvisaer    = ctrl_out((/ 2, 6, 10, 10, 10 /),'absvisaer')
    373   type(ctrl_out),save :: o_od550lt1aer  = ctrl_out((/ 2, 6, 10, 10, 10 /),'od550lt1aer')
    374 
    375   type(ctrl_out),save :: o_sconcso4     = ctrl_out((/ 2, 6, 10, 10, 10 /),'sconcso4')
    376   type(ctrl_out),save :: o_sconcoa      = ctrl_out((/ 2, 6, 10, 10, 10 /),'sconcoa')
    377   type(ctrl_out),save :: o_sconcbc      = ctrl_out((/ 2, 6, 10, 10, 10 /),'sconcbc')
    378   type(ctrl_out),save :: o_sconcss      = ctrl_out((/ 2, 6, 10, 10, 10 /),'sconcss')
    379   type(ctrl_out),save :: o_sconcdust    = ctrl_out((/ 2, 6, 10, 10, 10 /),'sconcdust')
    380   type(ctrl_out),save :: o_concso4      = ctrl_out((/ 2, 6, 10, 10, 10 /),'concso4')
    381   type(ctrl_out),save :: o_concoa       = ctrl_out((/ 2, 6, 10, 10, 10 /),'concoa')
    382   type(ctrl_out),save :: o_concbc       = ctrl_out((/ 2, 6, 10, 10, 10 /),'concbc')
    383   type(ctrl_out),save :: o_concss       = ctrl_out((/ 2, 6, 10, 10, 10 /),'concss')
    384   type(ctrl_out),save :: o_concdust     = ctrl_out((/ 2, 6, 10, 10, 10 /),'concdust')
    385   type(ctrl_out),save :: o_loadso4      = ctrl_out((/ 2, 6, 10, 10, 10 /),'loadso4')
    386   type(ctrl_out),save :: o_loadoa       = ctrl_out((/ 2, 6, 10, 10, 10 /),'loadoa')
    387   type(ctrl_out),save :: o_loadbc       = ctrl_out((/ 2, 6, 10, 10, 10 /),'loadbc')
    388   type(ctrl_out),save :: o_loadss       = ctrl_out((/ 2, 6, 10, 10, 10 /),'loadss')
    389   type(ctrl_out),save :: o_loaddust     = ctrl_out((/ 2, 6, 10, 10, 10 /),'loaddust')
    390 
    391   type(ctrl_out),save :: o_swtoaas_nat  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swtoaas_nat')
    392   type(ctrl_out),save :: o_swsrfas_nat  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swsrfas_nat')
    393   type(ctrl_out),save :: o_swtoacs_nat  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swtoacs_nat')
    394   type(ctrl_out),save :: o_swsrfcs_nat  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swsrfcs_nat')
    395 
    396   type(ctrl_out),save :: o_swtoaas_ant  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swtoaas_ant')
    397   type(ctrl_out),save :: o_swsrfas_ant  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swsrfas_ant')
    398   type(ctrl_out),save :: o_swtoacs_ant  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swtoacs_ant')
    399   type(ctrl_out),save :: o_swsrfcs_ant  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swsrfcs_ant')
    400 
    401   type(ctrl_out),save :: o_swtoacf_nat  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swtoacf_nat')
    402   type(ctrl_out),save :: o_swsrfcf_nat  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swsrfcf_nat')
    403   type(ctrl_out),save :: o_swtoacf_ant  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swtoacf_ant')
    404   type(ctrl_out),save :: o_swsrfcf_ant  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swsrfcf_ant')
    405   type(ctrl_out),save :: o_swtoacf_zero = ctrl_out((/ 4, 6, 10, 10, 10 /),'swtoacf_zero')
    406   type(ctrl_out),save :: o_swsrfcf_zero = ctrl_out((/ 4, 6, 10, 10, 10 /),'swsrfcf_zero')
    407 
    408   type(ctrl_out),save :: o_cldncl       = ctrl_out((/ 2, 6, 10, 10, 10 /),'cldncl')
    409   type(ctrl_out),save :: o_reffclwtop   = ctrl_out((/ 2, 6, 10, 10, 10 /),'reffclwtop')
    410   type(ctrl_out),save :: o_cldnvi       = ctrl_out((/ 2, 6, 10, 10, 10 /),'cldnvi')
    411   type(ctrl_out),save :: o_lcc          = ctrl_out((/ 2, 6, 10, 10, 10 /),'lcc')
     271  type(ctrl_out),save,dimension(7) :: o_vSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v850'), &
     272                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v700'), &
     273                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v500'), &
     274                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v200'), &
     275                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v100'), &
     276                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v50'), &
     277                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v10') /)
     278
     279  type(ctrl_out),save,dimension(7) :: o_wSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w850'), &
     280                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w700'), &
     281                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w500'), &
     282                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w200'), &
     283                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w100'), &
     284                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w50'), &
     285                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w10') /)
     286
     287  type(ctrl_out),save,dimension(7) :: o_tSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t850'), &
     288                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t700'), &
     289                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t500'), &
     290                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t200'), &
     291                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t100'), &
     292                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t50'), &
     293                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t10') /)
     294
     295  type(ctrl_out),save,dimension(7) :: o_qSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q850'), &
     296                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q700'), &
     297                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q500'), &
     298                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q200'), &
     299                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q100'), &
     300                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q50'), &
     301                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q10') /)
     302
     303  type(ctrl_out),save,dimension(7) :: o_zSTDlevs   = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z850'), &
     304                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z700'), &
     305                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z500'), &
     306                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z200'), &
     307                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z100'), &
     308                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z50'), &
     309                                                     ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z10') /)
     310
     311
     312  type(ctrl_out),save :: o_t_oce_sic    = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'t_oce_sic')
     313
     314  type(ctrl_out),save :: o_weakinv      = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'weakinv')
     315  type(ctrl_out),save :: o_dthmin       = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'dthmin')
     316  type(ctrl_out),save,dimension(4) :: o_u10_srf      = (/ ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'u10_ter'), &
     317                                                     ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'u10_lic'), &
     318                                                     ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'u10_oce'), &
     319                                                     ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'u10_sic') /)
     320
     321  type(ctrl_out),save,dimension(4) :: o_v10_srf      = (/ ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'v10_ter'), &
     322                                                     ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'v10_lic'), &
     323                                                     ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'v10_oce'), &
     324                                                     ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'v10_sic') /)
     325
     326  type(ctrl_out),save :: o_cldtau       = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'cldtau')                     
     327  type(ctrl_out),save :: o_cldemi       = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'cldemi')
     328  type(ctrl_out),save :: o_rh2m         = ctrl_out((/ 5, 5, 10, 10, 10, 10 /),'rh2m')
     329  type(ctrl_out),save :: o_rh2m_min     = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'rh2m_min')
     330  type(ctrl_out),save :: o_rh2m_max     = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'rh2m_max')
     331  type(ctrl_out),save :: o_qsat2m       = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'qsat2m')
     332  type(ctrl_out),save :: o_tpot         = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'tpot')
     333  type(ctrl_out),save :: o_tpote        = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'tpote')
     334  type(ctrl_out),save :: o_tke          = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tke ')
     335  type(ctrl_out),save :: o_tke_max      = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tke_max')
     336
     337  type(ctrl_out),save,dimension(4) :: o_tke_srf      = (/ ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_ter'), &
     338                                                     ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_lic'), &
     339                                                     ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_oce'), &
     340                                                     ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_sic') /)
     341
     342  type(ctrl_out),save,dimension(4) :: o_tke_max_srf  = (/ ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_max_ter'), &
     343                                                     ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_max_lic'), &
     344                                                     ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_max_oce'), &
     345                                                     ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_max_sic') /)
     346
     347  type(ctrl_out),save :: o_kz           = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'kz')
     348  type(ctrl_out),save :: o_kz_max       = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'kz_max')
     349  type(ctrl_out),save :: o_SWnetOR      = ctrl_out((/ 10, 10, 2, 10, 10, 10 /),'SWnetOR')
     350  type(ctrl_out),save :: o_SWdownOR     = ctrl_out((/ 10, 10, 2, 10, 10, 10 /),'SWdownOR')
     351  type(ctrl_out),save :: o_LWdownOR     = ctrl_out((/ 10, 10, 2, 10, 10, 10 /),'LWdownOR')
     352
     353  type(ctrl_out),save :: o_snowl        = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'snowl')
     354  type(ctrl_out),save :: o_cape_max     = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'cape_max')
     355  type(ctrl_out),save :: o_solldown     = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'solldown')
     356
     357  type(ctrl_out),save :: o_dtsvdfo      = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dtsvdfo')
     358  type(ctrl_out),save :: o_dtsvdft      = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dtsvdft')
     359  type(ctrl_out),save :: o_dtsvdfg      = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dtsvdfg')
     360  type(ctrl_out),save :: o_dtsvdfi      = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dtsvdfi')
     361  type(ctrl_out),save :: o_rugs         = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'rugs')
     362
     363  type(ctrl_out),save :: o_topswad      = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'topswad')
     364  type(ctrl_out),save :: o_topswai      = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'topswai')
     365  type(ctrl_out),save :: o_solswad      = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'solswad')
     366  type(ctrl_out),save :: o_solswai      = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'solswai')
     367
     368  type(ctrl_out),save,dimension(10) :: o_tausumaero  = (/ ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASBCM'), &
     369                                                     ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASPOMM'), &
     370                                                     ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASSO4M'), &
     371                                                     ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_CSSO4M'), &
     372                                                     ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_SSSSM'), &
     373                                                     ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASSSM'), &
     374                                                     ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_CSSSM'), &
     375                                                     ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_CIDUSTM'), &
     376                                                     ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_AIBCM'), &
     377                                                     ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_AIPOMM') /)
     378
     379  type(ctrl_out),save :: o_od550aer     = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'od550aer')
     380  type(ctrl_out),save :: o_od865aer     = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'od865aer')
     381  type(ctrl_out),save :: o_absvisaer    = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'absvisaer')
     382  type(ctrl_out),save :: o_od550lt1aer  = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'od550lt1aer')
     383
     384  type(ctrl_out),save :: o_sconcso4     = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'sconcso4')
     385  type(ctrl_out),save :: o_sconcoa      = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'sconcoa')
     386  type(ctrl_out),save :: o_sconcbc      = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'sconcbc')
     387  type(ctrl_out),save :: o_sconcss      = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'sconcss')
     388  type(ctrl_out),save :: o_sconcdust    = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'sconcdust')
     389  type(ctrl_out),save :: o_concso4      = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'concso4')
     390  type(ctrl_out),save :: o_concoa       = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'concoa')
     391  type(ctrl_out),save :: o_concbc       = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'concbc')
     392  type(ctrl_out),save :: o_concss       = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'concss')
     393  type(ctrl_out),save :: o_concdust     = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'concdust')
     394  type(ctrl_out),save :: o_loadso4      = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'loadso4')
     395  type(ctrl_out),save :: o_loadoa       = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'loadoa')
     396  type(ctrl_out),save :: o_loadbc       = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'loadbc')
     397  type(ctrl_out),save :: o_loadss       = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'loadss')
     398  type(ctrl_out),save :: o_loaddust     = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'loaddust')
     399
     400  type(ctrl_out),save :: o_swtoaas_nat  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoaas_nat')
     401  type(ctrl_out),save :: o_swsrfas_nat  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfas_nat')
     402  type(ctrl_out),save :: o_swtoacs_nat  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoacs_nat')
     403  type(ctrl_out),save :: o_swsrfcs_nat  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfcs_nat')
     404
     405  type(ctrl_out),save :: o_swtoaas_ant  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoaas_ant')
     406  type(ctrl_out),save :: o_swsrfas_ant  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfas_ant')
     407  type(ctrl_out),save :: o_swtoacs_ant  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoacs_ant')
     408  type(ctrl_out),save :: o_swsrfcs_ant  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfcs_ant')
     409
     410  type(ctrl_out),save :: o_swtoacf_nat  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoacf_nat')
     411  type(ctrl_out),save :: o_swsrfcf_nat  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfcf_nat')
     412  type(ctrl_out),save :: o_swtoacf_ant  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoacf_ant')
     413  type(ctrl_out),save :: o_swsrfcf_ant  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfcf_ant')
     414  type(ctrl_out),save :: o_swtoacf_zero = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoacf_zero')
     415  type(ctrl_out),save :: o_swsrfcf_zero = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfcf_zero')
     416
     417  type(ctrl_out),save :: o_cldncl       = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'cldncl')
     418  type(ctrl_out),save :: o_reffclwtop   = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'reffclwtop')
     419  type(ctrl_out),save :: o_cldnvi       = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'cldnvi')
     420  type(ctrl_out),save :: o_lcc          = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'lcc')
    412421
    413422
    414423!!!!!!!!!!!!!!!!!!!!!! 3D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    415   type(ctrl_out),save :: o_ec550aer     = ctrl_out((/ 2, 6, 10, 10, 10 /),'ec550aer')
    416   type(ctrl_out),save :: o_lwcon        = ctrl_out((/ 2, 5, 10, 10, 10 /),'lwcon')
    417   type(ctrl_out),save :: o_iwcon        = ctrl_out((/ 2, 5, 10, 10, 10 /),'iwcon')
    418   type(ctrl_out),save :: o_temp         = ctrl_out((/ 2, 3, 4, 10, 10 /),'temp')
    419   type(ctrl_out),save :: o_theta        = ctrl_out((/ 2, 3, 4, 10, 10 /),'theta')
    420   type(ctrl_out),save :: o_ovap         = ctrl_out((/ 2, 3, 4, 10, 10 /),'ovap')
    421   type(ctrl_out),save :: o_ovapinit     = ctrl_out((/ 2, 10, 10, 10, 10 /),'ovapinit')
    422   type(ctrl_out),save :: o_wvapp        = ctrl_out((/ 2, 10, 10, 10, 10 /),'wvapp')
    423   type(ctrl_out),save :: o_geop         = ctrl_out((/ 2, 3, 10, 10, 10 /),'geop')
    424   type(ctrl_out),save :: o_vitu         = ctrl_out((/ 2, 3, 4, 6, 10 /),'vitu')
    425   type(ctrl_out),save :: o_vitv         = ctrl_out((/ 2, 3, 4, 6, 10 /),'vitv')
    426   type(ctrl_out),save :: o_vitw         = ctrl_out((/ 2, 3, 10, 6, 10 /),'vitw')
    427   type(ctrl_out),save :: o_pres         = ctrl_out((/ 2, 3, 10, 10, 10 /),'pres')
    428   type(ctrl_out),save :: o_paprs        = ctrl_out((/ 2, 3, 10, 10, 10 /),'paprs')
    429   type(ctrl_out),save :: o_rneb         = ctrl_out((/ 2, 5, 10, 10, 10 /),'rneb')
    430   type(ctrl_out),save :: o_rnebcon      = ctrl_out((/ 2, 5, 10, 10, 10 /),'rnebcon')
    431   type(ctrl_out),save :: o_rhum         = ctrl_out((/ 2, 5, 10, 10, 10 /),'rhum')
    432   type(ctrl_out),save :: o_ozone        = ctrl_out((/ 2, 10, 10, 10, 10 /),'ozone')
    433   type(ctrl_out),save :: o_ozone_light  = ctrl_out((/ 2, 10, 10, 10, 10 /),'ozone_daylight')
    434   type(ctrl_out),save :: o_upwd         = ctrl_out((/ 2, 10, 10, 10, 10 /),'upwd')
    435   type(ctrl_out),save :: o_dtphy        = ctrl_out((/ 2, 10, 10, 10, 10 /),'dtphy')
    436   type(ctrl_out),save :: o_dqphy        = ctrl_out((/ 2, 10, 10, 10, 10 /),'dqphy')
    437   type(ctrl_out),save :: o_pr_con_l     = ctrl_out((/ 2, 10, 10, 10, 10 /),'pr_con_l')
    438   type(ctrl_out),save :: o_pr_con_i     = ctrl_out((/ 2, 10, 10, 10, 10 /),'pr_con_i')
    439   type(ctrl_out),save :: o_pr_lsc_l     = ctrl_out((/ 2, 10, 10, 10, 10 /),'pr_lsc_l')
    440   type(ctrl_out),save :: o_pr_lsc_i     = ctrl_out((/ 2, 10, 10, 10, 10 /),'pr_lsc_i')
    441   type(ctrl_out),save :: o_re           = ctrl_out((/ 5, 10, 10, 10, 10 /),'re')
    442   type(ctrl_out),save :: o_fl           = ctrl_out((/ 5, 10, 10, 10, 10 /),'fl')
    443   type(ctrl_out),save :: o_scdnc        = ctrl_out((/ 2,  6, 10, 10, 10 /),'scdnc')
    444   type(ctrl_out),save :: o_reffclws     = ctrl_out((/ 2,  6, 10, 10, 10 /),'reffclws')
    445   type(ctrl_out),save :: o_reffclwc     = ctrl_out((/ 2,  6, 10, 10, 10 /),'reffclwc')
    446   type(ctrl_out),save :: o_lcc3d        = ctrl_out((/ 2,  6, 10, 10, 10 /),'lcc3d')
    447   type(ctrl_out),save :: o_lcc3dcon     = ctrl_out((/ 2,  6, 10, 10, 10 /),'lcc3dcon')
    448   type(ctrl_out),save :: o_lcc3dstra    = ctrl_out((/ 2,  6, 10, 10, 10 /),'lcc3dstra')
     424  type(ctrl_out),save :: o_ec550aer     = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'ec550aer')
     425  type(ctrl_out),save :: o_lwcon        = ctrl_out((/ 2, 5, 10, 10, 10, 10 /),'lwcon')
     426  type(ctrl_out),save :: o_iwcon        = ctrl_out((/ 2, 5, 10, 10, 10, 10 /),'iwcon')
     427  type(ctrl_out),save :: o_temp         = ctrl_out((/ 2, 3, 4, 10, 10, 10 /),'temp')
     428  type(ctrl_out),save :: o_theta        = ctrl_out((/ 2, 3, 4, 10, 10, 10 /),'theta')
     429  type(ctrl_out),save :: o_ovap         = ctrl_out((/ 2, 3, 4, 10, 10, 10 /),'ovap')
     430  type(ctrl_out),save :: o_ovapinit     = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'ovapinit')
     431  type(ctrl_out),save :: o_wvapp        = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'wvapp')
     432  type(ctrl_out),save :: o_geop         = ctrl_out((/ 2, 3, 10, 10, 10, 10 /),'geop')
     433  type(ctrl_out),save :: o_vitu         = ctrl_out((/ 2, 3, 4, 6, 10, 10 /),'vitu')
     434  type(ctrl_out),save :: o_vitv         = ctrl_out((/ 2, 3, 4, 6, 10, 10 /),'vitv')
     435  type(ctrl_out),save :: o_vitw         = ctrl_out((/ 2, 3, 10, 6, 10, 10 /),'vitw')
     436  type(ctrl_out),save :: o_pres         = ctrl_out((/ 2, 3, 10, 10, 10, 10 /),'pres')
     437  type(ctrl_out),save :: o_paprs        = ctrl_out((/ 2, 3, 10, 10, 10, 10 /),'paprs')
     438  type(ctrl_out),save :: o_zfull       = ctrl_out((/ 2, 3, 10, 10, 10, 10 /),'zfull')
     439  type(ctrl_out),save :: o_zhalf       = ctrl_out((/ 2, 3, 10, 10, 10, 10 /),'zhalf')
     440  type(ctrl_out),save :: o_rneb         = ctrl_out((/ 2, 5, 10, 10, 10, 10 /),'rneb')
     441  type(ctrl_out),save :: o_rnebcon      = ctrl_out((/ 2, 5, 10, 10, 10, 10 /),'rnebcon')
     442  type(ctrl_out),save :: o_rhum         = ctrl_out((/ 2, 5, 10, 10, 10, 10 /),'rhum')
     443  type(ctrl_out),save :: o_ozone        = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'ozone')
     444  type(ctrl_out),save :: o_ozone_light  = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'ozone_daylight')
     445  type(ctrl_out),save :: o_upwd         = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'upwd')
     446  type(ctrl_out),save :: o_dtphy        = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'dtphy')
     447  type(ctrl_out),save :: o_dqphy        = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'dqphy')
     448  type(ctrl_out),save :: o_pr_con_l     = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'pr_con_l')
     449  type(ctrl_out),save :: o_pr_con_i     = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'pr_con_i')
     450  type(ctrl_out),save :: o_pr_lsc_l     = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'pr_lsc_l')
     451  type(ctrl_out),save :: o_pr_lsc_i     = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'pr_lsc_i')
     452  type(ctrl_out),save :: o_re           = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'re')
     453  type(ctrl_out),save :: o_fl           = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'fl')
     454  type(ctrl_out),save :: o_scdnc        = ctrl_out((/ 2,  6, 10, 10, 10, 10 /),'scdnc')
     455  type(ctrl_out),save :: o_reffclws     = ctrl_out((/ 2,  6, 10, 10, 10, 10 /),'reffclws')
     456  type(ctrl_out),save :: o_reffclwc     = ctrl_out((/ 2,  6, 10, 10, 10, 10 /),'reffclwc')
     457  type(ctrl_out),save :: o_lcc3d        = ctrl_out((/ 2,  6, 10, 10, 10, 10 /),'lcc3d')
     458  type(ctrl_out),save :: o_lcc3dcon     = ctrl_out((/ 2,  6, 10, 10, 10, 10 /),'lcc3dcon')
     459  type(ctrl_out),save :: o_lcc3dstra    = ctrl_out((/ 2,  6, 10, 10, 10, 10 /),'lcc3dstra')
    449460!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    450461
    451   type(ctrl_out),save,dimension(4) :: o_albe_srf     = (/ ctrl_out((/ 3, 7, 10, 7, 10 /),'albe_ter'), &
    452                                                      ctrl_out((/ 3, 7, 10, 7, 10 /),'albe_lic'), &
    453                                                      ctrl_out((/ 3, 7, 10, 7, 10 /),'albe_oce'), &
    454                                                      ctrl_out((/ 3, 7, 10, 7, 10 /),'albe_sic') /)
    455 
    456   type(ctrl_out),save,dimension(4) :: o_ages_srf     = (/ ctrl_out((/ 10, 10, 10, 10, 10 /),'ages_ter'), &
    457                                                      ctrl_out((/ 3, 10, 10, 10, 10 /),'ages_lic'), &
    458                                                      ctrl_out((/ 10, 10, 10, 10, 10 /),'ages_oce'), &
    459                                                      ctrl_out((/ 3, 10, 10, 10, 10 /),'ages_sic') /)
    460 
    461   type(ctrl_out),save,dimension(4) :: o_rugs_srf     = (/ ctrl_out((/ 3, 6, 10, 10, 10 /),'rugs_ter'), &
    462                                                      ctrl_out((/ 3, 6, 10, 10, 10 /),'rugs_lic'), &
    463                                                      ctrl_out((/ 3, 6, 10, 10, 10 /),'rugs_oce'), &
    464                                                      ctrl_out((/ 3, 6, 10, 10, 10 /),'rugs_sic') /)
    465 
    466   type(ctrl_out),save :: o_alb1         = ctrl_out((/ 3, 10, 10, 10, 10 /),'alb1')
    467   type(ctrl_out),save :: o_alb2       = ctrl_out((/ 3, 10, 10, 10, 10 /),'alb2')
    468 
    469   type(ctrl_out),save :: o_clwcon       = ctrl_out((/ 4, 10, 10, 10, 10 /),'clwcon')
    470   type(ctrl_out),save :: o_Ma           = ctrl_out((/ 4, 10, 10, 10, 10 /),'Ma')
    471   type(ctrl_out),save :: o_dnwd         = ctrl_out((/ 4, 10, 10, 10, 10 /),'dnwd')
    472   type(ctrl_out),save :: o_dnwd0        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dnwd0')
    473   type(ctrl_out),save :: o_mc           = ctrl_out((/ 4, 5, 10, 10, 10 /),'mc')
    474   type(ctrl_out),save :: o_ftime_con    = ctrl_out((/ 4, 10, 10, 10, 10 /),'ftime_con')
    475   type(ctrl_out),save :: o_dtdyn        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtdyn')
    476   type(ctrl_out),save :: o_dqdyn        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dqdyn')
    477   type(ctrl_out),save :: o_dudyn        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dudyn')  !AXC
    478   type(ctrl_out),save :: o_dvdyn        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dvdyn')  !AXC
    479   type(ctrl_out),save :: o_dtcon        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtcon')
    480   type(ctrl_out),save :: o_ducon        = ctrl_out((/ 4, 10, 10, 10, 10 /),'ducon')
    481   type(ctrl_out),save :: o_dqcon        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dqcon')
    482   type(ctrl_out),save :: o_dtwak        = ctrl_out((/ 4, 5, 10, 10, 10 /),'dtwak')
    483   type(ctrl_out),save :: o_dqwak        = ctrl_out((/ 4, 5, 10, 10, 10 /),'dqwak')
    484   type(ctrl_out),save :: o_wake_h       = ctrl_out((/ 4, 5, 10, 10, 10 /),'wake_h')
    485   type(ctrl_out),save :: o_wake_s       = ctrl_out((/ 4, 5, 10, 10, 10 /),'wake_s')
    486   type(ctrl_out),save :: o_wake_deltat  = ctrl_out((/ 4, 5, 10, 10, 10 /),'wake_deltat')
    487   type(ctrl_out),save :: o_wake_deltaq  = ctrl_out((/ 4, 5, 10, 10, 10 /),'wake_deltaq')
    488   type(ctrl_out),save :: o_wake_omg     = ctrl_out((/ 4, 5, 10, 10, 10 /),'wake_omg')
    489   type(ctrl_out),save :: o_Vprecip      = ctrl_out((/ 10, 10, 10, 10, 10 /),'Vprecip')
    490   type(ctrl_out),save :: o_ftd          = ctrl_out((/ 4, 5, 10, 10, 10 /),'ftd')
    491   type(ctrl_out),save :: o_fqd          = ctrl_out((/ 4, 5, 10, 10, 10 /),'fqd')
    492   type(ctrl_out),save :: o_dtlsc        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtlsc')
    493   type(ctrl_out),save :: o_dtlschr      = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtlschr')
    494   type(ctrl_out),save :: o_dqlsc        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dqlsc')
    495   type(ctrl_out),save :: o_dtvdf        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtvdf')
    496   type(ctrl_out),save :: o_dqvdf        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dqvdf')
    497   type(ctrl_out),save :: o_dteva        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dteva')
    498   type(ctrl_out),save :: o_dqeva        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dqeva')
    499   type(ctrl_out),save :: o_ptconv       = ctrl_out((/ 4, 10, 10, 10, 10 /),'ptconv')
    500   type(ctrl_out),save :: o_ratqs        = ctrl_out((/ 4, 10, 10, 10, 10 /),'ratqs')
    501   type(ctrl_out),save :: o_dtthe        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtthe')
    502   type(ctrl_out),save :: o_f_th         = ctrl_out((/ 4, 10, 10, 10, 10 /),'f_th')
    503   type(ctrl_out),save :: o_e_th         = ctrl_out((/ 4, 10, 10, 10, 10 /),'e_th')
    504   type(ctrl_out),save :: o_w_th         = ctrl_out((/ 4, 10, 10, 10, 10 /),'w_th')
    505   type(ctrl_out),save :: o_lambda_th    = ctrl_out((/ 10, 10, 10, 10, 10 /),'lambda_th')
    506   type(ctrl_out),save :: o_ftime_th     = ctrl_out((/ 4, 10, 10, 10, 10 /),'ftime_th')
    507   type(ctrl_out),save :: o_q_th         = ctrl_out((/ 4, 10, 10, 10, 10 /),'q_th')
    508   type(ctrl_out),save :: o_a_th         = ctrl_out((/ 4, 10, 10, 10, 10 /),'a_th')
    509   type(ctrl_out),save :: o_d_th         = ctrl_out((/ 4, 10, 10, 10, 10 /),'d_th')
    510   type(ctrl_out),save :: o_f0_th        = ctrl_out((/ 4, 10, 10, 10, 10 /),'f0_th')
    511   type(ctrl_out),save :: o_zmax_th      = ctrl_out((/ 4, 10, 10, 10, 10 /),'zmax_th')
    512   type(ctrl_out),save :: o_dqthe        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dqthe')
    513   type(ctrl_out),save :: o_dtajs        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtajs')
    514   type(ctrl_out),save :: o_dqajs        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dqajs')
    515   type(ctrl_out),save :: o_dtswr        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtswr')
    516   type(ctrl_out),save :: o_dtsw0        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtsw0')
    517   type(ctrl_out),save :: o_dtlwr        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtlwr')
    518   type(ctrl_out),save :: o_dtlw0        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtlw0')
    519   type(ctrl_out),save :: o_dtec         = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtec')
    520   type(ctrl_out),save :: o_duvdf        = ctrl_out((/ 4, 10, 10, 10, 10 /),'duvdf')
    521   type(ctrl_out),save :: o_dvvdf        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dvvdf')
    522   type(ctrl_out),save :: o_duoro        = ctrl_out((/ 4, 10, 10, 10, 10 /),'duoro')
    523   type(ctrl_out),save :: o_dvoro        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dvoro')
    524   type(ctrl_out),save :: o_dulif        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dulif')
    525   type(ctrl_out),save :: o_dvlif        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dvlif')
    526   type(ctrl_out),save :: o_duhin        = ctrl_out((/ 4, 10, 10, 10, 10 /),'duhin')
    527   type(ctrl_out),save :: o_dvhin        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dvhin')
     462  type(ctrl_out),save,dimension(4) :: o_albe_srf     = (/ ctrl_out((/ 3, 7, 10, 7, 10, 10 /),'albe_ter'), &
     463                                                     ctrl_out((/ 3, 7, 10, 7, 10, 10 /),'albe_lic'), &
     464                                                     ctrl_out((/ 3, 7, 10, 7, 10, 10 /),'albe_oce'), &
     465                                                     ctrl_out((/ 3, 7, 10, 7, 10, 10 /),'albe_sic') /)
     466
     467  type(ctrl_out),save,dimension(4) :: o_ages_srf     = (/ ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'ages_ter'), &
     468                                                     ctrl_out((/ 3, 10, 10, 10, 10, 10 /),'ages_lic'), &
     469                                                     ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'ages_oce'), &
     470                                                     ctrl_out((/ 3, 10, 10, 10, 10, 10 /),'ages_sic') /)
     471
     472  type(ctrl_out),save,dimension(4) :: o_rugs_srf     = (/ ctrl_out((/ 3, 6, 10, 10, 10, 10 /),'rugs_ter'), &
     473                                                     ctrl_out((/ 3, 6, 10, 10, 10, 10 /),'rugs_lic'), &
     474                                                     ctrl_out((/ 3, 6, 10, 10, 10, 10 /),'rugs_oce'), &
     475                                                     ctrl_out((/ 3, 6, 10, 10, 10, 10 /),'rugs_sic') /)
     476
     477  type(ctrl_out),save :: o_alb1         = ctrl_out((/ 3, 10, 10, 10, 10, 10 /),'alb1')
     478  type(ctrl_out),save :: o_alb2       = ctrl_out((/ 3, 10, 10, 10, 10, 10 /),'alb2')
     479
     480  type(ctrl_out),save :: o_clwcon       = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'clwcon')
     481  type(ctrl_out),save :: o_Ma           = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'Ma')
     482  type(ctrl_out),save :: o_dnwd         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dnwd')
     483  type(ctrl_out),save :: o_dnwd0        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dnwd0')
     484  type(ctrl_out),save :: o_mc           = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'mc')
     485  type(ctrl_out),save :: o_ftime_con    = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ftime_con')
     486  type(ctrl_out),save :: o_dtdyn        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtdyn')
     487  type(ctrl_out),save :: o_dqdyn        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqdyn')
     488  type(ctrl_out),save :: o_dudyn        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dudyn')  !AXC
     489  type(ctrl_out),save :: o_dvdyn        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dvdyn')  !AXC
     490  type(ctrl_out),save :: o_dtcon        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtcon')
     491  type(ctrl_out),save :: o_ducon        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ducon')
     492  type(ctrl_out),save :: o_dqcon        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqcon')
     493  type(ctrl_out),save :: o_dtwak        = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'dtwak')
     494  type(ctrl_out),save :: o_dqwak        = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'dqwak')
     495  type(ctrl_out),save :: o_wake_h       = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'wake_h')
     496  type(ctrl_out),save :: o_wake_s       = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'wake_s')
     497  type(ctrl_out),save :: o_wake_deltat  = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'wake_deltat')
     498  type(ctrl_out),save :: o_wake_deltaq  = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'wake_deltaq')
     499  type(ctrl_out),save :: o_wake_omg     = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'wake_omg')
     500  type(ctrl_out),save :: o_Vprecip      = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'Vprecip')
     501  type(ctrl_out),save :: o_ftd          = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'ftd')
     502  type(ctrl_out),save :: o_fqd          = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'fqd')
     503  type(ctrl_out),save :: o_dtlsc        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtlsc')
     504  type(ctrl_out),save :: o_dtlschr      = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtlschr')
     505  type(ctrl_out),save :: o_dqlsc        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqlsc')
     506  type(ctrl_out),save :: o_dtvdf        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtvdf')
     507  type(ctrl_out),save :: o_dqvdf        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqvdf')
     508  type(ctrl_out),save :: o_dteva        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dteva')
     509  type(ctrl_out),save :: o_dqeva        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqeva')
     510  type(ctrl_out),save :: o_ptconv       = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ptconv')
     511  type(ctrl_out),save :: o_ratqs        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ratqs')
     512  type(ctrl_out),save :: o_dtthe        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtthe')
     513  type(ctrl_out),save :: o_f_th         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'f_th')
     514  type(ctrl_out),save :: o_e_th         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'e_th')
     515  type(ctrl_out),save :: o_w_th         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'w_th')
     516  type(ctrl_out),save :: o_lambda_th    = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'lambda_th')
     517  type(ctrl_out),save :: o_ftime_th     = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ftime_th')
     518  type(ctrl_out),save :: o_q_th         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'q_th')
     519  type(ctrl_out),save :: o_a_th         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'a_th')
     520  type(ctrl_out),save :: o_d_th         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'d_th')
     521  type(ctrl_out),save :: o_f0_th        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'f0_th')
     522  type(ctrl_out),save :: o_zmax_th      = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'zmax_th')
     523  type(ctrl_out),save :: o_dqthe        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqthe')
     524  type(ctrl_out),save :: o_dtajs        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtajs')
     525  type(ctrl_out),save :: o_dqajs        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqajs')
     526  type(ctrl_out),save :: o_dtswr        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtswr')
     527  type(ctrl_out),save :: o_dtsw0        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtsw0')
     528  type(ctrl_out),save :: o_dtlwr        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtlwr')
     529  type(ctrl_out),save :: o_dtlw0        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtlw0')
     530  type(ctrl_out),save :: o_dtec         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtec')
     531  type(ctrl_out),save :: o_duvdf        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'duvdf')
     532  type(ctrl_out),save :: o_dvvdf        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dvvdf')
     533  type(ctrl_out),save :: o_duoro        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'duoro')
     534  type(ctrl_out),save :: o_dvoro        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dvoro')
     535  type(ctrl_out),save :: o_dulif        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dulif')
     536  type(ctrl_out),save :: o_dvlif        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dvlif')
     537  type(ctrl_out),save :: o_duhin        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'duhin')
     538  type(ctrl_out),save :: o_dvhin        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dvhin')
     539  type(ctrl_out),save :: o_dtoro        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtoro')
     540  type(ctrl_out),save :: o_dtlif        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtlif')
     541  type(ctrl_out),save :: o_dthin        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dthin')
    528542
    529543! Attention a refaire correctement
    530   type(ctrl_out),save,dimension(2) :: o_trac         = (/ ctrl_out((/ 4, 10, 10, 10, 10 /),'trac01'), &
    531                                                      ctrl_out((/ 4, 10, 10, 10, 10 /),'trac02') /)
     544  type(ctrl_out),save,dimension(2) :: o_trac         = (/ ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'trac01'), &
     545                                                     ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'trac02') /)
     546
     547  type(ctrl_out),save :: o_rsu        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rsu')
     548  type(ctrl_out),save :: o_rsd        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rsd')
     549  type(ctrl_out),save :: o_rlu        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rlu')
     550  type(ctrl_out),save :: o_rld        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rld')
     551  type(ctrl_out),save :: o_rsucs      = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rsucs')
     552  type(ctrl_out),save :: o_rsdcs      = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rsdcs')
     553  type(ctrl_out),save :: o_rlucs      = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rlucs')
     554  type(ctrl_out),save :: o_rldcs      = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rldcs')
     555
     556  type(ctrl_out),save :: o_tnt          = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tnt')
     557  type(ctrl_out),save :: o_tntc         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tntc')
     558  type(ctrl_out),save :: o_tntr        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tntr')
     559  type(ctrl_out),save :: o_tntscpbl          = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tntscpbl')
     560
     561  type(ctrl_out),save :: o_tnhus          = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tnhus')
     562  type(ctrl_out),save :: o_tnhusc         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tnhusc')
     563  type(ctrl_out),save :: o_tnhusscpbl     = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tnhusscpbl')
     564
     565  type(ctrl_out),save :: o_evu          = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'evu')
     566
     567  type(ctrl_out),save :: o_h2o          = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'h2o')
     568
     569  type(ctrl_out),save :: o_mcd          = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'mcd')
     570  type(ctrl_out),save :: o_dmc          = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dmc')
     571  type(ctrl_out),save :: o_ref_liq      = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ref_liq')
     572  type(ctrl_out),save :: o_ref_ice      = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ref_ice')
     573
     574  type(ctrl_out),save :: o_rsut4co2     = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rsut4co2')
     575  type(ctrl_out),save :: o_rlut4co2     = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rlut4co2')
     576  type(ctrl_out),save :: o_rsutcs4co2   = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rsutcs4co2')
     577  type(ctrl_out),save :: o_rlutcs4co2   = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rlutcs4co2')
     578
     579  type(ctrl_out),save :: o_rsu4co2     = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rsu4co2')
     580  type(ctrl_out),save :: o_rlu4co2     = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rlu4co2')
     581  type(ctrl_out),save :: o_rsucs4co2   = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rsucs4co2')
     582  type(ctrl_out),save :: o_rlucs4co2   = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rlucs4co2')
     583  type(ctrl_out),save :: o_rsd4co2     = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rsd4co2')
     584  type(ctrl_out),save :: o_rld4co2     = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rld4co2')
     585  type(ctrl_out),save :: o_rsdcs4co2   = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rsdcs4co2')
     586  type(ctrl_out),save :: o_rldcs4co2   = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rldcs4co2')
     587
     588
    532589    CONTAINS
    533590
     
    537594!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    538595 
    539   SUBROUTINE phys_output_open(jjmp1,nlevSTD,clevSTD,nbteta, &
    540        ctetaSTD,dtime, ok_veget, &
     596  SUBROUTINE phys_output_open(rlon,rlat,pim,tabij,ipt,jpt,plon,plat, &
     597       jjmp1,nlevSTD,clevSTD,nbteta, &
     598       ctetaSTD, dtime, ok_veget, &
    541599       type_ocean, iflag_pbl,ok_mensuel,ok_journe, &
    542600       ok_hf,ok_instan,ok_LES,ok_ade,ok_aie, read_climoz, &
     601       phys_out_filestations, &
    543602       new_aod, aerosol_couple)   
    544 
    545603
    546604  USE iophy
     
    558616  include "thermcell.h"
    559617  include "comvert.h"
     618
     619    real,dimension(klon),intent(in) :: rlon
     620    real,dimension(klon),intent(in) :: rlat
     621    integer, intent(in)             :: pim
     622    INTEGER, DIMENSION(pim)            :: tabij
     623    INTEGER,dimension(pim), intent(in) :: ipt, jpt
     624    REAL,dimension(pim), intent(in) :: plat, plon
     625    REAL,dimension(pim,2) :: plat_bounds, plon_bounds
    560626
    561627  integer                               :: jjmp1
     
    593659  integer, dimension(nfiles)            :: phys_out_filelevels
    594660  CHARACTER(len=20), dimension(nfiles)  :: type_ecri_files, phys_out_filetypes
    595   character(len=20), dimension(nfiles)  :: chtimestep   = (/ 'DefFreq', 'DefFreq','DefFreq', 'DefFreq', 'DefFreq' /)
     661  character(len=20), dimension(nfiles)  :: chtimestep   = (/ 'DefFreq', 'DefFreq','DefFreq', 'DefFreq', 'DefFreq', 'DefFreq' /)
    596662  logical, dimension(nfiles)            :: phys_out_filekeys
     663  logical, dimension(nfiles)            :: phys_out_filestations
    597664
    598665!!!!!!!!!! stockage dans une region limitee pour chaque fichier !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    599666!                 entre [phys_out_lonmin,phys_out_lonmax] et [phys_out_latmin,phys_out_latmax]
    600667
    601   logical, dimension(nfiles), save  :: phys_out_regfkey       = (/ .false., .false., .false., .false., .false. /)
    602   real, dimension(nfiles), save     :: phys_out_lonmin        = (/ -180., -180., -180., -180., -180. /)
    603   real, dimension(nfiles), save     :: phys_out_lonmax        = (/ 180., 180., 180., 180., 180. /)
    604   real, dimension(nfiles), save     :: phys_out_latmin        = (/ -90., -90., -90., -90., -90. /)
    605   real, dimension(nfiles), save     :: phys_out_latmax        = (/ 90., 90., 90., 90., 90. /)
    606  
    607  
     668  logical, dimension(nfiles), save  :: phys_out_regfkey       = (/ .false., .false., .false., .false., .false., .false. /)
     669  real, dimension(nfiles), save     :: phys_out_lonmin        = (/ -180., -180., -180., -180., -180., -180. /)
     670  real, dimension(nfiles), save     :: phys_out_lonmax        = (/ 180., 180., 180., 180., 180., 180. /)
     671  real, dimension(nfiles), save     :: phys_out_latmin        = (/ -90., -90., -90., -90., -90., -90. /)
     672  real, dimension(nfiles), save     :: phys_out_latmax        = (/ 90., 90., 90., 90., 90., 90. /)
    608673
    609674!
    610675   print*,'Debut phys_output_mod.F90'
    611676! Initialisations (Valeurs par defaut
    612    levmax = (/ klev, klev, klev, klev, klev /)
     677   levmax = (/ klev, klev, klev, klev, klev, klev /)
    613678
    614679   phys_out_filenames(1) = 'histmth'
     
    617682   phys_out_filenames(4) = 'histins'
    618683   phys_out_filenames(5) = 'histLES'
     684   phys_out_filenames(6) = 'histstn'
    619685
    620686   type_ecri(1) = 'ave(X)'
     
    623689   type_ecri(4) = 'inst(X)'
    624690   type_ecri(5) = 'ave(X)'
     691   type_ecri(6) = 'inst(X)'
    625692
    626693   clef_files(1) = ok_mensuel
     
    629696   clef_files(4) = ok_instan
    630697   clef_files(5) = ok_LES
     698   clef_files(6) = ok_instan
     699
     700!sortir des fichiers "stations" si clef_stations(:)=.TRUE.
     701   clef_stations(1) = .FALSE.
     702   clef_stations(2) = .FALSE.
     703   clef_stations(3) = .FALSE.
     704   clef_stations(4) = .FALSE.
     705   clef_stations(5) = .FALSE.
     706   clef_stations(6) = .TRUE.
    631707
    632708   lev_files(1) = lev_histmth
     
    635711   lev_files(4) = lev_histins
    636712   lev_files(5) = lev_histLES
    637 
     713   lev_files(6) = lev_histins
    638714
    639715   ecrit_files(1) = ecrit_mth
     
    642718   ecrit_files(4) = ecrit_ins
    643719   ecrit_files(5) = ecrit_LES
     720   ecrit_files(6) = ecrit_ins
    644721 
    645722!! Lectures des parametres de sorties dans physiq.def
     
    657734     phys_out_filekeys(:)=clef_files(:)
    658735   call getin('phys_out_filekeys',clef_files)
     736     phys_out_filestations(:)=clef_stations(:)
     737   call getin('phys_out_filestations',clef_stations)
    659738     phys_out_filelevels(:)=lev_files(:)
    660739   call getin('phys_out_filelevels',lev_files)
     
    672751   print*,'phys_out_filetypes=',type_ecri
    673752   print*,'phys_out_filekeys=',clef_files
     753   print*,'phys_out_filestations=',clef_stations
    674754   print*,'phys_out_filelevels=',lev_files
    675755
     
    743823              itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
    744824!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     825!IM fichiers stations
     826     else if (clef_stations(iff)) THEN
     827
     828     print*,'phys_output_mod phys_out_filenames=',phys_out_filenames(iff)
     829
     830      call histbeg_phy_all(rlon,rlat,pim,tabij,ipt,jpt,plon,plat,plon_bounds,plat_bounds, &
     831                           phys_out_filenames(iff), &
     832                           itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
    745833       else
    746834 CALL histbeg_phy(phys_out_filenames(iff),itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
    747835       endif
    748  
    749       CALL histvert(nid_files(iff), "presnivs", "Vertical levels", "Pa", &
     836
     837       CALL histvert(nid_files(iff), "presnivs", "Vertical levels", "Pa", &
    750838           levmax(iff) - levmin(iff) + 1, &
    751839           presnivs(levmin(iff):levmax(iff)), nvertm(iff),"down")
     
    776864!                 1,preff,nvertp0(iff))
    777865!!! Champs 1D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    778  CALL histdef2d(iff,o_phis%flag,o_phis%name,"Surface geop.height", "m2/s2")
     866 IF (.NOT.clef_stations(iff)) THEN
     867!
     868!IM: there is no way to have one single value in a netcdf file
     869!
    779870   type_ecri(1) = 'once'
    780871   type_ecri(2) = 'once'
     
    782873   type_ecri(4) = 'once'
    783874   type_ecri(5) = 'once'
    784  CALL histdef2d(iff,o_aire%flag,o_aire%name,"Grid area", "-")
    785  CALL histdef2d(iff,o_contfracATM%flag,o_contfracATM%name,"% sfce ter+lic", "-")
     875   type_ecri(6) = 'once'
     876   CALL histdef2d(iff,clef_stations(iff),o_aire%flag,o_aire%name,"Grid area", "-")
     877   CALL histdef2d(iff,clef_stations(iff),o_contfracATM%flag,o_contfracATM%name,"% sfce ter+lic", "-")
     878 ENDIF
    786879   type_ecri(:) = type_ecri_files(:)
    787880
    788881!!! Champs 2D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    789  CALL histdef2d(iff,o_contfracOR%flag,o_contfracOR%name,"% sfce terre OR", "-" )
    790  CALL histdef2d(iff,o_aireTER%flag,o_aireTER%name,"Grid area CONT", "-" )
    791  CALL histdef2d(iff,o_flat%flag,o_flat%name, "Latent heat flux", "W/m2")
    792  CALL histdef2d(iff,o_slp%flag,o_slp%name, "Sea Level Pressure", "Pa" )
    793  CALL histdef2d(iff,o_tsol%flag,o_tsol%name, "Surface Temperature", "K")
    794  CALL histdef2d(iff,o_t2m%flag,o_t2m%name, "Temperature 2m", "K" )
     882 CALL histdef2d(iff,clef_stations(iff),o_phis%flag,o_phis%name,"Surface geop.height", "m2/s2" )
     883 CALL histdef2d(iff,clef_stations(iff),o_contfracOR%flag,o_contfracOR%name,"% sfce terre OR", "-" )
     884 CALL histdef2d(iff,clef_stations(iff),o_aireTER%flag,o_aireTER%name,"Grid area CONT", "-" )
     885 CALL histdef2d(iff,clef_stations(iff),o_flat%flag,o_flat%name, "Latent heat flux", "W/m2")
     886 CALL histdef2d(iff,clef_stations(iff),o_slp%flag,o_slp%name, "Sea Level Pressure", "Pa" )
     887 CALL histdef2d(iff,clef_stations(iff),o_tsol%flag,o_tsol%name, "Surface Temperature", "K")
     888 CALL histdef2d(iff,clef_stations(iff),o_t2m%flag,o_t2m%name, "Temperature 2m", "K" )
     889  IF (.NOT.clef_stations(iff)) THEN
     890!
     891!IM: there is no way to have one single value in a netcdf file
     892!
    795893   type_ecri(1) = 't_min(X)'
    796894   type_ecri(2) = 't_min(X)'
     
    798896   type_ecri(4) = 't_min(X)'
    799897   type_ecri(5) = 't_min(X)'
    800  CALL histdef2d(iff,o_t2m_min%flag,o_t2m_min%name, "Temp 2m min", "K" )
     898   type_ecri(6) = 't_min(X)'
     899   CALL histdef2d(iff,clef_stations(iff),o_t2m_min%flag,o_t2m_min%name, "Temp 2m min", "K" )
    801900   type_ecri(1) = 't_max(X)'
    802901   type_ecri(2) = 't_max(X)'
     
    804903   type_ecri(4) = 't_max(X)'
    805904   type_ecri(5) = 't_max(X)'
    806  CALL histdef2d(iff,o_t2m_max%flag,o_t2m_max%name, "Temp 2m max", "K" )
     905   type_ecri(6) = 't_max(X)'
     906   CALL histdef2d(iff,clef_stations(iff),o_t2m_max%flag,o_t2m_max%name, "Temp 2m max", "K" )
     907  ENDIF
    807908   type_ecri(:) = type_ecri_files(:)
    808  CALL histdef2d(iff,o_wind10m%flag,o_wind10m%name, "10-m wind speed", "m/s")
    809  CALL histdef2d(iff,o_wind10max%flag,o_wind10max%name, "10m wind speed max", "m/s")
    810  CALL histdef2d(iff,o_sicf%flag,o_sicf%name, "Sea-ice fraction", "-" )
    811  CALL histdef2d(iff,o_q2m%flag,o_q2m%name, "Specific humidity 2m", "kg/kg")
    812  CALL histdef2d(iff,o_u10m%flag,o_u10m%name, "Vent zonal 10m", "m/s" )
    813  CALL histdef2d(iff,o_v10m%flag,o_v10m%name, "Vent meridien 10m", "m/s")
    814  CALL histdef2d(iff,o_psol%flag,o_psol%name, "Surface Pressure", "Pa" )
    815  CALL histdef2d(iff,o_qsurf%flag,o_qsurf%name, "Surface Air humidity", "kg/kg")
     909 CALL histdef2d(iff,clef_stations(iff),o_wind10m%flag,o_wind10m%name, "10-m wind speed", "m/s")
     910 CALL histdef2d(iff,clef_stations(iff),o_wind10max%flag,o_wind10max%name, "10m wind speed max", "m/s")
     911 CALL histdef2d(iff,clef_stations(iff),o_sicf%flag,o_sicf%name, "Sea-ice fraction", "-" )
     912 CALL histdef2d(iff,clef_stations(iff),o_q2m%flag,o_q2m%name, "Specific humidity 2m", "kg/kg")
     913 CALL histdef2d(iff,clef_stations(iff),o_u10m%flag,o_u10m%name, "Vent zonal 10m", "m/s" )
     914 CALL histdef2d(iff,clef_stations(iff),o_v10m%flag,o_v10m%name, "Vent meridien 10m", "m/s")
     915 CALL histdef2d(iff,clef_stations(iff),o_psol%flag,o_psol%name, "Surface Pressure", "Pa" )
     916 CALL histdef2d(iff,clef_stations(iff),o_qsurf%flag,o_qsurf%name, "Surface Air humidity", "kg/kg")
    816917
    817918  if (.not. ok_veget) then
    818  CALL histdef2d(iff,o_qsol%flag,o_qsol%name, "Soil watter content", "mm" )
     919 CALL histdef2d(iff,clef_stations(iff),o_qsol%flag,o_qsol%name, "Soil watter content", "mm" )
    819920  endif
    820921
    821  CALL histdef2d(iff,o_ndayrain%flag,o_ndayrain%name, "Number of dayrain(liq+sol)", "-")
    822  CALL histdef2d(iff,o_precip%flag,o_precip%name, "Precip Totale liq+sol", "kg/(s*m2)" )
    823  CALL histdef2d(iff,o_plul%flag,o_plul%name, "Large-scale Precip.", "kg/(s*m2)")
    824  CALL histdef2d(iff,o_pluc%flag,o_pluc%name, "Convective Precip.", "kg/(s*m2)")
    825  CALL histdef2d(iff,o_snow%flag,o_snow%name, "Snow fall", "kg/(s*m2)" )
    826  CALL histdef2d(iff,o_msnow%flag,o_msnow%name, "Surface snow amount", "kg/m2" )
    827  CALL histdef2d(iff,o_fsnow%flag,o_fsnow%name, "Surface snow area fraction", "-" )
    828  CALL histdef2d(iff,o_evap%flag,o_evap%name, "Evaporat", "kg/(s*m2)" )
    829  CALL histdef2d(iff,o_tops%flag,o_tops%name, "Solar rad. at TOA", "W/m2")
    830  CALL histdef2d(iff,o_tops0%flag,o_tops0%name, "CS Solar rad. at TOA", "W/m2")
    831  CALL histdef2d(iff,o_topl%flag,o_topl%name, "IR rad. at TOA", "W/m2" )
    832  CALL histdef2d(iff,o_topl0%flag,o_topl0%name, "IR rad. at TOA", "W/m2")
    833  CALL histdef2d(iff,o_SWupTOA%flag,o_SWupTOA%name, "SWup at TOA", "W/m2")
    834  CALL histdef2d(iff,o_SWupTOAclr%flag,o_SWupTOAclr%name, "SWup clear sky at TOA", "W/m2")
    835  CALL histdef2d(iff,o_SWdnTOA%flag,o_SWdnTOA%name, "SWdn at TOA", "W/m2" )
    836  CALL histdef2d(iff,o_SWdnTOAclr%flag,o_SWdnTOAclr%name, "SWdn clear sky at TOA", "W/m2")
    837  CALL histdef2d(iff,o_nettop%flag,o_nettop%name, "Net dn radiatif flux at TOA", "W/m2")
    838  CALL histdef2d(iff,o_SWup200%flag,o_SWup200%name, "SWup at 200mb", "W/m2" )
    839  CALL histdef2d(iff,o_SWup200clr%flag,o_SWup200clr%name, "SWup clear sky at 200mb", "W/m2")
    840  CALL histdef2d(iff,o_SWdn200%flag,o_SWdn200%name, "SWdn at 200mb", "W/m2" )
    841  CALL histdef2d(iff,o_SWdn200clr%flag,o_SWdn200clr%name, "SWdn clear sky at 200mb", "W/m2")
    842  CALL histdef2d(iff,o_LWup200%flag,o_LWup200%name, "LWup at 200mb", "W/m2")
    843  CALL histdef2d(iff,o_LWup200clr%flag,o_LWup200clr%name, "LWup clear sky at 200mb", "W/m2")
    844  CALL histdef2d(iff,o_LWdn200%flag,o_LWdn200%name, "LWdn at 200mb", "W/m2")
    845  CALL histdef2d(iff,o_LWdn200clr%flag,o_LWdn200clr%name, "LWdn clear sky at 200mb", "W/m2")
    846  CALL histdef2d(iff,o_sols%flag,o_sols%name, "Solar rad. at surf.", "W/m2")
    847  CALL histdef2d(iff,o_sols0%flag,o_sols0%name, "Solar rad. at surf.", "W/m2")
    848  CALL histdef2d(iff,o_soll%flag,o_soll%name, "IR rad. at surface", "W/m2") 
    849  CALL histdef2d(iff,o_radsol%flag,o_radsol%name, "Rayonnement au sol", "W/m2")
    850  CALL histdef2d(iff,o_soll0%flag,o_soll0%name, "IR rad. at surface", "W/m2")
    851  CALL histdef2d(iff,o_SWupSFC%flag,o_SWupSFC%name, "SWup at surface", "W/m2")
    852  CALL histdef2d(iff,o_SWupSFCclr%flag,o_SWupSFCclr%name, "SWup clear sky at surface", "W/m2")
    853  CALL histdef2d(iff,o_SWdnSFC%flag,o_SWdnSFC%name, "SWdn at surface", "W/m2")
    854  CALL histdef2d(iff,o_SWdnSFCclr%flag,o_SWdnSFCclr%name, "SWdn clear sky at surface", "W/m2")
    855  CALL histdef2d(iff,o_LWupSFC%flag,o_LWupSFC%name, "Upwd. IR rad. at surface", "W/m2")
    856  CALL histdef2d(iff,o_LWdnSFC%flag,o_LWdnSFC%name, "Down. IR rad. at surface", "W/m2")
    857  CALL histdef2d(iff,o_LWupSFCclr%flag,o_LWupSFCclr%name, "CS Upwd. IR rad. at surface", "W/m2")
    858  CALL histdef2d(iff,o_LWdnSFCclr%flag,o_LWdnSFCclr%name, "Down. CS IR rad. at surface", "W/m2")
    859  CALL histdef2d(iff,o_bils%flag,o_bils%name, "Surf. total heat flux", "W/m2")
    860  CALL histdef2d(iff,o_sens%flag,o_sens%name, "Sensible heat flux", "W/m2")
    861  CALL histdef2d(iff,o_fder%flag,o_fder%name, "Heat flux derivation", "W/m2")
    862  CALL histdef2d(iff,o_ffonte%flag,o_ffonte%name, "Thermal flux for snow melting", "W/m2")
    863  CALL histdef2d(iff,o_fqcalving%flag,o_fqcalving%name, "Ice Calving", "kg/m2/s")
    864  CALL histdef2d(iff,o_fqfonte%flag,o_fqfonte%name, "Land ice melt", "kg/m2/s")
    865 
    866  CALL histdef2d(iff,o_taux%flag,o_taux%name, "Zonal wind stress","Pa")
    867  CALL histdef2d(iff,o_tauy%flag,o_tauy%name, "Meridional wind stress","Pa")
     922 CALL histdef2d(iff,clef_stations(iff),o_ndayrain%flag,o_ndayrain%name, "Number of dayrain(liq+sol)", "-")
     923 CALL histdef2d(iff,clef_stations(iff),o_precip%flag,o_precip%name, "Precip Totale liq+sol", "kg/(s*m2)" )
     924 CALL histdef2d(iff,clef_stations(iff),o_plul%flag,o_plul%name, "Large-scale Precip.", "kg/(s*m2)")
     925 CALL histdef2d(iff,clef_stations(iff),o_pluc%flag,o_pluc%name, "Convective Precip.", "kg/(s*m2)")
     926 CALL histdef2d(iff,clef_stations(iff),o_snow%flag,o_snow%name, "Snow fall", "kg/(s*m2)" )
     927 CALL histdef2d(iff,clef_stations(iff),o_msnow%flag,o_msnow%name, "Surface snow amount", "kg/m2" )
     928 CALL histdef2d(iff,clef_stations(iff),o_fsnow%flag,o_fsnow%name, "Surface snow area fraction", "-" )
     929 CALL histdef2d(iff,clef_stations(iff),o_evap%flag,o_evap%name, "Evaporat", "kg/(s*m2)" )
     930 CALL histdef2d(iff,clef_stations(iff),o_tops%flag,o_tops%name, "Solar rad. at TOA", "W/m2")
     931 CALL histdef2d(iff,clef_stations(iff),o_tops0%flag,o_tops0%name, "CS Solar rad. at TOA", "W/m2")
     932 CALL histdef2d(iff,clef_stations(iff),o_topl%flag,o_topl%name, "IR rad. at TOA", "W/m2" )
     933 CALL histdef2d(iff,clef_stations(iff),o_topl0%flag,o_topl0%name, "IR rad. at TOA", "W/m2")
     934 CALL histdef2d(iff,clef_stations(iff),o_SWupTOA%flag,o_SWupTOA%name, "SWup at TOA", "W/m2")
     935 CALL histdef2d(iff,clef_stations(iff),o_SWupTOAclr%flag,o_SWupTOAclr%name, "SWup clear sky at TOA", "W/m2")
     936 CALL histdef2d(iff,clef_stations(iff),o_SWdnTOA%flag,o_SWdnTOA%name, "SWdn at TOA", "W/m2" )
     937 CALL histdef2d(iff,clef_stations(iff),o_SWdnTOAclr%flag,o_SWdnTOAclr%name, "SWdn clear sky at TOA", "W/m2")
     938 CALL histdef2d(iff,clef_stations(iff),o_nettop%flag,o_nettop%name, "Net dn radiatif flux at TOA", "W/m2")
     939 CALL histdef2d(iff,clef_stations(iff),o_SWup200%flag,o_SWup200%name, "SWup at 200mb", "W/m2" )
     940 CALL histdef2d(iff,clef_stations(iff),o_SWup200clr%flag,o_SWup200clr%name, "SWup clear sky at 200mb", "W/m2")
     941 CALL histdef2d(iff,clef_stations(iff),o_SWdn200%flag,o_SWdn200%name, "SWdn at 200mb", "W/m2" )
     942 CALL histdef2d(iff,clef_stations(iff),o_SWdn200clr%flag,o_SWdn200clr%name, "SWdn clear sky at 200mb", "W/m2")
     943 CALL histdef2d(iff,clef_stations(iff),o_LWup200%flag,o_LWup200%name, "LWup at 200mb", "W/m2")
     944 CALL histdef2d(iff,clef_stations(iff),o_LWup200clr%flag,o_LWup200clr%name, "LWup clear sky at 200mb", "W/m2")
     945 CALL histdef2d(iff,clef_stations(iff),o_LWdn200%flag,o_LWdn200%name, "LWdn at 200mb", "W/m2")
     946 CALL histdef2d(iff,clef_stations(iff),o_LWdn200clr%flag,o_LWdn200clr%name, "LWdn clear sky at 200mb", "W/m2")
     947 CALL histdef2d(iff,clef_stations(iff),o_sols%flag,o_sols%name, "Solar rad. at surf.", "W/m2")
     948 CALL histdef2d(iff,clef_stations(iff),o_sols0%flag,o_sols0%name, "Solar rad. at surf.", "W/m2")
     949 CALL histdef2d(iff,clef_stations(iff),o_soll%flag,o_soll%name, "IR rad. at surface", "W/m2") 
     950 CALL histdef2d(iff,clef_stations(iff),o_radsol%flag,o_radsol%name, "Rayonnement au sol", "W/m2")
     951 CALL histdef2d(iff,clef_stations(iff),o_soll0%flag,o_soll0%name, "IR rad. at surface", "W/m2")
     952 CALL histdef2d(iff,clef_stations(iff),o_SWupSFC%flag,o_SWupSFC%name, "SWup at surface", "W/m2")
     953 CALL histdef2d(iff,clef_stations(iff),o_SWupSFCclr%flag,o_SWupSFCclr%name, "SWup clear sky at surface", "W/m2")
     954 CALL histdef2d(iff,clef_stations(iff),o_SWdnSFC%flag,o_SWdnSFC%name, "SWdn at surface", "W/m2")
     955 CALL histdef2d(iff,clef_stations(iff),o_SWdnSFCclr%flag,o_SWdnSFCclr%name, "SWdn clear sky at surface", "W/m2")
     956 CALL histdef2d(iff,clef_stations(iff),o_LWupSFC%flag,o_LWupSFC%name, "Upwd. IR rad. at surface", "W/m2")
     957 CALL histdef2d(iff,clef_stations(iff),o_LWdnSFC%flag,o_LWdnSFC%name, "Down. IR rad. at surface", "W/m2")
     958 CALL histdef2d(iff,clef_stations(iff),o_LWupSFCclr%flag,o_LWupSFCclr%name, "CS Upwd. IR rad. at surface", "W/m2")
     959 CALL histdef2d(iff,clef_stations(iff),o_LWdnSFCclr%flag,o_LWdnSFCclr%name, "Down. CS IR rad. at surface", "W/m2")
     960 CALL histdef2d(iff,clef_stations(iff),o_bils%flag,o_bils%name, "Surf. total heat flux", "W/m2")
     961 CALL histdef2d(iff,clef_stations(iff),o_sens%flag,o_sens%name, "Sensible heat flux", "W/m2")
     962 CALL histdef2d(iff,clef_stations(iff),o_fder%flag,o_fder%name, "Heat flux derivation", "W/m2")
     963 CALL histdef2d(iff,clef_stations(iff),o_ffonte%flag,o_ffonte%name, "Thermal flux for snow melting", "W/m2")
     964 CALL histdef2d(iff,clef_stations(iff),o_fqcalving%flag,o_fqcalving%name, "Ice Calving", "kg/m2/s")
     965 CALL histdef2d(iff,clef_stations(iff),o_fqfonte%flag,o_fqfonte%name, "Land ice melt", "kg/m2/s")
     966
     967 CALL histdef2d(iff,clef_stations(iff),o_taux%flag,o_taux%name, "Zonal wind stress","Pa")
     968 CALL histdef2d(iff,clef_stations(iff),o_tauy%flag,o_tauy%name, "Meridional wind stress","Pa")
    868969
    869970     DO nsrf = 1, nbsrf
    870  CALL histdef2d(iff,o_pourc_srf(nsrf)%flag,o_pourc_srf(nsrf)%name,"% "//clnsurf(nsrf),"%")
    871  CALL histdef2d(iff,o_fract_srf(nsrf)%flag,o_fract_srf(nsrf)%name,"Fraction "//clnsurf(nsrf),"1")
    872  CALL histdef2d(iff,o_taux_srf(nsrf)%flag,o_taux_srf(nsrf)%name,"Zonal wind stress"//clnsurf(nsrf),"Pa")
    873  CALL histdef2d(iff,o_tauy_srf(nsrf)%flag,o_tauy_srf(nsrf)%name,"Meridional wind stress "//clnsurf(nsrf),"Pa")
    874  CALL histdef2d(iff,o_tsol_srf(nsrf)%flag,o_tsol_srf(nsrf)%name,"Temperature "//clnsurf(nsrf),"K")
    875  CALL histdef2d(iff,o_u10m_srf(nsrf)%flag,o_u10m_srf(nsrf)%name,"Vent Zonal 10m "//clnsurf(nsrf),"m/s")
    876  CALL histdef2d(iff,o_evap_srf(nsrf)%flag,o_evap_srf(nsrf)%name,"evaporation at surface "//clnsurf(nsrf),"kg/(s*m2)")
    877  CALL histdef2d(iff,o_v10m_srf(nsrf)%flag,o_v10m_srf(nsrf)%name,"Vent meredien 10m "//clnsurf(nsrf),"m/s")
    878  CALL histdef2d(iff,o_t2m_srf(nsrf)%flag,o_t2m_srf(nsrf)%name,"Temp 2m "//clnsurf(nsrf),"K")
    879  CALL histdef2d(iff,o_sens_srf(nsrf)%flag,o_sens_srf(nsrf)%name,"Sensible heat flux "//clnsurf(nsrf),"W/m2")
    880  CALL histdef2d(iff,o_lat_srf(nsrf)%flag,o_lat_srf(nsrf)%name,"Latent heat flux "//clnsurf(nsrf),"W/m2")
    881  CALL histdef2d(iff,o_flw_srf(nsrf)%flag,o_flw_srf(nsrf)%name,"LW "//clnsurf(nsrf),"W/m2")
    882  CALL histdef2d(iff,o_fsw_srf(nsrf)%flag,o_fsw_srf(nsrf)%name,"SW "//clnsurf(nsrf),"W/m2")
    883  CALL histdef2d(iff,o_wbils_srf(nsrf)%flag,o_wbils_srf(nsrf)%name,"Bilan sol "//clnsurf(nsrf),"W/m2" )
    884  CALL histdef2d(iff,o_wbilo_srf(nsrf)%flag,o_wbilo_srf(nsrf)%name,"Bilan eau "//clnsurf(nsrf),"kg/(m2*s)")
     971 CALL histdef2d(iff,clef_stations(iff),o_pourc_srf(nsrf)%flag,o_pourc_srf(nsrf)%name,"% "//clnsurf(nsrf),"%")
     972 CALL histdef2d(iff,clef_stations(iff),o_fract_srf(nsrf)%flag,o_fract_srf(nsrf)%name,"Fraction "//clnsurf(nsrf),"1")
     973 CALL histdef2d(iff,clef_stations(iff), &
     974o_taux_srf(nsrf)%flag,o_taux_srf(nsrf)%name,"Zonal wind stress"//clnsurf(nsrf),"Pa")
     975 CALL histdef2d(iff,clef_stations(iff), &
     976o_tauy_srf(nsrf)%flag,o_tauy_srf(nsrf)%name,"Meridional wind stress "//clnsurf(nsrf),"Pa")
     977 CALL histdef2d(iff,clef_stations(iff), &
     978o_tsol_srf(nsrf)%flag,o_tsol_srf(nsrf)%name,"Temperature "//clnsurf(nsrf),"K")
     979 CALL histdef2d(iff,clef_stations(iff), &
     980o_u10m_srf(nsrf)%flag,o_u10m_srf(nsrf)%name,"Vent Zonal 10m "//clnsurf(nsrf),"m/s")
     981 CALL histdef2d(iff,clef_stations(iff), &
     982o_evap_srf(nsrf)%flag,o_evap_srf(nsrf)%name,"evaporation at surface "//clnsurf(nsrf),"kg/(s*m2)")
     983 CALL histdef2d(iff,clef_stations(iff), &
     984o_v10m_srf(nsrf)%flag,o_v10m_srf(nsrf)%name,"Vent meredien 10m "//clnsurf(nsrf),"m/s")
     985 CALL histdef2d(iff,clef_stations(iff), &
     986o_t2m_srf(nsrf)%flag,o_t2m_srf(nsrf)%name,"Temp 2m "//clnsurf(nsrf),"K")
     987 CALL histdef2d(iff,clef_stations(iff), &
     988o_sens_srf(nsrf)%flag,o_sens_srf(nsrf)%name,"Sensible heat flux "//clnsurf(nsrf),"W/m2")
     989 CALL histdef2d(iff,clef_stations(iff), &
     990o_lat_srf(nsrf)%flag,o_lat_srf(nsrf)%name,"Latent heat flux "//clnsurf(nsrf),"W/m2")
     991 CALL histdef2d(iff,clef_stations(iff), &
     992o_flw_srf(nsrf)%flag,o_flw_srf(nsrf)%name,"LW "//clnsurf(nsrf),"W/m2")
     993 CALL histdef2d(iff,clef_stations(iff), &
     994o_fsw_srf(nsrf)%flag,o_fsw_srf(nsrf)%name,"SW "//clnsurf(nsrf),"W/m2")
     995 CALL histdef2d(iff,clef_stations(iff), &
     996o_wbils_srf(nsrf)%flag,o_wbils_srf(nsrf)%name,"Bilan sol "//clnsurf(nsrf),"W/m2" )
     997 CALL histdef2d(iff,clef_stations(iff), &
     998o_wbilo_srf(nsrf)%flag,o_wbilo_srf(nsrf)%name,"Bilan eau "//clnsurf(nsrf),"kg/(m2*s)")
    885999  if (iflag_pbl>1 .and. lev_files(iff).gt.10 ) then
    886  CALL histdef2d(iff,o_tke_srf(nsrf)%flag,o_tke_srf(nsrf)%name,"Max Turb. Kinetic Energy "//clnsurf(nsrf),"-")
     1000 CALL histdef2d(iff,clef_stations(iff), &
     1001o_tke_srf(nsrf)%flag,o_tke_srf(nsrf)%name,"Max Turb. Kinetic Energy "//clnsurf(nsrf),"-")
     1002
     1003  IF (.NOT.clef_stations(iff)) THEN
     1004!
     1005!IM: there is no way to have one single value in a netcdf file
     1006!
    8871007   type_ecri(1) = 't_max(X)'
    8881008   type_ecri(2) = 't_max(X)'
     
    8901010   type_ecri(4) = 't_max(X)'
    8911011   type_ecri(5) = 't_max(X)'
    892  CALL histdef2d(iff,o_tke_max_srf(nsrf)%flag,o_tke_max_srf(nsrf)%name,"Max Turb. Kinetic Energy "//clnsurf(nsrf),"-")
     1012   type_ecri(6) = 't_max(X)'
     1013  CALL histdef2d(iff,clef_stations(iff), &
     1014  o_tke_max_srf(nsrf)%flag,o_tke_max_srf(nsrf)%name,"Max Turb. Kinetic Energy "//clnsurf(nsrf),"-")
    8931015   type_ecri(:) = type_ecri_files(:)
     1016  ENDIF
     1017
    8941018  endif
    895  CALL histdef2d(iff,o_albe_srf(nsrf)%flag,o_albe_srf(nsrf)%name,"Albedo VIS surf. "//clnsurf(nsrf),"-")
    896  CALL histdef2d(iff,o_rugs_srf(nsrf)%flag,o_rugs_srf(nsrf)%name,"Surface roughness "//clnsurf(nsrf),"m")
    897  CALL histdef2d(iff,o_ages_srf(nsrf)%flag,o_ages_srf(nsrf)%name,"Snow age", "day")
     1019
     1020 CALL histdef2d(iff,clef_stations(iff), &
     1021o_albe_srf(nsrf)%flag,o_albe_srf(nsrf)%name,"Albedo VIS surf. "//clnsurf(nsrf),"-")
     1022 CALL histdef2d(iff,clef_stations(iff), &
     1023o_rugs_srf(nsrf)%flag,o_rugs_srf(nsrf)%name,"Surface roughness "//clnsurf(nsrf),"m")
     1024 CALL histdef2d(iff,clef_stations(iff), &
     1025o_ages_srf(nsrf)%flag,o_ages_srf(nsrf)%name,"Snow age", "day")
    8981026END DO
    8991027
     
    9011029 IF (ok_ade.OR.ok_aie) THEN
    9021030
    903   CALL histdef2d(iff,o_od550aer%flag,o_od550aer%name, "Total aerosol optical depth at 550nm", "-")
    904   CALL histdef2d(iff,o_od865aer%flag,o_od865aer%name, "Total aerosol optical depth at 870nm", "-")
    905   CALL histdef2d(iff,o_absvisaer%flag,o_absvisaer%name, "Absorption aerosol visible optical depth", "-")
    906   CALL histdef2d(iff,o_od550lt1aer%flag,o_od550lt1aer%name, "Fine mode optical depth", "-")
    907 
    908 
    909   CALL histdef2d(iff,o_sconcso4%flag,o_sconcso4%name,"Surface Concentration of Sulfate ","kg/m3")
    910   CALL histdef2d(iff,o_sconcoa%flag,o_sconcoa%name,"Surface Concentration of Organic Aerosol ","kg/m3")
    911   CALL histdef2d(iff,o_sconcbc%flag,o_sconcbc%name,"Surface Concentration of Black Carbon ","kg/m3")
    912   CALL histdef2d(iff,o_sconcss%flag,o_sconcss%name,"Surface Concentration of Sea Salt ","kg/m3")
    913   CALL histdef2d(iff,o_sconcdust%flag,o_sconcdust%name,"Surface Concentration of Dust ","kg/m3")
    914   CALL histdef3d(iff,o_concso4%flag,o_concso4%name,"Concentration of Sulfate ","kg/m3")
    915   CALL histdef3d(iff,o_concoa%flag,o_concoa%name,"Concentration of Organic Aerosol ","kg/m3")
    916   CALL histdef3d(iff,o_concbc%flag,o_concbc%name,"Concentration of Black Carbon ","kg/m3")
    917   CALL histdef3d(iff,o_concss%flag,o_concss%name,"Concentration of Sea Salt ","kg/m3")
    918   CALL histdef3d(iff,o_concdust%flag,o_concdust%name,"Concentration of Dust ","kg/m3")
    919   CALL histdef2d(iff,o_loadso4%flag,o_loadso4%name,"Column Load of Sulfate ","kg/m2")
    920   CALL histdef2d(iff,o_loadoa%flag,o_loadoa%name,"Column Load of Organic Aerosol ","kg/m2")
    921   CALL histdef2d(iff,o_loadbc%flag,o_loadbc%name,"Column Load of Black Carbon ","kg/m2")
    922   CALL histdef2d(iff,o_loadss%flag,o_loadss%name,"Column Load of Sea Salt ","kg/m2")
    923   CALL histdef2d(iff,o_loaddust%flag,o_loaddust%name,"Column Load of Dust ","kg/m2")
     1031  CALL histdef2d(iff,clef_stations(iff), &
     1032o_od550aer%flag,o_od550aer%name, "Total aerosol optical depth at 550nm", "-")
     1033  CALL histdef2d(iff,clef_stations(iff), &
     1034o_od865aer%flag,o_od865aer%name, "Total aerosol optical depth at 870nm", "-")
     1035  CALL histdef2d(iff,clef_stations(iff), &
     1036o_absvisaer%flag,o_absvisaer%name, "Absorption aerosol visible optical depth", "-")
     1037  CALL histdef2d(iff,clef_stations(iff), &
     1038o_od550lt1aer%flag,o_od550lt1aer%name, "Fine mode optical depth", "-")
     1039
     1040
     1041  CALL histdef2d(iff,clef_stations(iff), &
     1042o_sconcso4%flag,o_sconcso4%name,"Surface Concentration of Sulfate ","kg/m3")
     1043  CALL histdef2d(iff,clef_stations(iff), &
     1044o_sconcoa%flag,o_sconcoa%name,"Surface Concentration of Organic Aerosol ","kg/m3")
     1045  CALL histdef2d(iff,clef_stations(iff), &
     1046o_sconcbc%flag,o_sconcbc%name,"Surface Concentration of Black Carbon ","kg/m3")
     1047  CALL histdef2d(iff,clef_stations(iff), &
     1048o_sconcss%flag,o_sconcss%name,"Surface Concentration of Sea Salt ","kg/m3")
     1049  CALL histdef2d(iff,clef_stations(iff), &
     1050o_sconcdust%flag,o_sconcdust%name,"Surface Concentration of Dust ","kg/m3")
     1051  CALL histdef3d(iff,clef_stations(iff), &
     1052o_concso4%flag,o_concso4%name,"Concentration of Sulfate ","kg/m3")
     1053  CALL histdef3d(iff,clef_stations(iff), &
     1054o_concoa%flag,o_concoa%name,"Concentration of Organic Aerosol ","kg/m3")
     1055  CALL histdef3d(iff,clef_stations(iff), &
     1056o_concbc%flag,o_concbc%name,"Concentration of Black Carbon ","kg/m3")
     1057  CALL histdef3d(iff,clef_stations(iff), &
     1058o_concss%flag,o_concss%name,"Concentration of Sea Salt ","kg/m3")
     1059  CALL histdef3d(iff,clef_stations(iff), &
     1060o_concdust%flag,o_concdust%name,"Concentration of Dust ","kg/m3")
     1061  CALL histdef2d(iff,clef_stations(iff), &
     1062o_loadso4%flag,o_loadso4%name,"Column Load of Sulfate ","kg/m2")
     1063  CALL histdef2d(iff,clef_stations(iff), &
     1064o_loadoa%flag,o_loadoa%name,"Column Load of Organic Aerosol ","kg/m2")
     1065  CALL histdef2d(iff,clef_stations(iff), &
     1066o_loadbc%flag,o_loadbc%name,"Column Load of Black Carbon ","kg/m2")
     1067  CALL histdef2d(iff,clef_stations(iff), &
     1068o_loadss%flag,o_loadss%name,"Column Load of Sea Salt ","kg/m2")
     1069  CALL histdef2d(iff,clef_stations(iff), &
     1070o_loaddust%flag,o_loaddust%name,"Column Load of Dust ","kg/m2")
    9241071
    9251072  DO naero = 1, naero_spc
    926   CALL histdef2d(iff,o_tausumaero(naero)%flag,o_tausumaero(naero)%name,"Aerosol Optical depth at 550 nm "//name_aero(naero),"1")
     1073  CALL histdef2d(iff,clef_stations(iff), &
     1074o_tausumaero(naero)%flag,o_tausumaero(naero)%name,"Aerosol Optical depth at 550 nm "//name_aero(naero),"1")
    9271075  END DO
    9281076 ENDIF
     
    9301078
    9311079 IF (ok_ade) THEN
    932   CALL histdef2d(iff,o_topswad%flag,o_topswad%name, "ADE at TOA", "W/m2")
    933   CALL histdef2d(iff,o_solswad%flag,o_solswad%name, "ADE at SRF", "W/m2")
    934 
    935  CALL histdef2d(iff,o_swtoaas_nat%flag,o_swtoaas_nat%name, "Natural aerosol radiative forcing all-sky at TOA", "W/m2")
    936  CALL histdef2d(iff,o_swsrfas_nat%flag,o_swsrfas_nat%name, "Natural aerosol radiative forcing all-sky at SRF", "W/m2")
    937  CALL histdef2d(iff,o_swtoacs_nat%flag,o_swtoacs_nat%name, "Natural aerosol radiative forcing clear-sky at TOA", "W/m2")
    938  CALL histdef2d(iff,o_swsrfcs_nat%flag,o_swsrfcs_nat%name, "Natural aerosol radiative forcing clear-sky at SRF", "W/m2")
    939 
    940  CALL histdef2d(iff,o_swtoaas_ant%flag,o_swtoaas_ant%name, "Anthropogenic aerosol radiative forcing all-sky at TOA", "W/m2")
    941  CALL histdef2d(iff,o_swsrfas_ant%flag,o_swsrfas_ant%name, "Anthropogenic aerosol radiative forcing all-sky at SRF", "W/m2")
    942  CALL histdef2d(iff,o_swtoacs_ant%flag,o_swtoacs_ant%name, "Anthropogenic aerosol radiative forcing clear-sky at TOA", "W/m2")
    943  CALL histdef2d(iff,o_swsrfcs_ant%flag,o_swsrfcs_ant%name, "Anthropogenic aerosol radiative forcing clear-sky at SRF", "W/m2")
     1080  CALL histdef2d(iff,clef_stations(iff), &
     1081o_topswad%flag,o_topswad%name, "ADE at TOA", "W/m2")
     1082  CALL histdef2d(iff,clef_stations(iff), &
     1083o_solswad%flag,o_solswad%name, "ADE at SRF", "W/m2")
     1084
     1085 CALL histdef2d(iff,clef_stations(iff), &
     1086o_swtoaas_nat%flag,o_swtoaas_nat%name, "Natural aerosol radiative forcing all-sky at TOA", "W/m2")
     1087 CALL histdef2d(iff,clef_stations(iff), &
     1088o_swsrfas_nat%flag,o_swsrfas_nat%name, "Natural aerosol radiative forcing all-sky at SRF", "W/m2")
     1089 CALL histdef2d(iff,clef_stations(iff), &
     1090o_swtoacs_nat%flag,o_swtoacs_nat%name, "Natural aerosol radiative forcing clear-sky at TOA", "W/m2")
     1091 CALL histdef2d(iff,clef_stations(iff), &
     1092o_swsrfcs_nat%flag,o_swsrfcs_nat%name, "Natural aerosol radiative forcing clear-sky at SRF", "W/m2")
     1093
     1094 CALL histdef2d(iff,clef_stations(iff), &
     1095o_swtoaas_ant%flag,o_swtoaas_ant%name, "Anthropogenic aerosol radiative forcing all-sky at TOA", "W/m2")
     1096 CALL histdef2d(iff,clef_stations(iff), &
     1097o_swsrfas_ant%flag,o_swsrfas_ant%name, "Anthropogenic aerosol radiative forcing all-sky at SRF", "W/m2")
     1098 CALL histdef2d(iff,clef_stations(iff), &
     1099o_swtoacs_ant%flag,o_swtoacs_ant%name, "Anthropogenic aerosol radiative forcing clear-sky at TOA", "W/m2")
     1100 CALL histdef2d(iff,clef_stations(iff), &
     1101o_swsrfcs_ant%flag,o_swsrfcs_ant%name, "Anthropogenic aerosol radiative forcing clear-sky at SRF", "W/m2")
    9441102
    9451103 IF (.NOT. aerosol_couple) THEN
    946  CALL histdef2d(iff,o_swtoacf_nat%flag,o_swtoacf_nat%name, "Natural aerosol impact on cloud radiative forcing at TOA", "W/m2")
    947  CALL histdef2d(iff,o_swsrfcf_nat%flag,o_swsrfcf_nat%name, "Natural aerosol impact on cloud radiative forcing  at SRF", "W/m2")
    948  CALL histdef2d(iff,o_swtoacf_ant%flag,o_swtoacf_ant%name, "Anthropogenic aerosol impact on cloud radiative forcing at TOA", "W/m2")
    949  CALL histdef2d(iff,o_swsrfcf_ant%flag,o_swsrfcf_ant%name, "Anthropogenic aerosol impact on cloud radiative forcing at SRF", "W/m2")
    950  CALL histdef2d(iff,o_swtoacf_zero%flag,o_swtoacf_zero%name, "Cloud radiative forcing (allsky-clearsky fluxes) at TOA", "W/m2")
    951  CALL histdef2d(iff,o_swsrfcf_zero%flag,o_swsrfcf_zero%name, "Cloud radiative forcing (allsky-clearsky fluxes) at SRF", "W/m2")
     1104 CALL histdef2d(iff,clef_stations(iff), &
     1105o_swtoacf_nat%flag,o_swtoacf_nat%name, "Natural aerosol impact on cloud radiative forcing at TOA", "W/m2")
     1106 CALL histdef2d(iff,clef_stations(iff), &
     1107o_swsrfcf_nat%flag,o_swsrfcf_nat%name, "Natural aerosol impact on cloud radiative forcing  at SRF", "W/m2")
     1108 CALL histdef2d(iff,clef_stations(iff), &
     1109o_swtoacf_ant%flag,o_swtoacf_ant%name, "Anthropogenic aerosol impact on cloud radiative forcing at TOA", "W/m2")
     1110 CALL histdef2d(iff,clef_stations(iff), &
     1111o_swsrfcf_ant%flag,o_swsrfcf_ant%name, "Anthropogenic aerosol impact on cloud radiative forcing at SRF", "W/m2")
     1112 CALL histdef2d(iff,clef_stations(iff), &
     1113o_swtoacf_zero%flag,o_swtoacf_zero%name, "Cloud radiative forcing (allsky-clearsky fluxes) at TOA", "W/m2")
     1114 CALL histdef2d(iff,clef_stations(iff), &
     1115o_swsrfcf_zero%flag,o_swsrfcf_zero%name, "Cloud radiative forcing (allsky-clearsky fluxes) at SRF", "W/m2")
    9521116 ENDIF
    9531117
     
    9551119
    9561120 IF (ok_aie) THEN
    957   CALL histdef2d(iff,o_topswai%flag,o_topswai%name, "AIE at TOA", "W/m2")
    958   CALL histdef2d(iff,o_solswai%flag,o_solswai%name, "AIE at SFR", "W/m2")
     1121  CALL histdef2d(iff,clef_stations(iff), &
     1122o_topswai%flag,o_topswai%name, "AIE at TOA", "W/m2")
     1123  CALL histdef2d(iff,clef_stations(iff), &
     1124o_solswai%flag,o_solswai%name, "AIE at SFR", "W/m2")
    9591125!Cloud droplet number concentration
    960   CALL histdef3d(iff,o_scdnc%flag,o_scdnc%name, "Cloud droplet number concentration","m-3")
    961   CALL histdef2d(iff,o_cldncl%flag,o_cldncl%name, "CDNC at top of liquid water cloud", "m-3")
    962   CALL histdef3d(iff,o_reffclws%flag,o_reffclws%name, "Stratiform Cloud Droplet Effective Radius","m")
    963   CALL histdef3d(iff,o_reffclwc%flag,o_reffclwc%name, "Convective Cloud Droplet Effective Radius","m")
    964   CALL histdef2d(iff,o_cldnvi%flag,o_cldnvi%name, "Column Integrated Cloud Droplet Number", "m-2")
    965   CALL histdef3d(iff,o_lcc3d%flag,o_lcc3d%name, "Cloud liquid fraction","1")
    966   CALL histdef3d(iff,o_lcc3dcon%flag,o_lcc3dcon%name, "Convective cloud liquid fraction","1")
    967   CALL histdef3d(iff,o_lcc3dstra%flag,o_lcc3dstra%name, "Stratiform cloud liquid fraction","1")
    968   CALL histdef2d(iff,o_lcc%flag,o_lcc%name, "Cloud liquid fraction at top of cloud","1")
    969   CALL histdef2d(iff,o_reffclwtop%flag,o_reffclwtop%name, "Droplet effective radius at top of liquid water cloud", "m")
     1126  CALL histdef3d(iff,clef_stations(iff), &
     1127o_scdnc%flag,o_scdnc%name, "Cloud droplet number concentration","m-3")
     1128  CALL histdef2d(iff,clef_stations(iff), &
     1129o_cldncl%flag,o_cldncl%name, "CDNC at top of liquid water cloud", "m-3")
     1130  CALL histdef3d(iff,clef_stations(iff), &
     1131o_reffclws%flag,o_reffclws%name, "Stratiform Cloud Droplet Effective Radius (aerosol diags.)","m")
     1132  CALL histdef3d(iff,clef_stations(iff), &
     1133o_reffclwc%flag,o_reffclwc%name, "Convective Cloud Droplet Effective Radius (aerosol diags.)","m")
     1134  CALL histdef2d(iff,clef_stations(iff), &
     1135o_cldnvi%flag,o_cldnvi%name, "Column Integrated Cloud Droplet Number", "m-2")
     1136  CALL histdef3d(iff,clef_stations(iff), &
     1137o_lcc3d%flag,o_lcc3d%name, "Cloud liquid fraction","1")
     1138  CALL histdef3d(iff,clef_stations(iff), &
     1139o_lcc3dcon%flag,o_lcc3dcon%name, "Convective cloud liquid fraction","1")
     1140  CALL histdef3d(iff,clef_stations(iff), &
     1141o_lcc3dstra%flag,o_lcc3dstra%name, "Stratiform cloud liquid fraction","1")
     1142  CALL histdef2d(iff,clef_stations(iff), &
     1143o_lcc%flag,o_lcc%name, "Cloud liquid fraction at top of cloud","1")
     1144  CALL histdef2d(iff,clef_stations(iff), &
     1145o_reffclwtop%flag,o_reffclwtop%name, "Droplet effective radius at top of liquid water cloud", "m")
    9701146 ENDIF
    9711147
    9721148
    973  CALL histdef2d(iff,o_alb1%flag,o_alb1%name, "Surface VIS albedo", "-")
    974  CALL histdef2d(iff,o_alb2%flag,o_alb2%name, "Surface Near IR albedo", "-")
    975  CALL histdef2d(iff,o_cdrm%flag,o_cdrm%name, "Momentum drag coef.", "-")
    976  CALL histdef2d(iff,o_cdrh%flag,o_cdrh%name, "Heat drag coef.", "-" )
    977  CALL histdef2d(iff,o_cldl%flag,o_cldl%name, "Low-level cloudiness", "-")
    978  CALL histdef2d(iff,o_cldm%flag,o_cldm%name, "Mid-level cloudiness", "-")
    979  CALL histdef2d(iff,o_cldh%flag,o_cldh%name, "High-level cloudiness", "-")
    980  CALL histdef2d(iff,o_cldt%flag,o_cldt%name, "Total cloudiness", "-")
    981  CALL histdef2d(iff,o_cldq%flag,o_cldq%name, "Cloud liquid water path", "kg/m2")
    982  CALL histdef2d(iff,o_lwp%flag,o_lwp%name, "Cloud water path", "kg/m2")
    983  CALL histdef2d(iff,o_iwp%flag,o_iwp%name, "Cloud ice water path", "kg/m2" )
    984  CALL histdef2d(iff,o_ue%flag,o_ue%name, "Zonal energy transport", "-")
    985  CALL histdef2d(iff,o_ve%flag,o_ve%name, "Merid energy transport", "-")
    986  CALL histdef2d(iff,o_uq%flag,o_uq%name, "Zonal humidity transport", "-")
    987  CALL histdef2d(iff,o_vq%flag,o_vq%name, "Merid humidity transport", "-")
     1149 CALL histdef2d(iff,clef_stations(iff), &
     1150o_alb1%flag,o_alb1%name, "Surface VIS albedo", "-")
     1151 CALL histdef2d(iff,clef_stations(iff), &
     1152o_alb2%flag,o_alb2%name, "Surface Near IR albedo", "-")
     1153 CALL histdef2d(iff,clef_stations(iff), &
     1154o_cdrm%flag,o_cdrm%name, "Momentum drag coef.", "-")
     1155 CALL histdef2d(iff,clef_stations(iff), &
     1156o_cdrh%flag,o_cdrh%name, "Heat drag coef.", "-" )
     1157 CALL histdef2d(iff,clef_stations(iff), &
     1158o_cldl%flag,o_cldl%name, "Low-level cloudiness", "-")
     1159 CALL histdef2d(iff,clef_stations(iff), &
     1160o_cldm%flag,o_cldm%name, "Mid-level cloudiness", "-")
     1161 CALL histdef2d(iff,clef_stations(iff), &
     1162o_cldh%flag,o_cldh%name, "High-level cloudiness", "-")
     1163 CALL histdef2d(iff,clef_stations(iff), &
     1164o_cldt%flag,o_cldt%name, "Total cloudiness", "-")
     1165 CALL histdef2d(iff,clef_stations(iff), &
     1166o_cldq%flag,o_cldq%name, "Cloud liquid water path", "kg/m2")
     1167 CALL histdef2d(iff,clef_stations(iff), &
     1168o_lwp%flag,o_lwp%name, "Cloud water path", "kg/m2")
     1169 CALL histdef2d(iff,clef_stations(iff), &
     1170o_iwp%flag,o_iwp%name, "Cloud ice water path", "kg/m2" )
     1171 CALL histdef2d(iff,clef_stations(iff), &
     1172o_ue%flag,o_ue%name, "Zonal energy transport", "-")
     1173 CALL histdef2d(iff,clef_stations(iff), &
     1174o_ve%flag,o_ve%name, "Merid energy transport", "-")
     1175 CALL histdef2d(iff,clef_stations(iff), &
     1176o_uq%flag,o_uq%name, "Zonal humidity transport", "-")
     1177 CALL histdef2d(iff,clef_stations(iff), &
     1178o_vq%flag,o_vq%name, "Merid humidity transport", "-")
    9881179
    9891180     IF(iflag_con.GE.3) THEN ! sb
    990  CALL histdef2d(iff,o_cape%flag,o_cape%name, "Conv avlbl pot ener", "J/kg")
    991  CALL histdef2d(iff,o_pbase%flag,o_pbase%name, "Cld base pressure", "Pa")
    992  CALL histdef2d(iff,o_ptop%flag,o_ptop%name, "Cld top pressure", "Pa")
    993  CALL histdef2d(iff,o_fbase%flag,o_fbase%name, "Cld base mass flux", "kg/m2/s")
    994  CALL histdef2d(iff,o_prw%flag,o_prw%name, "Precipitable water", "kg/m2")
     1181 CALL histdef2d(iff,clef_stations(iff), &
     1182o_cape%flag,o_cape%name, "Conv avlbl pot ener", "J/kg")
     1183 CALL histdef2d(iff,clef_stations(iff), &
     1184o_pbase%flag,o_pbase%name, "Cld base pressure", "Pa")
     1185 CALL histdef2d(iff,clef_stations(iff), &
     1186o_ptop%flag,o_ptop%name, "Cld top pressure", "Pa")
     1187 CALL histdef2d(iff,clef_stations(iff), &
     1188o_fbase%flag,o_fbase%name, "Cld base mass flux", "kg/m2/s")
     1189 CALL histdef2d(iff,clef_stations(iff), &
     1190o_prw%flag,o_prw%name, "Precipitable water", "kg/m2")
     1191  IF (.NOT.clef_stations(iff)) THEN
     1192!
     1193!IM: there is no way to have one single value in a netcdf file
     1194!
     1195    type_ecri(1) = 't_max(X)'
     1196    type_ecri(2) = 't_max(X)'
     1197    type_ecri(3) = 't_max(X)'
     1198    type_ecri(4) = 't_max(X)'
     1199    type_ecri(5) = 't_max(X)'
     1200    type_ecri(6) = 't_max(X)'
     1201    CALL histdef2d(iff,clef_stations(iff), &
     1202  o_cape_max%flag,o_cape_max%name, "CAPE max.", "J/kg")
     1203  ENDIF
     1204   type_ecri(:) = type_ecri_files(:)
     1205 CALL histdef3d(iff,clef_stations(iff), &
     1206o_upwd%flag,o_upwd%name, "saturated updraft", "kg/m2/s")
     1207 CALL histdef3d(iff,clef_stations(iff), &
     1208o_Ma%flag,o_Ma%name, "undilute adiab updraft", "kg/m2/s")
     1209 CALL histdef3d(iff,clef_stations(iff), &
     1210o_dnwd%flag,o_dnwd%name, "saturated downdraft", "kg/m2/s")
     1211 CALL histdef3d(iff,clef_stations(iff), &
     1212o_dnwd0%flag,o_dnwd0%name, "unsat. downdraft", "kg/m2/s")
     1213 CALL histdef3d(iff,clef_stations(iff), &
     1214o_mc%flag,o_mc%name, "Convective mass flux", "kg/m2/s")
     1215   type_ecri(1) = 'inst(X)'
     1216   type_ecri(2) = 'inst(X)'
     1217   type_ecri(3) = 'inst(X)'
     1218   type_ecri(4) = 'inst(X)'
     1219   type_ecri(5) = 'inst(X)'
     1220   type_ecri(6) = 'inst(X)'
     1221 CALL histdef2d(iff,clef_stations(iff), &
     1222o_ftime_con%flag,o_ftime_con%name, "Fraction of time convection Occurs", " ")
     1223   type_ecri(:) = type_ecri_files(:)
     1224     ENDIF !iflag_con .GE. 3
     1225
     1226 CALL histdef2d(iff,clef_stations(iff), &
     1227o_s_pblh%flag,o_s_pblh%name, "Boundary Layer Height", "m")
     1228 CALL histdef2d(iff,clef_stations(iff), &
     1229o_s_pblt%flag,o_s_pblt%name, "t at Boundary Layer Height", "K")
     1230 CALL histdef2d(iff,clef_stations(iff), &
     1231o_s_lcl%flag,o_s_lcl%name, "Condensation level", "m")
     1232 CALL histdef2d(iff,clef_stations(iff), &
     1233o_s_therm%flag,o_s_therm%name, "Exces du thermique", "K")
     1234!IM : Les champs suivants (s_oliqCL, s_cteiCL, s_trmb1, s_trmb2, s_trmb3) ne sont pas definis dans HBTM.F
     1235!CALL histdef2d(iff,clef_stations(iff), &
     1236!o_s_capCL%flag,o_s_capCL%name, "Conv avlbl pot enerfor ABL", "J/m2" )
     1237!CALL histdef2d(iff,clef_stations(iff), &
     1238!o_s_oliqCL%flag,o_s_oliqCL%name, "Liq Water in BL", "kg/m2")
     1239!CALL histdef2d(iff,clef_stations(iff), &
     1240!o_s_cteiCL%flag,o_s_cteiCL%name, "Instability criteria(ABL)", "K")
     1241!CALL histdef2d(iff,clef_stations(iff), &
     1242!o_s_trmb1%flag,o_s_trmb1%name, "deep_cape(HBTM2)", "J/m2")
     1243!CALL histdef2d(iff,clef_stations(iff), &
     1244!o_s_trmb2%flag,o_s_trmb2%name, "inhibition (HBTM2)", "J/m2")
     1245!CALL histdef2d(iff,clef_stations(iff), &
     1246!o_s_trmb3%flag,o_s_trmb3%name, "Point Omega (HBTM2)", "m")
     1247
     1248! Champs interpolles sur des niveaux de pression
     1249
     1250   type_ecri(1) = 'inst(X)'
     1251   type_ecri(2) = 'inst(X)'
     1252   type_ecri(3) = 'inst(X)'
     1253   type_ecri(4) = 'inst(X)'
     1254   type_ecri(5) = 'inst(X)'
     1255   type_ecri(6) = 'inst(X)'
     1256
     1257! Attention a reverifier
     1258
     1259        ilev=0       
     1260        DO k=1, nlevSTD
     1261     bb2=clevSTD(k)
     1262     IF(bb2.EQ."850".OR.bb2.EQ."700".OR.bb2.EQ."500".OR.bb2.EQ."200" &
     1263.OR.bb2.EQ."100".OR.bb2.EQ."50".OR.bb2.EQ."10")THEN
     1264      ilev=ilev+1
     1265!     print*,'ilev k bb2 flag name ',ilev,k, bb2,o_uSTDlevs(ilev)%flag,o_uSTDlevs(ilev)%name
     1266 CALL histdef2d(iff,clef_stations(iff), &
     1267o_uSTDlevs(ilev)%flag,o_uSTDlevs(ilev)%name,"Zonal wind "//bb2//"hPa", "m/s")
     1268 CALL histdef2d(iff,clef_stations(iff), &
     1269o_vSTDlevs(ilev)%flag,o_vSTDlevs(ilev)%name,"Meridional wind "//bb2//"hPa", "m/s")
     1270 CALL histdef2d(iff,clef_stations(iff), &
     1271o_wSTDlevs(ilev)%flag,o_wSTDlevs(ilev)%name,"Vertical wind "//bb2//"hPa", "Pa/s")
     1272 CALL histdef2d(iff,clef_stations(iff), &
     1273o_zSTDlevs(ilev)%flag,o_zSTDlevs(ilev)%name,"Geopotential height "//bb2//"hPa", "m")
     1274 CALL histdef2d(iff,clef_stations(iff), &
     1275o_qSTDlevs(ilev)%flag,o_qSTDlevs(ilev)%name,"Specific humidity "//bb2//"hPa", "kg/kg" )
     1276 CALL histdef2d(iff,clef_stations(iff), &
     1277o_tSTDlevs(ilev)%flag,o_tSTDlevs(ilev)%name,"Temperature "//bb2//"hPa", "K")
     1278     ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR."500".OR.bb2.EQ."200".OR.bb2.EQ."50".OR.bb2.EQ."10")
     1279       ENDDO
     1280   type_ecri(:) = type_ecri_files(:)
     1281
     1282 CALL histdef2d(iff,clef_stations(iff), &
     1283o_t_oce_sic%flag,o_t_oce_sic%name, "Temp mixte oce-sic", "K")
     1284
     1285 IF (type_ocean=='slab') &
     1286     CALL histdef2d(iff,clef_stations(iff), &
     1287o_slab_bils%flag, o_slab_bils%name,"Bilan au sol sur ocean slab", "W/m2")
     1288
     1289! Couplage conv-CL
     1290 IF (iflag_con.GE.3) THEN
     1291    IF (iflag_coupl.EQ.1) THEN
     1292 CALL histdef2d(iff,clef_stations(iff), &
     1293o_ale_bl%flag,o_ale_bl%name, "ALE BL", "m2/s2")
     1294 CALL histdef2d(iff,clef_stations(iff), &
     1295o_alp_bl%flag,o_alp_bl%name, "ALP BL", "m2/s2")
     1296    ENDIF
     1297 ENDIF !(iflag_con.GE.3)
     1298
     1299 CALL histdef2d(iff,clef_stations(iff), &
     1300o_weakinv%flag,o_weakinv%name, "Weak inversion", "-")
     1301 CALL histdef2d(iff,clef_stations(iff), &
     1302o_dthmin%flag,o_dthmin%name, "dTheta mini", "K/m")
     1303 CALL histdef2d(iff,clef_stations(iff), &
     1304o_rh2m%flag,o_rh2m%name, "Relative humidity at 2m", "%" )
     1305
     1306  IF (.NOT.clef_stations(iff)) THEN
     1307!
     1308!IM: there is no way to have one single value in a netcdf file
     1309!
     1310   type_ecri(1) = 't_min(X)'
     1311   type_ecri(2) = 't_min(X)'
     1312   type_ecri(3) = 't_min(X)'
     1313   type_ecri(4) = 't_min(X)'
     1314   type_ecri(5) = 't_min(X)'
     1315   type_ecri(6) = 't_min(X)'
     1316   CALL histdef2d(iff,clef_stations(iff),o_rh2m_min%flag,o_rh2m_min%name, "Min Relative humidity at 2m", "%" )
    9951317   type_ecri(1) = 't_max(X)'
    9961318   type_ecri(2) = 't_max(X)'
     
    9981320   type_ecri(4) = 't_max(X)'
    9991321   type_ecri(5) = 't_max(X)'
    1000  CALL histdef2d(iff,o_cape_max%flag,o_cape_max%name, "CAPE max.", "J/kg")
     1322   type_ecri(6) = 't_max(X)'
     1323   CALL histdef2d(iff,clef_stations(iff),o_rh2m_max%flag,o_rh2m_max%name, "Max Relative humidity at 2m", "%" )
     1324  ENDIF 
     1325
    10011326   type_ecri(:) = type_ecri_files(:)
    1002  CALL histdef3d(iff,o_upwd%flag,o_upwd%name, "saturated updraft", "kg/m2/s")
    1003  CALL histdef3d(iff,o_Ma%flag,o_Ma%name, "undilute adiab updraft", "kg/m2/s")
    1004  CALL histdef3d(iff,o_dnwd%flag,o_dnwd%name, "saturated downdraft", "kg/m2/s")
    1005  CALL histdef3d(iff,o_dnwd0%flag,o_dnwd0%name, "unsat. downdraft", "kg/m2/s")
    1006  CALL histdef3d(iff,o_mc%flag,o_mc%name, "Convective mass flux", "kg/m2/s")
    1007    type_ecri(1) = 'inst(X)'
    1008    type_ecri(2) = 'inst(X)'
    1009    type_ecri(3) = 'inst(X)'
    1010    type_ecri(4) = 'inst(X)'
    1011    type_ecri(5) = 'inst(X)'
    1012  CALL histdef2d(iff,o_ftime_con%flag,o_ftime_con%name, "Fraction of time convection Occurs", " ")
    1013    type_ecri(:) = type_ecri_files(:)
    1014      ENDIF !iflag_con .GE. 3
    1015 
    1016  CALL histdef2d(iff,o_s_pblh%flag,o_s_pblh%name, "Boundary Layer Height", "m")
    1017  CALL histdef2d(iff,o_s_pblt%flag,o_s_pblt%name, "t at Boundary Layer Height", "K")
    1018  CALL histdef2d(iff,o_s_lcl%flag,o_s_lcl%name, "Condensation level", "m")
    1019  CALL histdef2d(iff,o_s_therm%flag,o_s_therm%name, "Exces du thermique", "K")
    1020 !IM : Les champs suivants (s_oliqCL, s_cteiCL, s_trmb1, s_trmb2, s_trmb3) ne sont pas definis dans HBTM.F
    1021 !CALL histdef2d(iff,o_s_capCL%flag,o_s_capCL%name, "Conv avlbl pot enerfor ABL", "J/m2" )
    1022 !CALL histdef2d(iff,o_s_oliqCL%flag,o_s_oliqCL%name, "Liq Water in BL", "kg/m2")
    1023 !CALL histdef2d(iff,o_s_cteiCL%flag,o_s_cteiCL%name, "Instability criteria(ABL)", "K")
    1024 !CALL histdef2d(iff,o_s_trmb1%flag,o_s_trmb1%name, "deep_cape(HBTM2)", "J/m2")
    1025 !CALL histdef2d(iff,o_s_trmb2%flag,o_s_trmb2%name, "inhibition (HBTM2)", "J/m2")
    1026 !CALL histdef2d(iff,o_s_trmb3%flag,o_s_trmb3%name, "Point Omega (HBTM2)", "m")
    1027 
    1028 ! Champs interpolles sur des niveaux de pression
    1029 
    1030    type_ecri(1) = 'inst(X)'
    1031    type_ecri(2) = 'inst(X)'
    1032    type_ecri(3) = 'inst(X)'
    1033    type_ecri(4) = 'inst(X)'
    1034    type_ecri(5) = 'inst(X)'
    1035 
    1036 ! Attention a reverifier
    1037 
    1038         ilev=0       
    1039         DO k=1, nlevSTD
    1040 !     IF(k.GE.2.AND.k.LE.12) bb2=clevSTD(k)
    1041      bb2=clevSTD(k)
    1042      IF(bb2.EQ."850".OR.bb2.EQ."700".OR.bb2.EQ."500".OR.bb2.EQ."200".OR.bb2.EQ."50".OR.bb2.EQ."10")THEN
    1043       ilev=ilev+1
    1044       print*,'ilev k bb2 flag name ',ilev,k, bb2,o_uSTDlevs(ilev)%flag,o_uSTDlevs(ilev)%name
    1045  CALL histdef2d(iff,o_uSTDlevs(ilev)%flag,o_uSTDlevs(ilev)%name,"Zonal wind "//bb2//"hPa", "m/s")
    1046  CALL histdef2d(iff,o_vSTDlevs(ilev)%flag,o_vSTDlevs(ilev)%name,"Meridional wind "//bb2//"hPa", "m/s")
    1047  CALL histdef2d(iff,o_wSTDlevs(ilev)%flag,o_wSTDlevs(ilev)%name,"Vertical wind "//bb2//"hPa", "Pa/s")
    1048  CALL histdef2d(iff,o_zSTDlevs(ilev)%flag,o_zSTDlevs(ilev)%name,"Geopotential height "//bb2//"hPa", "m")
    1049  CALL histdef2d(iff,o_qSTDlevs(ilev)%flag,o_qSTDlevs(ilev)%name,"Specific humidity "//bb2//"hPa", "kg/kg" )
    1050  CALL histdef2d(iff,o_tSTDlevs(ilev)%flag,o_tSTDlevs(ilev)%name,"Temperature "//bb2//"hPa", "K")
    1051      ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR."500".OR.bb2.EQ."200".OR.bb2.EQ."50".OR.bb2.EQ."10")
    1052        ENDDO
    1053    type_ecri(:) = type_ecri_files(:)
    1054 
    1055  CALL histdef2d(iff,o_t_oce_sic%flag,o_t_oce_sic%name, "Temp mixte oce-sic", "K")
    1056 
    1057  IF (type_ocean=='slab') &
    1058      CALL histdef2d(iff,o_slab_bils%flag, o_slab_bils%name,"Bilan au sol sur ocean slab", "W/m2")
    1059 
    1060 ! Couplage conv-CL
    1061  IF (iflag_con.GE.3) THEN
    1062     IF (iflag_coupl.EQ.1) THEN
    1063  CALL histdef2d(iff,o_ale_bl%flag,o_ale_bl%name, "ALE BL", "m2/s2")
    1064  CALL histdef2d(iff,o_alp_bl%flag,o_alp_bl%name, "ALP BL", "m2/s2")
    1065     ENDIF
    1066  ENDIF !(iflag_con.GE.3)
    1067 
    1068  CALL histdef2d(iff,o_weakinv%flag,o_weakinv%name, "Weak inversion", "-")
    1069  CALL histdef2d(iff,o_dthmin%flag,o_dthmin%name, "dTheta mini", "K/m")
    1070  CALL histdef2d(iff,o_rh2m%flag,o_rh2m%name, "Relative humidity at 2m", "%" )
    1071    type_ecri(1) = 't_min(X)'
    1072    type_ecri(2) = 't_min(X)'
    1073    type_ecri(3) = 't_min(X)'
    1074    type_ecri(4) = 't_min(X)'
    1075    type_ecri(5) = 't_min(X)'
    1076  CALL histdef2d(iff,o_rh2m_min%flag,o_rh2m_min%name, "Min Relative humidity at 2m", "%" )
     1327 CALL histdef2d(iff,clef_stations(iff),o_qsat2m%flag,o_qsat2m%name, "Saturant humidity at 2m", "%")
     1328 CALL histdef2d(iff,clef_stations(iff),o_tpot%flag,o_tpot%name, "Surface air potential temperature", "K")
     1329 CALL histdef2d(iff,clef_stations(iff), &
     1330o_tpote%flag,o_tpote%name, "Surface air equivalent potential temperature", "K")
     1331 CALL histdef2d(iff,clef_stations(iff),o_SWnetOR%flag,o_SWnetOR%name, "Sfce net SW radiation OR", "W/m2")
     1332 CALL histdef2d(iff,clef_stations(iff),o_SWdownOR%flag,o_SWdownOR%name, "Sfce incident SW radiation OR", "W/m2")
     1333 CALL histdef2d(iff,clef_stations(iff),o_LWdownOR%flag,o_LWdownOR%name, "Sfce incident LW radiation OR", "W/m2")
     1334 CALL histdef2d(iff,clef_stations(iff),o_snowl%flag,o_snowl%name, "Solid Large-scale Precip.", "kg/(m2*s)")
     1335
     1336 CALL histdef2d(iff,clef_stations(iff),o_solldown%flag,o_solldown%name, "Down. IR rad. at surface", "W/m2")
     1337 CALL histdef2d(iff,clef_stations(iff),o_dtsvdfo%flag,o_dtsvdfo%name, "Boundary-layer dTs(o)", "K/s")
     1338 CALL histdef2d(iff,clef_stations(iff),o_dtsvdft%flag,o_dtsvdft%name, "Boundary-layer dTs(t)", "K/s")
     1339 CALL histdef2d(iff,clef_stations(iff),o_dtsvdfg%flag,o_dtsvdfg%name, "Boundary-layer dTs(g)", "K/s")
     1340 CALL histdef2d(iff,clef_stations(iff),o_dtsvdfi%flag,o_dtsvdfi%name, "Boundary-layer dTs(g)", "K/s")
     1341 CALL histdef2d(iff,clef_stations(iff),o_rugs%flag,o_rugs%name, "rugosity", "-" )
     1342
     1343! Champs 3D:
     1344 CALL histdef3d(iff,clef_stations(iff),o_ec550aer%flag,o_ec550aer%name, "Extinction at 550nm", "m^-1")
     1345 CALL histdef3d(iff,clef_stations(iff),o_lwcon%flag,o_lwcon%name, "Cloud liquid water content", "kg/kg")
     1346 CALL histdef3d(iff,clef_stations(iff),o_iwcon%flag,o_iwcon%name, "Cloud ice water content", "kg/kg")
     1347 CALL histdef3d(iff,clef_stations(iff),o_temp%flag,o_temp%name, "Air temperature", "K" )
     1348 CALL histdef3d(iff,clef_stations(iff),o_theta%flag,o_theta%name, "Potential air temperature", "K" )
     1349 CALL histdef3d(iff,clef_stations(iff),o_ovap%flag,o_ovap%name, "Specific humidity", "kg/kg" )
     1350 CALL histdef3d(iff,clef_stations(iff), &
     1351o_ovapinit%flag,o_ovapinit%name, "Specific humidity (begin of timestep)", "kg/kg" )
     1352 CALL histdef3d(iff,clef_stations(iff), &
     1353o_geop%flag,o_geop%name, "Geopotential height", "m2/s2")
     1354 CALL histdef3d(iff,clef_stations(iff), &
     1355o_vitu%flag,o_vitu%name, "Zonal wind", "m/s" )
     1356 CALL histdef3d(iff,clef_stations(iff), &
     1357o_vitv%flag,o_vitv%name, "Meridional wind", "m/s" )
     1358 CALL histdef3d(iff,clef_stations(iff), &
     1359o_vitw%flag,o_vitw%name, "Vertical wind", "Pa/s" )
     1360 CALL histdef3d(iff,clef_stations(iff), &
     1361o_pres%flag,o_pres%name, "Air pressure", "Pa" )
     1362 CALL histdef3d(iff,clef_stations(iff), &
     1363o_paprs%flag,o_paprs%name, "Air pressure Inter-Couches", "Pa" )
     1364 CALL histdef3d(iff,clef_stations(iff), &
     1365o_zfull%flag,o_zfull%name, "Altitude of full pressure levels", "m" )
     1366 CALL histdef3d(iff,clef_stations(iff), &
     1367o_zhalf%flag,o_zhalf%name, "Altitude of half pressure levels", "m" )
     1368 CALL histdef3d(iff,clef_stations(iff), &
     1369o_rneb%flag,o_rneb%name, "Cloud fraction", "-")
     1370 CALL histdef3d(iff,clef_stations(iff), &
     1371o_rnebcon%flag,o_rnebcon%name, "Convective Cloud Fraction", "-")
     1372 CALL histdef3d(iff,clef_stations(iff), &
     1373o_rhum%flag,o_rhum%name, "Relative humidity", "-")
     1374 CALL histdef3d(iff,clef_stations(iff), &
     1375o_ozone%flag,o_ozone%name, "Ozone mole fraction", "-")
     1376 if (read_climoz == 2) &
     1377      CALL histdef3d(iff,clef_stations(iff), &
     1378o_ozone_light%flag,o_ozone_light%name, &
     1379      "Daylight ozone mole fraction", "-")
     1380 CALL histdef3d(iff,clef_stations(iff), &
     1381o_dtphy%flag,o_dtphy%name, "Physics dT", "K/s")
     1382 CALL histdef3d(iff,clef_stations(iff), &
     1383o_dqphy%flag,o_dqphy%name, "Physics dQ", "(kg/kg)/s")
     1384 CALL histdef3d(iff,clef_stations(iff), &
     1385o_cldtau%flag,o_cldtau%name, "Cloud optical thickness", "1")
     1386 CALL histdef3d(iff,clef_stations(iff), &
     1387o_cldemi%flag,o_cldemi%name, "Cloud optical emissivity", "1")
     1388!IM: bug ?? dimensionnement variables (klon,klev+1) pmflxr, pmflxs, prfl, psfl
     1389 CALL histdef3d(iff,clef_stations(iff), &
     1390o_pr_con_l%flag,o_pr_con_l%name, "Convective precipitation lic", " ")
     1391 CALL histdef3d(iff,clef_stations(iff), &
     1392o_pr_con_i%flag,o_pr_con_i%name, "Convective precipitation ice", " ")
     1393 CALL histdef3d(iff,clef_stations(iff), &
     1394o_pr_lsc_l%flag,o_pr_lsc_l%name, "Large scale precipitation lic", " ")
     1395 CALL histdef3d(iff,clef_stations(iff), &
     1396o_pr_lsc_i%flag,o_pr_lsc_i%name, "Large scale precipitation ice", " ")
     1397!Cloud droplet effective radius
     1398 CALL histdef3d(iff,clef_stations(iff), &
     1399o_re%flag,o_re%name, "Cloud droplet effective radius","um")
     1400 CALL histdef3d(iff,clef_stations(iff), &
     1401o_fl%flag,o_fl%name, "Denominator of Cloud droplet effective radius"," ")
     1402!FH Sorties pour la couche limite
     1403     if (iflag_pbl>1) then
     1404 CALL histdef3d(iff,clef_stations(iff), &
     1405o_tke%flag,o_tke%name, "TKE", "m2/s2")
     1406  IF (.NOT.clef_stations(iff)) THEN
     1407!
     1408!IM: there is no way to have one single value in a netcdf file
     1409!
    10771410   type_ecri(1) = 't_max(X)'
    10781411   type_ecri(2) = 't_max(X)'
     
    10801413   type_ecri(4) = 't_max(X)'
    10811414   type_ecri(5) = 't_max(X)'
    1082  CALL histdef2d(iff,o_rh2m_max%flag,o_rh2m_max%name, "Max Relative humidity at 2m", "%" )
     1415   type_ecri(6) = 't_max(X)'
     1416   CALL histdef3d(iff,clef_stations(iff), &
     1417  o_tke_max%flag,o_tke_max%name, "TKE max", "m2/s2")
     1418  ENDIF
    10831419   type_ecri(:) = type_ecri_files(:)
    1084  CALL histdef2d(iff,o_qsat2m%flag,o_qsat2m%name, "Saturant humidity at 2m", "%")
    1085  CALL histdef2d(iff,o_tpot%flag,o_tpot%name, "Surface air potential temperature", "K")
    1086  CALL histdef2d(iff,o_tpote%flag,o_tpote%name, "Surface air equivalent potential temperature", "K")
    1087  CALL histdef2d(iff,o_SWnetOR%flag,o_SWnetOR%name, "Sfce net SW radiation OR", "W/m2")
    1088  CALL histdef2d(iff,o_SWdownOR%flag,o_SWdownOR%name, "Sfce incident SW radiation OR", "W/m2")
    1089  CALL histdef2d(iff,o_LWdownOR%flag,o_LWdownOR%name, "Sfce incident LW radiation OR", "W/m2")
    1090  CALL histdef2d(iff,o_snowl%flag,o_snowl%name, "Solid Large-scale Precip.", "kg/(m2*s)")
    1091 
    1092  CALL histdef2d(iff,o_solldown%flag,o_solldown%name, "Down. IR rad. at surface", "W/m2")
    1093  CALL histdef2d(iff,o_dtsvdfo%flag,o_dtsvdfo%name, "Boundary-layer dTs(o)", "K/s")
    1094  CALL histdef2d(iff,o_dtsvdft%flag,o_dtsvdft%name, "Boundary-layer dTs(t)", "K/s")
    1095  CALL histdef2d(iff,o_dtsvdfg%flag,o_dtsvdfg%name, "Boundary-layer dTs(g)", "K/s")
    1096  CALL histdef2d(iff,o_dtsvdfi%flag,o_dtsvdfi%name, "Boundary-layer dTs(g)", "K/s")
    1097  CALL histdef2d(iff,o_rugs%flag,o_rugs%name, "rugosity", "-" )
    1098 
    1099 ! Champs 3D:
    1100  CALL histdef3d(iff,o_ec550aer%flag,o_ec550aer%name, "Extinction at 550nm", "m^-1")
    1101  CALL histdef3d(iff,o_lwcon%flag,o_lwcon%name, "Cloud liquid water content", "kg/kg")
    1102  CALL histdef3d(iff,o_iwcon%flag,o_iwcon%name, "Cloud ice water content", "kg/kg")
    1103  CALL histdef3d(iff,o_temp%flag,o_temp%name, "Air temperature", "K" )
    1104  CALL histdef3d(iff,o_theta%flag,o_theta%name, "Potential air temperature", "K" )
    1105  CALL histdef3d(iff,o_ovap%flag,o_ovap%name, "Specific humidity", "kg/kg" )
    1106  CALL histdef3d(iff,o_ovapinit%flag,o_ovapinit%name, "Specific humidity (begin of timestep)", "kg/kg" )
    1107  CALL histdef3d(iff,o_geop%flag,o_geop%name, "Geopotential height", "m2/s2")
    1108  CALL histdef3d(iff,o_vitu%flag,o_vitu%name, "Zonal wind", "m/s" )
    1109  CALL histdef3d(iff,o_vitv%flag,o_vitv%name, "Meridional wind", "m/s" )
    1110  CALL histdef3d(iff,o_vitw%flag,o_vitw%name, "Vertical wind", "Pa/s" )
    1111  CALL histdef3d(iff,o_pres%flag,o_pres%name, "Air pressure", "Pa" )
    1112  CALL histdef3d(iff,o_paprs%flag,o_paprs%name, "Air pressure Inter-Couches", "Pa" )
    1113  CALL histdef3d(iff,o_rneb%flag,o_rneb%name, "Cloud fraction", "-")
    1114  CALL histdef3d(iff,o_rnebcon%flag,o_rnebcon%name, "Convective Cloud Fraction", "-")
    1115  CALL histdef3d(iff,o_rhum%flag,o_rhum%name, "Relative humidity", "-")
    1116  CALL histdef3d(iff,o_ozone%flag,o_ozone%name, "Ozone mole fraction", "-")
    1117  if (read_climoz == 2) &
    1118       CALL histdef3d(iff,o_ozone_light%flag,o_ozone_light%name, &
    1119       "Daylight ozone mole fraction", "-")
    1120  CALL histdef3d(iff,o_dtphy%flag,o_dtphy%name, "Physics dT", "K/s")
    1121  CALL histdef3d(iff,o_dqphy%flag,o_dqphy%name, "Physics dQ", "(kg/kg)/s")
    1122  CALL histdef3d(iff,o_cldtau%flag,o_cldtau%name, "Cloud optical thickness", "1")
    1123  CALL histdef3d(iff,o_cldemi%flag,o_cldemi%name, "Cloud optical emissivity", "1")
    1124 !IM: bug ?? dimensionnement variables (klon,klev+1) pmflxr, pmflxs, prfl, psfl
    1125  CALL histdef3d(iff,o_pr_con_l%flag,o_pr_con_l%name, "Convective precipitation lic", " ")
    1126  CALL histdef3d(iff,o_pr_con_i%flag,o_pr_con_i%name, "Convective precipitation ice", " ")
    1127  CALL histdef3d(iff,o_pr_lsc_l%flag,o_pr_lsc_l%name, "Large scale precipitation lic", " ")
    1128  CALL histdef3d(iff,o_pr_lsc_i%flag,o_pr_lsc_i%name, "Large scale precipitation ice", " ")
    1129 !Cloud droplet effective radius
    1130  CALL histdef3d(iff,o_re%flag,o_re%name, "Cloud droplet effective radius","um")
    1131  CALL histdef3d(iff,o_fl%flag,o_fl%name, "Denominator of Cloud droplet effective radius"," ")
    1132 !FH Sorties pour la couche limite
    1133      if (iflag_pbl>1) then
    1134  CALL histdef3d(iff,o_tke%flag,o_tke%name, "TKE", "m2/s2")
     1420     endif
     1421
     1422 CALL histdef3d(iff,clef_stations(iff), &
     1423o_kz%flag,o_kz%name, "Kz melange", "m2/s")
     1424  IF (.NOT.clef_stations(iff)) THEN
     1425!
     1426!IM: there is no way to have one single value in a netcdf file
     1427!
    11351428   type_ecri(1) = 't_max(X)'
    11361429   type_ecri(2) = 't_max(X)'
     
    11381431   type_ecri(4) = 't_max(X)'
    11391432   type_ecri(5) = 't_max(X)'
    1140  CALL histdef3d(iff,o_tke_max%flag,o_tke_max%name, "TKE max", "m2/s2")
     1433   type_ecri(6) = 't_max(X)'
     1434   CALL histdef3d(iff,clef_stations(iff), &
     1435   o_kz_max%flag,o_kz_max%name, "Kz melange max", "m2/s" )
     1436  ENDIF
    11411437   type_ecri(:) = type_ecri_files(:)
    1142      endif
    1143 
    1144  CALL histdef3d(iff,o_kz%flag,o_kz%name, "Kz melange", "m2/s")
    1145    type_ecri(1) = 't_max(X)'
    1146    type_ecri(2) = 't_max(X)'
    1147    type_ecri(3) = 't_max(X)'
    1148    type_ecri(4) = 't_max(X)'
    1149    type_ecri(5) = 't_max(X)'
    1150  CALL histdef3d(iff,o_kz_max%flag,o_kz_max%name, "Kz melange max", "m2/s" )
    1151    type_ecri(:) = type_ecri_files(:)
    1152  CALL histdef3d(iff,o_clwcon%flag,o_clwcon%name, "Convective Cloud Liquid water content", "kg/kg")
    1153  CALL histdef3d(iff,o_dtdyn%flag,o_dtdyn%name, "Dynamics dT", "K/s")
    1154  CALL histdef3d(iff,o_dqdyn%flag,o_dqdyn%name, "Dynamics dQ", "(kg/kg)/s")
    1155  CALL histdef3d(iff,o_dudyn%flag,o_dudyn%name, "Dynamics dU", "m/s2")
    1156  CALL histdef3d(iff,o_dvdyn%flag,o_dvdyn%name, "Dynamics dV", "m/s2")
    1157  CALL histdef3d(iff,o_dtcon%flag,o_dtcon%name, "Convection dT", "K/s")
    1158  CALL histdef3d(iff,o_ducon%flag,o_ducon%name, "Convection du", "m/s2")
    1159  CALL histdef3d(iff,o_dqcon%flag,o_dqcon%name, "Convection dQ", "(kg/kg)/s")
     1438 CALL histdef3d(iff,clef_stations(iff), &
     1439o_clwcon%flag,o_clwcon%name, "Convective Cloud Liquid water content", "kg/kg")
     1440 CALL histdef3d(iff,clef_stations(iff), &
     1441o_dtdyn%flag,o_dtdyn%name, "Dynamics dT", "K/s")
     1442 CALL histdef3d(iff,clef_stations(iff), &
     1443o_dqdyn%flag,o_dqdyn%name, "Dynamics dQ", "(kg/kg)/s")
     1444 CALL histdef3d(iff,clef_stations(iff), &
     1445o_dudyn%flag,o_dudyn%name, "Dynamics dU", "m/s2")
     1446 CALL histdef3d(iff,clef_stations(iff), &
     1447o_dvdyn%flag,o_dvdyn%name, "Dynamics dV", "m/s2")
     1448 CALL histdef3d(iff,clef_stations(iff), &
     1449o_dtcon%flag,o_dtcon%name, "Convection dT", "K/s")
     1450 CALL histdef3d(iff,clef_stations(iff), &
     1451o_ducon%flag,o_ducon%name, "Convection du", "m/s2")
     1452 CALL histdef3d(iff,clef_stations(iff), &
     1453o_dqcon%flag,o_dqcon%name, "Convection dQ", "(kg/kg)/s")
    11601454
    11611455! Wakes
    11621456 IF(iflag_con.EQ.3) THEN
    11631457 IF (iflag_wake == 1) THEN
    1164    CALL histdef2d(iff,o_ale_wk%flag,o_ale_wk%name, "ALE WK", "m2/s2")
    1165    CALL histdef2d(iff,o_alp_wk%flag,o_alp_wk%name, "ALP WK", "m2/s2")
    1166    CALL histdef2d(iff,o_ale%flag,o_ale%name, "ALE", "m2/s2")
    1167    CALL histdef2d(iff,o_alp%flag,o_alp%name, "ALP", "W/m2")
    1168    CALL histdef2d(iff,o_cin%flag,o_cin%name, "Convective INhibition", "m2/s2")
    1169    CALL histdef2d(iff,o_wape%flag,o_WAPE%name, "WAPE", "m2/s2")
    1170    CALL histdef2d(iff,o_wake_h%flag,o_wake_h%name, "wake_h", "-")
    1171    CALL histdef2d(iff,o_wake_s%flag,o_wake_s%name, "wake_s", "-")
    1172    CALL histdef3d(iff,o_dtwak%flag,o_dtwak%name, "Wake dT", "K/s")
    1173    CALL histdef3d(iff,o_dqwak%flag,o_dqwak%name, "Wake dQ", "(kg/kg)/s")
    1174    CALL histdef3d(iff,o_wake_deltat%flag,o_wake_deltat%name, "wake_deltat", " ")
    1175    CALL histdef3d(iff,o_wake_deltaq%flag,o_wake_deltaq%name, "wake_deltaq", " ")
    1176    CALL histdef3d(iff,o_wake_omg%flag,o_wake_omg%name, "wake_omg", " ")
     1458   CALL histdef2d(iff,clef_stations(iff), &
     1459o_ale_wk%flag,o_ale_wk%name, "ALE WK", "m2/s2")
     1460   CALL histdef2d(iff,clef_stations(iff), &
     1461o_alp_wk%flag,o_alp_wk%name, "ALP WK", "m2/s2")
     1462   CALL histdef2d(iff,clef_stations(iff), &
     1463o_ale%flag,o_ale%name, "ALE", "m2/s2")
     1464   CALL histdef2d(iff,clef_stations(iff), &
     1465o_alp%flag,o_alp%name, "ALP", "W/m2")
     1466   CALL histdef2d(iff,clef_stations(iff),o_cin%flag,o_cin%name, "Convective INhibition", "m2/s2")
     1467   CALL histdef2d(iff,clef_stations(iff),o_wape%flag,o_WAPE%name, "WAPE", "m2/s2")
     1468   CALL histdef2d(iff,clef_stations(iff),o_wake_h%flag,o_wake_h%name, "wake_h", "-")
     1469   CALL histdef2d(iff,clef_stations(iff),o_wake_s%flag,o_wake_s%name, "wake_s", "-")
     1470   CALL histdef3d(iff,clef_stations(iff),o_dtwak%flag,o_dtwak%name, "Wake dT", "K/s")
     1471   CALL histdef3d(iff,clef_stations(iff),o_dqwak%flag,o_dqwak%name, "Wake dQ", "(kg/kg)/s")
     1472   CALL histdef3d(iff,clef_stations(iff),o_wake_deltat%flag,o_wake_deltat%name, "wake_deltat", " ")
     1473   CALL histdef3d(iff,clef_stations(iff),o_wake_deltaq%flag,o_wake_deltaq%name, "wake_deltaq", " ")
     1474   CALL histdef3d(iff,clef_stations(iff),o_wake_omg%flag,o_wake_omg%name, "wake_omg", " ")
    11771475 ENDIF
    1178    CALL histdef3d(iff,o_Vprecip%flag,o_Vprecip%name, "precipitation vertical profile", "-")
    1179    CALL histdef3d(iff,o_ftd%flag,o_ftd%name, "tend temp due aux descentes precip", "-")
    1180    CALL histdef3d(iff,o_fqd%flag,o_fqd%name,"tend vap eau due aux descentes precip", "-")
     1476   CALL histdef3d(iff,clef_stations(iff),o_Vprecip%flag,o_Vprecip%name, "precipitation vertical profile", "-")
     1477   CALL histdef3d(iff,clef_stations(iff),o_ftd%flag,o_ftd%name, "tend temp due aux descentes precip", "-")
     1478   CALL histdef3d(iff,clef_stations(iff),o_fqd%flag,o_fqd%name,"tend vap eau due aux descentes precip", "-")
    11811479 ENDIF !(iflag_con.EQ.3)
    11821480
    1183  CALL histdef3d(iff,o_dtlsc%flag,o_dtlsc%name, "Condensation dT", "K/s")
    1184  CALL histdef3d(iff,o_dtlschr%flag,o_dtlschr%name,"Large-scale condensational heating rate","K/s")
    1185  CALL histdef3d(iff,o_dqlsc%flag,o_dqlsc%name, "Condensation dQ", "(kg/kg)/s")
    1186  CALL histdef3d(iff,o_dtvdf%flag,o_dtvdf%name, "Boundary-layer dT", "K/s")
    1187  CALL histdef3d(iff,o_dqvdf%flag,o_dqvdf%name, "Boundary-layer dQ", "(kg/kg)/s")
    1188  CALL histdef3d(iff,o_dteva%flag,o_dteva%name, "Reevaporation dT", "K/s")
    1189  CALL histdef3d(iff,o_dqeva%flag,o_dqeva%name, "Reevaporation dQ", "(kg/kg)/s")
    1190  CALL histdef3d(iff,o_ptconv%flag,o_ptconv%name, "POINTS CONVECTIFS", " ")
    1191  CALL histdef3d(iff,o_ratqs%flag,o_ratqs%name, "RATQS", " ")
    1192  CALL histdef3d(iff,o_dtthe%flag,o_dtthe%name, "Dry adjust. dT", "K/s")
     1481 CALL histdef3d(iff,clef_stations(iff),o_dtlsc%flag,o_dtlsc%name, "Condensation dT", "K/s")
     1482 CALL histdef3d(iff,clef_stations(iff),o_dtlschr%flag,o_dtlschr%name,"Large-scale condensational heating rate","K/s")
     1483 CALL histdef3d(iff,clef_stations(iff),o_dqlsc%flag,o_dqlsc%name, "Condensation dQ", "(kg/kg)/s")
     1484 CALL histdef3d(iff,clef_stations(iff),o_dtvdf%flag,o_dtvdf%name, "Boundary-layer dT", "K/s")
     1485 CALL histdef3d(iff,clef_stations(iff),o_dqvdf%flag,o_dqvdf%name, "Boundary-layer dQ", "(kg/kg)/s")
     1486 CALL histdef3d(iff,clef_stations(iff),o_dteva%flag,o_dteva%name, "Reevaporation dT", "K/s")
     1487 CALL histdef3d(iff,clef_stations(iff),o_dqeva%flag,o_dqeva%name, "Reevaporation dQ", "(kg/kg)/s")
     1488 CALL histdef3d(iff,clef_stations(iff),o_ptconv%flag,o_ptconv%name, "POINTS CONVECTIFS", " ")
     1489 CALL histdef3d(iff,clef_stations(iff),o_ratqs%flag,o_ratqs%name, "RATQS", " ")
     1490 CALL histdef3d(iff,clef_stations(iff),o_dtthe%flag,o_dtthe%name, "Thermal dT", "K/s")
    11931491
    11941492if(iflag_thermals.gt.1) THEN
    1195  CALL histdef3d(iff,o_f_th%flag,o_f_th%name, "Thermal plume mass flux", "K/s")
    1196  CALL histdef3d(iff,o_e_th%flag,o_e_th%name,"Thermal plume entrainment","K/s")
    1197  CALL histdef3d(iff,o_w_th%flag,o_w_th%name,"Thermal plume vertical velocity","m/s")
    1198  CALL histdef3d(iff,o_lambda_th%flag,o_lambda_th%name,"Thermal plume vertical velocity","m/s")
    1199  CALL histdef2d(iff,o_ftime_th%flag,o_ftime_th%name,"Fraction of time Shallow convection occurs"," ")
    1200  CALL histdef3d(iff,o_q_th%flag,o_q_th%name, "Thermal plume total humidity", "kg/kg")
    1201  CALL histdef3d(iff,o_a_th%flag,o_a_th%name, "Thermal plume fraction", "")
    1202  CALL histdef3d(iff,o_d_th%flag,o_d_th%name, "Thermal plume detrainment", "K/s")
    1203 !IM endif !iflag_thermals.gt.1
    1204  CALL histdef2d(iff,o_f0_th%flag,o_f0_th%name, "Thermal closure mass flux", "K/s")
    1205  CALL histdef2d(iff,o_zmax_th%flag,o_zmax_th%name, "Thermal plume height", "K/s")
    1206  CALL histdef3d(iff,o_dqthe%flag,o_dqthe%name, "Dry adjust. dQ", "(kg/kg)/s")
     1493 CALL histdef3d(iff,clef_stations(iff),o_f_th%flag,o_f_th%name, "Thermal plume mass flux", "kg/(m2*s)")
     1494 CALL histdef3d(iff,clef_stations(iff),o_e_th%flag,o_e_th%name,"Thermal plume entrainment","K/s")
     1495 CALL histdef3d(iff,clef_stations(iff),o_w_th%flag,o_w_th%name,"Thermal plume vertical velocity","m/s")
     1496 CALL histdef3d(iff,clef_stations(iff), &
     1497o_lambda_th%flag,o_lambda_th%name,"Thermal plume vertical velocity","m/s")
     1498 CALL histdef2d(iff,clef_stations(iff), &
     1499o_ftime_th%flag,o_ftime_th%name,"Fraction of time Shallow convection occurs"," ")
     1500 CALL histdef3d(iff,clef_stations(iff), &
     1501o_q_th%flag,o_q_th%name, "Thermal plume total humidity", "kg/kg")
     1502 CALL histdef3d(iff,clef_stations(iff), &
     1503o_a_th%flag,o_a_th%name, "Thermal plume fraction", "")
     1504 CALL histdef3d(iff,clef_stations(iff), &
     1505o_d_th%flag,o_d_th%name, "Thermal plume detrainment", "K/s")
     1506
     1507 CALL histdef2d(iff,clef_stations(iff), &
     1508o_f0_th%flag,o_f0_th%name, "Thermal closure mass flux", "K/s")
     1509 CALL histdef2d(iff,clef_stations(iff), &
     1510o_zmax_th%flag,o_zmax_th%name, "Thermal plume height", "K/s")
     1511 CALL histdef3d(iff,clef_stations(iff), &
     1512o_dqthe%flag,o_dqthe%name, "Thermal dQ", "(kg/kg)/s")
    12071513endif !iflag_thermals.gt.1
    1208  CALL histdef3d(iff,o_dtajs%flag,o_dtajs%name, "Dry adjust. dT", "K/s")
    1209  CALL histdef3d(iff,o_dqajs%flag,o_dqajs%name, "Dry adjust. dQ", "(kg/kg)/s")
    1210  CALL histdef3d(iff,o_dtswr%flag,o_dtswr%name, "SW radiation dT", "K/s")
    1211  CALL histdef3d(iff,o_dtsw0%flag,o_dtsw0%name, "CS SW radiation dT", "K/s")
    1212  CALL histdef3d(iff,o_dtlwr%flag,o_dtlwr%name, "LW radiation dT", "K/s")
    1213  CALL histdef3d(iff,o_dtlw0%flag,o_dtlw0%name, "CS LW radiation dT", "K/s")
    1214  CALL histdef3d(iff,o_dtec%flag,o_dtec%name, "Cinetic dissip dT", "K/s")
    1215  CALL histdef3d(iff,o_duvdf%flag,o_duvdf%name, "Boundary-layer dU", "m/s2")
    1216  CALL histdef3d(iff,o_dvvdf%flag,o_dvvdf%name, "Boundary-layer dV", "m/s2")
     1514 CALL histdef3d(iff,clef_stations(iff), &
     1515o_dtajs%flag,o_dtajs%name, "Dry adjust. dT", "K/s")
     1516 CALL histdef3d(iff,clef_stations(iff), &
     1517o_dqajs%flag,o_dqajs%name, "Dry adjust. dQ", "(kg/kg)/s")
     1518 CALL histdef3d(iff,clef_stations(iff), &
     1519o_dtswr%flag,o_dtswr%name, "SW radiation dT", "K/s")
     1520 CALL histdef3d(iff,clef_stations(iff), &
     1521o_dtsw0%flag,o_dtsw0%name, "CS SW radiation dT", "K/s")
     1522 CALL histdef3d(iff,clef_stations(iff), &
     1523o_dtlwr%flag,o_dtlwr%name, "LW radiation dT", "K/s")
     1524 CALL histdef3d(iff,clef_stations(iff), &
     1525o_dtlw0%flag,o_dtlw0%name, "CS LW radiation dT", "K/s")
     1526 CALL histdef3d(iff,clef_stations(iff), &
     1527o_dtec%flag,o_dtec%name, "Cinetic dissip dT", "K/s")
     1528 CALL histdef3d(iff,clef_stations(iff), &
     1529o_duvdf%flag,o_duvdf%name, "Boundary-layer dU", "m/s2")
     1530 CALL histdef3d(iff,clef_stations(iff), &
     1531o_dvvdf%flag,o_dvvdf%name, "Boundary-layer dV", "m/s2")
    12171532
    12181533     IF (ok_orodr) THEN
    1219  CALL histdef3d(iff,o_duoro%flag,o_duoro%name, "Orography dU", "m/s2")
    1220  CALL histdef3d(iff,o_dvoro%flag,o_dvoro%name, "Orography dV", "m/s2")
     1534 CALL histdef3d(iff,clef_stations(iff), &
     1535o_duoro%flag,o_duoro%name, "Orography dU", "m/s2")
     1536 CALL histdef3d(iff,clef_stations(iff), &
     1537o_dvoro%flag,o_dvoro%name, "Orography dV", "m/s2")
     1538 CALL histdef3d(iff,clef_stations(iff), &
     1539o_dtoro%flag,o_dtoro%name, "Orography dT", "K/s")
    12211540     ENDIF
    12221541
    12231542     IF (ok_orolf) THEN
    1224  CALL histdef3d(iff,o_dulif%flag,o_dulif%name, "Orography dU", "m/s2")
    1225  CALL histdef3d(iff,o_dvlif%flag,o_dvlif%name, "Orography dV", "m/s2")
     1543 CALL histdef3d(iff,clef_stations(iff), &
     1544o_dulif%flag,o_dulif%name, "Orography dU", "m/s2")
     1545 CALL histdef3d(iff,clef_stations(iff), &
     1546o_dvlif%flag,o_dvlif%name, "Orography dV", "m/s2")
     1547 CALL histdef3d(iff,clef_stations(iff), &
     1548o_dtlif%flag,o_dtlif%name, "Orography dT", "K/s")
    12261549     ENDIF
    12271550
    12281551     IF (ok_hines) then
    1229  CALL histdef3d(iff,o_duhin%flag,o_duhin%name, "Hines GWD dU", "m/s2")
    1230  CALL histdef3d(iff,o_dvhin%flag,o_dvhin%name, "Hines GWD dV", "m/s2")
     1552 CALL histdef3d(iff,clef_stations(iff), &
     1553o_duhin%flag,o_duhin%name, "Hines GWD dU", "m/s2")
     1554 CALL histdef3d(iff,clef_stations(iff), &
     1555o_dvhin%flag,o_dvhin%name, "Hines GWD dV", "m/s2")
     1556
     1557 CALL histdef3d(iff,clef_stations(iff), &
     1558o_dthin%flag,o_dthin%name, "Hines GWD dT", "K/s")
    12311559     ENDIF
    12321560
     1561 CALL histdef3d(iff,clef_stations(iff), &
     1562o_rsu%flag,o_rsu%name, "SW upward radiation", "W m-2")
     1563 CALL histdef3d(iff,clef_stations(iff), &
     1564o_rsd%flag,o_rsd%name, "SW downward radiation", "W m-2")
     1565 CALL histdef3d(iff,clef_stations(iff), &
     1566o_rlu%flag,o_rlu%name, "LW upward radiation", "W m-2")
     1567 CALL histdef3d(iff,clef_stations(iff), &
     1568o_rld%flag,o_rld%name, "LW downward radiation", "W m-2")
     1569
     1570 CALL histdef3d(iff,clef_stations(iff), &
     1571o_rsucs%flag,o_rsucs%name, "SW CS upward radiation", "W m-2")
     1572 CALL histdef3d(iff,clef_stations(iff), &
     1573o_rsdcs%flag,o_rsdcs%name, "SW CS downward radiation", "W m-2")
     1574 CALL histdef3d(iff,clef_stations(iff), &
     1575o_rlucs%flag,o_rlucs%name, "LW CS upward radiation", "W m-2")
     1576 CALL histdef3d(iff,clef_stations(iff), &
     1577o_rldcs%flag,o_rldcs%name, "LW CS downward radiation", "W m-2")
     1578 
     1579 CALL histdef3d(iff,clef_stations(iff), &
     1580o_tnt%flag,o_tnt%name, "Tendency of air temperature", "K s-1")
     1581
     1582 CALL histdef3d(iff,clef_stations(iff), &
     1583o_tntc%flag,o_tntc%name, "Tendency of air temperature due to Moist Convection", &
     1584"K s-1")
     1585
     1586 CALL histdef3d(iff,clef_stations(iff), &
     1587o_tntr%flag,o_tntr%name, "Air temperature tendency due to Radiative heating", &
     1588"K s-1")
     1589
     1590 CALL histdef3d(iff,clef_stations(iff), &
     1591o_tntscpbl%flag,o_tntscpbl%name, "Air temperature tendency due to St cloud and precipitation and BL mixing", &
     1592"K s-1")
     1593
     1594 CALL histdef3d(iff,clef_stations(iff), &
     1595o_tnhus%flag,o_tnhus%name, "Tendency of specific humidity", "s-1")
     1596
     1597 CALL histdef3d(iff,clef_stations(iff), &
     1598o_tnhusc%flag,o_tnhusc%name, "Tendency of specific humidity due to convection", "s-1")
     1599
     1600 CALL histdef3d(iff,clef_stations(iff), &
     1601o_tnhusscpbl%flag,o_tnhusscpbl%name, "Tendency of Specific humidity due to ST cl, precip and BL mixing", &
     1602"s-1")
     1603
     1604 CALL histdef3d(iff,clef_stations(iff), &
     1605o_evu%flag,o_evu%name, "Eddy viscosity coefficient for Momentum Variables", "m2 s-1")
     1606
     1607 CALL histdef3d(iff,clef_stations(iff), &
     1608o_h2o%flag,o_h2o%name, "Mass Fraction of Water", "1")
     1609
     1610 CALL histdef3d(iff,clef_stations(iff), &
     1611o_mcd%flag,o_mcd%name, "Downdraft COnvective Mass Flux", "kg/(m2*s)")
     1612
     1613 CALL histdef3d(iff,clef_stations(iff), &
     1614o_dmc%flag,o_dmc%name, "Deep COnvective Mass Flux", "kg/(m2*s)")
     1615
     1616 CALL histdef3d(iff,clef_stations(iff), &
     1617o_ref_liq%flag,o_ref_liq%name, "Effective radius of convective cloud liquid water particle", "m")
     1618
     1619 CALL histdef3d(iff,clef_stations(iff), &
     1620o_ref_ice%flag,o_ref_ice%name, "Effective radius of startiform cloud ice particle", "m")
     1621
     1622   if (RCO2_per.NE.RCO2_act.OR.RCH4_per.NE.RCH4_act.OR. &
     1623    RN2O_per.NE.RN2O_act.OR.RCFC11_per.NE.RCFC11_act.OR. &
     1624    RCFC12_per.NE.RCFC12_act) THEN
     1625
     1626 CALL histdef2d(iff,clef_stations(iff),o_rsut4co2%flag,o_rsut4co2%name, &
     1627 "TOA Out SW in 4xCO2 atmosphere", "W/m2")
     1628CALL histdef2d(iff,clef_stations(iff),o_rlut4co2%flag,o_rlut4co2%name, &
     1629"TOA Out LW in 4xCO2 atmosphere", "W/m2")
     1630CALL histdef2d(iff,clef_stations(iff),o_rsutcs4co2%flag,o_rsutcs4co2%name, &
     1631"TOA Out CS SW in 4xCO2 atmosphere", "W/m2")
     1632CALL histdef2d(iff,clef_stations(iff),o_rlutcs4co2%flag,o_rlutcs4co2%name, &
     1633"TOA Out CS LW in 4xCO2 atmosphere", "W/m2")
     1634
     1635CALL histdef3d(iff,clef_stations(iff),o_rsu4co2%flag,o_rsu4co2%name, &
     1636"Upwelling SW 4xCO2 atmosphere", "W/m2")
     1637CALL histdef3d(iff,clef_stations(iff),o_rlu4co2%flag,o_rlu4co2%name, &
     1638"Upwelling LW 4xCO2 atmosphere", "W/m2")
     1639CALL histdef3d(iff,clef_stations(iff),o_rsucs4co2%flag,o_rsucs4co2%name, &
     1640"Upwelling CS SW 4xCO2 atmosphere", "W/m2")
     1641CALL histdef3d(iff,clef_stations(iff),o_rlucs4co2%flag,o_rlucs4co2%name, &
     1642"Upwelling CS LW 4xCO2 atmosphere", "W/m2")
     1643
     1644 CALL histdef3d(iff,clef_stations(iff),o_rsd4co2%flag,o_rsd4co2%name, &
     1645 "Downwelling SW 4xCO2 atmosphere", "W/m2")
     1646 CALL histdef3d(iff,clef_stations(iff),o_rld4co2%flag,o_rld4co2%name, &
     1647"Downwelling LW 4xCO2 atmosphere", "W/m2")
     1648 CALL histdef3d(iff,clef_stations(iff),o_rsdcs4co2%flag,o_rsdcs4co2%name, &
     1649"Downwelling CS SW 4xCO2 atmosphere", "W/m2")
     1650 CALL histdef3d(iff,clef_stations(iff),o_rldcs4co2%flag,o_rldcs4co2%name, &
     1651"Downwelling CS LW 4xCO2 atmosphere", "W/m2")
     1652
     1653   endif
    12331654
    12341655!Attention : sorties uniquement pour traceurs 3 et 4
     
    12381659           ttext(3)= "Age stratospheric air"
    12391660        END IF
    1240         CALL histdef3d (iff, o_trac(1)%flag,o_trac(1)%name,ttext(3), "-" )
     1661        CALL histdef3d(iff,clef_stations(iff), o_trac(1)%flag,o_trac(1)%name,ttext(3), "-" )
    12411662     END IF
    12421663     
    1243      IF (nqtot>=4) CALL histdef3d (iff, o_trac(2)%flag,o_trac(2)%name,ttext(4), "-" )
     1664     IF (nqtot>=4) CALL histdef3d(iff,clef_stations(iff), o_trac(2)%flag,o_trac(2)%name,ttext(4), "-" )
    12441665
    12451666
     
    12551676      end subroutine phys_output_open
    12561677
    1257       SUBROUTINE histdef2d (iff,flag_var,nomvar,titrevar,unitvar)
     1678      SUBROUTINE histdef2d (iff,lpoint,flag_var,nomvar,titrevar,unitvar)
    12581679     
    12591680       use ioipsl
    12601681       USE dimphy
    12611682       USE mod_phys_lmdz_para
     1683       USE iophy
    12621684
    12631685       IMPLICIT NONE
     
    12691691
    12701692       integer                          :: iff
     1693       logical                          :: lpoint
    12711694       integer, dimension(nfiles)       :: flag_var
    12721695       character(len=20)                 :: nomvar
     
    12841707! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def
    12851708       call conf_physoutputs(nomvar,flag_var)
    1286        
     1709     
     1710       if(.NOT.lpoint) THEN 
    12871711       if ( flag_var(iff)<=lev_files(iff) ) then
    12881712 call histdef (nid_files(iff),nomvar,titrevar,unitvar, &
     
    12901714               type_ecri(iff), zstophym,zoutm(iff))               
    12911715       endif                     
     1716       else
     1717       if ( flag_var(iff)<=lev_files(iff) ) then
     1718 call histdef (nid_files(iff),nomvar,titrevar,unitvar, &
     1719               npstn,1,nhorim(iff), 1,1,1, -99, 32, &
     1720               type_ecri(iff), zstophym,zoutm(iff))               
     1721       endif                     
     1722       endif                     
    12921723      end subroutine histdef2d
    12931724
    1294       SUBROUTINE histdef3d (iff,flag_var,nomvar,titrevar,unitvar)
     1725      SUBROUTINE histdef3d (iff,lpoint,flag_var,nomvar,titrevar,unitvar)
    12951726
    12961727       use ioipsl
    12971728       USE dimphy
    12981729       USE mod_phys_lmdz_para
     1730       USE iophy
    12991731
    13001732       IMPLICIT NONE
     
    13061738
    13071739       integer                          :: iff
     1740       logical                          :: lpoint
    13081741       integer, dimension(nfiles)       :: flag_var
    13091742       character(len=20)                 :: nomvar
     
    13221755       endif
    13231756
     1757       if(.NOT.lpoint) THEN
    13241758       if ( flag_var(iff)<=lev_files(iff) ) then
    13251759          call histdef (nid_files(iff), nomvar, titrevar, unitvar, &
     
    13271761               levmax(iff)-levmin(iff)+1, nvertm(iff), 32, type_ecri(iff), &
    13281762               zstophym, zoutm(iff))
     1763       endif
     1764       else
     1765       if ( flag_var(iff)<=lev_files(iff) ) then
     1766          call histdef (nid_files(iff), nomvar, titrevar, unitvar, &
     1767               npstn,1,nhorim(iff), klev, levmin(iff), &
     1768               levmax(iff)-levmin(iff)+1, nvertm(iff), 32, &
     1769               type_ecri(iff), zstophym,zoutm(iff))
     1770       endif
    13291771       endif
    13301772      end subroutine histdef3d
  • LMDZ4/branches/LMDZ4_AR5/libf/phylmd/phys_output_write.h

    r1419 r1534  
    99!!! Champs 1D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    1010       IF (o_phis%flag(iff)<=lev_files(iff)) THEN
    11          CALL histwrite_phy(nid_files(iff),
    12      $                      o_phis%name,itau_w,pphis)
    13        ENDIF
    14 
     11      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     12     $                  o_phis%name,itau_w,pphis)
     13       ENDIF
     14
     15       IF (.NOT.clef_stations(iff)) THEN
    1516       IF (o_aire%flag(iff)<=lev_files(iff)) THEN
    16        CALL histwrite_phy(nid_files(iff),o_aire%name,itau_w,airephy)
     17       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     18     $o_aire%name,itau_w,airephy)
    1719       ENDIF
    1820
     
    2123       zx_tmp_fi2d(i)=pctsrf(i,is_ter)+pctsrf(i,is_lic)
    2224      ENDDO
    23       CALL histwrite_phy(nid_files(iff),
     25      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    2426     $             o_contfracATM%name,itau_w,zx_tmp_fi2d)
    2527       ENDIF
     28       ENDIF
    2629
    2730       IF (o_contfracOR%flag(iff)<=lev_files(iff)) THEN
    28       CALL histwrite_phy(nid_files(iff),o_contfracOR%name,itau_w,
    29      $                   pctsrf(:,is_ter))
     31      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     32     $                  o_contfracOR%name,itau_w,pctsrf(:,is_ter))
    3033       ENDIF
    3134
    3235       IF (o_aireTER%flag(iff)<=lev_files(iff)) THEN
    33       CALL histwrite_phy(nid_files(iff),
     36      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    3437     $                  o_aireTER%name,itau_w,paire_ter)
    3538       ENDIF
     
    3841
    3942       IF (o_flat%flag(iff)<=lev_files(iff)) THEN
    40       CALL histwrite_phy(nid_files(iff),o_flat%name,itau_w,zxfluxlat)
     43      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     44     $                  o_flat%name,itau_w,zxfluxlat)
    4145       ENDIF
    4246
    4347       IF (o_slp%flag(iff)<=lev_files(iff)) THEN
    44       CALL histwrite_phy(nid_files(iff),o_slp%name,itau_w,slp)
     48      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     49     $                  o_slp%name,itau_w,slp)
    4550       ENDIF
    4651
    4752       IF (o_tsol%flag(iff)<=lev_files(iff)) THEN
    48       CALL histwrite_phy(nid_files(iff),o_tsol%name,itau_w,zxtsol)
     53      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     54     $                  o_tsol%name,itau_w,zxtsol)
    4955       ENDIF
    5056
    5157       IF (o_t2m%flag(iff)<=lev_files(iff)) THEN
    52       CALL histwrite_phy(nid_files(iff),o_t2m%name,itau_w,zt2m)
    53        ENDIF
    54 
     58      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     59     $                  o_t2m%name,itau_w,zt2m)
     60       ENDIF
     61
     62      IF (.NOT.clef_stations(iff)) THEN
    5563       IF (o_t2m_min%flag(iff)<=lev_files(iff)) THEN
    56       CALL histwrite_phy(nid_files(iff),o_t2m_min%name,itau_w,zt2m)
     64      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     65     $o_t2m_min%name,itau_w,zt2m)
    5766       ENDIF
    5867
    5968       IF (o_t2m_max%flag(iff)<=lev_files(iff)) THEN
    60       CALL histwrite_phy(nid_files(iff),o_t2m_max%name,itau_w,zt2m)
     69      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     70     $o_t2m_max%name,itau_w,zt2m)
     71       ENDIF
    6172       ENDIF
    6273
     
    6576       zx_tmp_fi2d(i)=SQRT(zu10m(i)*zu10m(i)+zv10m(i)*zv10m(i))
    6677      ENDDO
    67       CALL histwrite_phy(nid_files(iff),
     78      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    6879     s                  o_wind10m%name,itau_w,zx_tmp_fi2d)
    6980       ENDIF
    7081
     82      IF (.NOT.clef_stations(iff)) THEN
    7183       IF (o_wind10max%flag(iff)<=lev_files(iff)) THEN
    7284      DO i=1, klon
    7385       zx_tmp_fi2d(i)=SQRT(zu10m(i)*zu10m(i)+zv10m(i)*zv10m(i))
    7486      ENDDO
    75       CALL histwrite_phy(nid_files(iff),o_wind10max%name,
    76      $                   itau_w,zx_tmp_fi2d)
    77        ENDIF
     87      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     88     $o_wind10max%name,itau_w,zx_tmp_fi2d)
     89       ENDIF
     90      ENDIF
    7891
    7992       IF (o_sicf%flag(iff)<=lev_files(iff)) THEN
     
    8194         zx_tmp_fi2d(i) = pctsrf(i,is_sic)
    8295      ENDDO
    83       CALL histwrite_phy(nid_files(iff),
     96      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    8497     $                   o_sicf%name,itau_w,zx_tmp_fi2d)
    8598       ENDIF
    8699
    87100       IF (o_q2m%flag(iff)<=lev_files(iff)) THEN
    88       CALL histwrite_phy(nid_files(iff),o_q2m%name,itau_w,zq2m)
     101      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     102     $o_q2m%name,itau_w,zq2m)
    89103       ENDIF
    90104
    91105       IF (o_u10m%flag(iff)<=lev_files(iff)) THEN
    92       CALL histwrite_phy(nid_files(iff),o_u10m%name,itau_w,zu10m)
     106      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     107     $o_u10m%name,itau_w,zu10m)
    93108       ENDIF
    94109
    95110       IF (o_v10m%flag(iff)<=lev_files(iff)) THEN
    96       CALL histwrite_phy(nid_files(iff),o_v10m%name,itau_w,zv10m)
     111      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     112     $o_v10m%name,itau_w,zv10m)
    97113       ENDIF
    98114
     
    101117         zx_tmp_fi2d(i) = paprs(i,1)
    102118      ENDDO
    103       CALL histwrite_phy(nid_files(iff),
     119      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    104120     s                   o_psol%name,itau_w,zx_tmp_fi2d)
    105121       ENDIF
    106122
    107123       IF (o_qsurf%flag(iff)<=lev_files(iff)) THEN
    108       CALL histwrite_phy(nid_files(iff),o_qsurf%name,itau_w,zxqsurf)
     124      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     125     $o_qsurf%name,itau_w,zxqsurf)
    109126       ENDIF
    110127
    111128       if (.not. ok_veget) then
    112129         IF (o_qsol%flag(iff)<=lev_files(iff)) THEN
    113         CALL histwrite_phy(nid_files(iff),o_qsol%name,itau_w,qsol)
     130        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     131     $o_qsol%name,itau_w,qsol)
    114132         ENDIF
    115133       endif
     
    119137         zx_tmp_fi2d(i) = rain_fall(i) + snow_fall(i)
    120138       ENDDO
    121       CALL histwrite_phy(nid_files(iff),o_precip%name,
    122      s                   itau_w,zx_tmp_fi2d)
     139      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     140     $o_precip%name,itau_w,zx_tmp_fi2d)
    123141      ENDIF
    124142
    125143       IF (o_ndayrain%flag(iff)<=lev_files(iff)) THEN
    126       CALL histwrite_phy(nid_files(iff),o_ndayrain%name,
    127      s                   itau_w,nday_rain)
     144      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     145     $o_ndayrain%name,itau_w,nday_rain)
    128146       ENDIF
    129147
     
    132150         zx_tmp_fi2d(i) = rain_lsc(i) + snow_lsc(i)
    133151       ENDDO
    134       CALL histwrite_phy(nid_files(iff),o_plul%name,itau_w,zx_tmp_fi2d)
     152      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     153     $o_plul%name,itau_w,zx_tmp_fi2d)
    135154      ENDIF
    136155
     
    139158         zx_tmp_fi2d(i) = rain_con(i) + snow_con(i)
    140159      ENDDO
    141       CALL histwrite_phy(nid_files(iff),o_pluc%name,itau_w,zx_tmp_fi2d)
     160      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     161     $o_pluc%name,itau_w,zx_tmp_fi2d)
    142162      ENDIF
    143163
    144164       IF (o_snow%flag(iff)<=lev_files(iff)) THEN
    145       CALL histwrite_phy(nid_files(iff),o_snow%name,itau_w,snow_fall)
     165      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     166     $o_snow%name,itau_w,snow_fall)
    146167       ENDIF
    147168
    148169       IF (o_msnow%flag(iff)<=lev_files(iff)) THEN
    149       CALL histwrite_phy(nid_files(iff),o_msnow%name,itau_w,snow_o)
     170      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     171     $o_msnow%name,itau_w,snow_o)
    150172       ENDIF
    151173
    152174       IF (o_fsnow%flag(iff)<=lev_files(iff)) THEN
    153       CALL histwrite_phy(nid_files(iff),o_fsnow%name,itau_w,zfra_o)
     175      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     176     $o_fsnow%name,itau_w,zfra_o)
    154177       ENDIF
    155178
    156179       IF (o_evap%flag(iff)<=lev_files(iff)) THEN
    157       CALL histwrite_phy(nid_files(iff),o_evap%name,itau_w,evap)
     180      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     181     $o_evap%name,itau_w,evap)
    158182       ENDIF
    159183
    160184       IF (o_tops%flag(iff)<=lev_files(iff)) THEN
    161       CALL histwrite_phy(nid_files(iff),o_tops%name,itau_w,topsw)
     185      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     186     $o_tops%name,itau_w,topsw)
    162187       ENDIF
    163188
    164189       IF (o_tops0%flag(iff)<=lev_files(iff)) THEN
    165       CALL histwrite_phy(nid_files(iff),o_tops0%name,itau_w,topsw0)
     190      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     191     $o_tops0%name,itau_w,topsw0)
    166192       ENDIF
    167193
    168194       IF (o_topl%flag(iff)<=lev_files(iff)) THEN
    169       CALL histwrite_phy(nid_files(iff),o_topl%name,itau_w,toplw)
     195      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     196     $o_topl%name,itau_w,toplw)
    170197       ENDIF
    171198
    172199       IF (o_topl0%flag(iff)<=lev_files(iff)) THEN
    173       CALL histwrite_phy(nid_files(iff),o_topl0%name,itau_w,toplw0)
     200      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     201     $o_topl0%name,itau_w,toplw0)
    174202       ENDIF
    175203
    176204       IF (o_SWupTOA%flag(iff)<=lev_files(iff)) THEN
    177205      zx_tmp_fi2d(1 : klon) = swup ( 1 : klon, klevp1 )
    178       CALL histwrite_phy(nid_files(iff),o_SWupTOA%name,
    179      s                     itau_w,zx_tmp_fi2d)
     206      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     207     $o_SWupTOA%name,itau_w,zx_tmp_fi2d)
    180208       ENDIF
    181209
    182210       IF (o_SWupTOAclr%flag(iff)<=lev_files(iff)) THEN
    183211      zx_tmp_fi2d(1 : klon) = swup0 ( 1 : klon, klevp1 )
    184       CALL histwrite_phy(nid_files(iff),
     212      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    185213     $                  o_SWupTOAclr%name,itau_w,zx_tmp_fi2d)
    186214       ENDIF
     
    188216       IF (o_SWdnTOA%flag(iff)<=lev_files(iff)) THEN
    189217      zx_tmp_fi2d(1 : klon) = swdn ( 1 : klon, klevp1 )
    190       CALL histwrite_phy(nid_files(iff),
     218      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    191219     s                  o_SWdnTOA%name,itau_w,zx_tmp_fi2d)
    192220       ENDIF
     
    194222       IF (o_SWdnTOAclr%flag(iff)<=lev_files(iff)) THEN
    195223      zx_tmp_fi2d(1 : klon) = swdn0 ( 1 : klon, klevp1 )
    196       CALL histwrite_phy(nid_files(iff),
     224      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    197225     $                  o_SWdnTOAclr%name,itau_w,zx_tmp_fi2d)
    198226       ENDIF
     
    200228       IF (o_nettop%flag(iff)<=lev_files(iff)) THEN
    201229      zx_tmp_fi2d(:) = topsw(:)-toplw(:)
    202       CALL histwrite_phy(nid_files(iff),
     230      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    203231     $                  o_nettop%name,itau_w,zx_tmp_fi2d)
    204232       ENDIF
    205233
    206234       IF (o_SWup200%flag(iff)<=lev_files(iff)) THEN
    207       CALL histwrite_phy(nid_files(iff),o_SWup200%name,itau_w,SWup200)
     235      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     236     $o_SWup200%name,itau_w,SWup200)
    208237       ENDIF
    209238
    210239       IF (o_SWup200clr%flag(iff)<=lev_files(iff)) THEN
    211       CALL histwrite_phy(nid_files(iff),
     240      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    212241     s                   o_SWup200clr%name,itau_w,SWup200clr)
    213242       ENDIF
    214243
    215244       IF (o_SWdn200%flag(iff)<=lev_files(iff)) THEN
    216       CALL histwrite_phy(nid_files(iff),o_SWdn200%name,itau_w,SWdn200)
     245      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     246     $o_SWdn200%name,itau_w,SWdn200)
    217247       ENDIF
    218248
    219249       IF (o_SWdn200clr%flag(iff)<=lev_files(iff)) THEN
    220       CALL histwrite_phy(nid_files(iff),
     250      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    221251     s                o_SWdn200clr%name,itau_w,SWdn200clr)
    222252       ENDIF
    223253
    224254       IF (o_LWup200%flag(iff)<=lev_files(iff)) THEN
    225       CALL histwrite_phy(nid_files(iff),o_LWup200%name,itau_w,LWup200)
     255      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     256     $o_LWup200%name,itau_w,LWup200)
    226257       ENDIF
    227258
    228259       IF (o_LWup200clr%flag(iff)<=lev_files(iff)) THEN
    229       CALL histwrite_phy(nid_files(iff),
     260      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    230261     s                   o_LWup200clr%name,itau_w,LWup200clr)
    231262       ENDIF
    232263
    233264       IF (o_LWdn200%flag(iff)<=lev_files(iff)) THEN
    234       CALL histwrite_phy(nid_files(iff),
     265      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    235266     s                   o_LWdn200%name,itau_w,LWdn200)
    236267       ENDIF
    237268
    238269       IF (o_LWdn200clr%flag(iff)<=lev_files(iff)) THEN
    239       CALL histwrite_phy(nid_files(iff),
     270      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    240271     s                  o_LWdn200clr%name,itau_w,LWdn200clr)
    241272       ENDIF
    242273
    243274       IF (o_sols%flag(iff)<=lev_files(iff)) THEN
    244       CALL histwrite_phy(nid_files(iff),o_sols%name,itau_w,solsw)
     275      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     276     $o_sols%name,itau_w,solsw)
    245277       ENDIF
    246278
    247279       IF (o_sols0%flag(iff)<=lev_files(iff)) THEN
    248       CALL histwrite_phy(nid_files(iff),o_sols0%name,itau_w,solsw0)
     280      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     281     $o_sols0%name,itau_w,solsw0)
    249282       ENDIF
    250283
    251284       IF (o_soll%flag(iff)<=lev_files(iff)) THEN
    252       CALL histwrite_phy(nid_files(iff),o_soll%name,itau_w,sollw)
     285      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     286     $o_soll%name,itau_w,sollw)
    253287       ENDIF
    254288
    255289       IF (o_radsol%flag(iff)<=lev_files(iff)) THEN
    256       CALL histwrite_phy(nid_files(iff),o_radsol%name,itau_w,radsol)
     290      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     291     $o_radsol%name,itau_w,radsol)
    257292       ENDIF
    258293
    259294       IF (o_soll0%flag(iff)<=lev_files(iff)) THEN
    260       CALL histwrite_phy(nid_files(iff),o_soll0%name,itau_w,sollw0)
     295      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     296     $o_soll0%name,itau_w,sollw0)
    261297       ENDIF
    262298
    263299       IF (o_SWupSFC%flag(iff)<=lev_files(iff)) THEN
    264300      zx_tmp_fi2d(1 : klon) = swup ( 1 : klon, 1 )
    265       CALL histwrite_phy(nid_files(iff),
     301      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    266302     s               o_SWupSFC%name,itau_w,zx_tmp_fi2d)
    267303       ENDIF
     
    269305       IF (o_SWupSFCclr%flag(iff)<=lev_files(iff)) THEN
    270306      zx_tmp_fi2d(1 : klon) = swup0 ( 1 : klon, 1 )
    271       CALL histwrite_phy(nid_files(iff),
     307      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    272308     $                   o_SWupSFCclr%name,itau_w,zx_tmp_fi2d)
    273309       ENDIF
     
    275311       IF (o_SWdnSFC%flag(iff)<=lev_files(iff)) THEN
    276312      zx_tmp_fi2d(1 : klon) = swdn ( 1 : klon, 1 )
    277       CALL histwrite_phy(nid_files(iff),
     313      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    278314     $                   o_SWdnSFC%name,itau_w,zx_tmp_fi2d)
    279315       ENDIF
     
    281317       IF (o_SWdnSFCclr%flag(iff)<=lev_files(iff)) THEN
    282318      zx_tmp_fi2d(1 : klon) = swdn0 ( 1 : klon, 1 )
    283       CALL histwrite_phy(nid_files(iff),
     319      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    284320     $                  o_SWdnSFCclr%name,itau_w,zx_tmp_fi2d)
    285321       ENDIF
     
    287323       IF (o_LWupSFC%flag(iff)<=lev_files(iff)) THEN
    288324      zx_tmp_fi2d(1:klon)=sollwdown(1:klon)-sollw(1:klon)
    289       CALL histwrite_phy(nid_files(iff),
     325      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    290326     $                    o_LWupSFC%name,itau_w,zx_tmp_fi2d)
    291327       ENDIF
    292328
    293329       IF (o_LWdnSFC%flag(iff)<=lev_files(iff)) THEN
    294       CALL histwrite_phy(nid_files(iff),
     330      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    295331     $                   o_LWdnSFC%name,itau_w,sollwdown)
    296332       ENDIF
     
    299335       IF (o_LWupSFCclr%flag(iff)<=lev_files(iff)) THEN
    300336      zx_tmp_fi2d(1:klon)=sollwdownclr(1:klon)-sollw0(1:klon)
    301       CALL histwrite_phy(nid_files(iff),
     337      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    302338     $                   o_LWupSFCclr%name,itau_w,zx_tmp_fi2d)
    303339       ENDIF
    304340
    305341       IF (o_LWdnSFCclr%flag(iff)<=lev_files(iff)) THEN
    306       CALL histwrite_phy(nid_files(iff),
     342      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    307343     $                   o_LWdnSFCclr%name,itau_w,sollwdownclr)
    308344       ENDIF
    309345
    310346       IF (o_bils%flag(iff)<=lev_files(iff)) THEN
    311       CALL histwrite_phy(nid_files(iff),o_bils%name,itau_w,bils)
     347      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     348     $o_bils%name,itau_w,bils)
    312349       ENDIF
    313350
    314351       IF (o_sens%flag(iff)<=lev_files(iff)) THEN
    315352      zx_tmp_fi2d(1:klon)=-1*sens(1:klon)
    316       CALL histwrite_phy(nid_files(iff),o_sens%name,itau_w,zx_tmp_fi2d)
     353      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     354     $o_sens%name,itau_w,zx_tmp_fi2d)
    317355       ENDIF
    318356
    319357       IF (o_fder%flag(iff)<=lev_files(iff)) THEN
    320       CALL histwrite_phy(nid_files(iff),o_fder%name,itau_w,fder)
     358      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     359     $o_fder%name,itau_w,fder)
    321360       ENDIF
    322361
    323362       IF (o_ffonte%flag(iff)<=lev_files(iff)) THEN
    324        CALL histwrite_phy(nid_files(iff),o_ffonte%name,itau_w,zxffonte)
     363       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     364     $o_ffonte%name,itau_w,zxffonte)
    325365       ENDIF
    326366
    327367       IF (o_fqcalving%flag(iff)<=lev_files(iff)) THEN
    328        CALL histwrite_phy(nid_files(iff),
     368       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    329369     $                    o_fqcalving%name,itau_w,zxfqcalving)
    330370       ENDIF
    331371
    332372       IF (o_fqfonte%flag(iff)<=lev_files(iff)) THEN
    333        CALL histwrite_phy(nid_files(iff),
     373       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    334374     $                   o_fqfonte%name,itau_w,zxfqfonte)
    335375       ENDIF
     
    340380          zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+pctsrf(:,nsrf)*fluxu(:,1,nsrf)
    341381         enddo
    342          CALL histwrite_phy(nid_files(iff),
     382         CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    343383     $                   o_taux%name,itau_w,zx_tmp_fi2d)
    344384       ENDIF
     
    349389          zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+pctsrf(:,nsrf)*fluxv(:,1,nsrf)
    350390         enddo
    351          CALL histwrite_phy(nid_files(iff),
     391         CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    352392     $                   o_tauy%name,itau_w,zx_tmp_fi2d)
    353393       ENDIF
     
    358398            zx_tmp_fi2d(1 : klon) = pctsrf( 1 : klon, nsrf)*100.
    359399            CALL histwrite_phy(nid_files(iff),
     400     $                     clef_stations(iff),
    360401     $                     o_pourc_srf(nsrf)%name,itau_w,
    361402     $                     zx_tmp_fi2d)
     
    364405          IF (o_fract_srf(nsrf)%flag(iff)<=lev_files(iff)) THEN
    365406          zx_tmp_fi2d(1 : klon) = pctsrf( 1 : klon, nsrf)
    366           CALL histwrite_phy(nid_files(iff),
     407          CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    367408     $                  o_fract_srf(nsrf)%name,itau_w,
    368409     $                  zx_tmp_fi2d)
     
    372413        IF (o_taux_srf(nsrf)%flag(iff)<=lev_files(iff)) THEN
    373414        zx_tmp_fi2d(1 : klon) = fluxu( 1 : klon, 1, nsrf)
    374         CALL histwrite_phy(nid_files(iff),
     415        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    375416     $                     o_taux_srf(nsrf)%name,itau_w,
    376417     $                     zx_tmp_fi2d)
     
    379420        IF (o_tauy_srf(nsrf)%flag(iff)<=lev_files(iff)) THEN           
    380421        zx_tmp_fi2d(1 : klon) = fluxv( 1 : klon, 1, nsrf)
    381         CALL histwrite_phy(nid_files(iff),
     422        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    382423     $                    o_tauy_srf(nsrf)%name,itau_w,
    383424     $                    zx_tmp_fi2d)
     
    386427        IF (o_tsol_srf(nsrf)%flag(iff)<=lev_files(iff)) THEN
    387428        zx_tmp_fi2d(1 : klon) = ftsol( 1 : klon, nsrf)
    388         CALL histwrite_phy(nid_files(iff),
     429        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    389430     $                   o_tsol_srf(nsrf)%name,itau_w,
    390431     $      zx_tmp_fi2d)
     
    393434      IF (o_u10m_srf(nsrf)%flag(iff)<=lev_files(iff)) THEN
    394435      zx_tmp_fi2d(1 : klon) = u10m(1 : klon, nsrf)
    395       CALL histwrite_phy(nid_files(iff),o_u10m_srf(nsrf)%name,
     436      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     437     $o_u10m_srf(nsrf)%name,
    396438     $                 itau_w,zx_tmp_fi2d)
    397439      ENDIF
     
    399441      IF (o_v10m_srf(nsrf)%flag(iff)<=lev_files(iff)) THEN
    400442      zx_tmp_fi2d(1 : klon) = v10m(1 : klon, nsrf)
    401       CALL histwrite_phy(nid_files(iff),o_v10m_srf(nsrf)%name,
     443      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     444     $o_v10m_srf(nsrf)%name,
    402445     $              itau_w,zx_tmp_fi2d)
    403446      ENDIF
     
    405448      IF (o_t2m_srf(nsrf)%flag(iff)<=lev_files(iff)) THEN
    406449      zx_tmp_fi2d(1 : klon) = t2m(1 : klon, nsrf)
    407       CALL histwrite_phy(nid_files(iff),o_t2m_srf(nsrf)%name,
     450      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     451     $o_t2m_srf(nsrf)%name,
    408452     $           itau_w,zx_tmp_fi2d)
    409453      ENDIF
     
    411455      IF (o_evap_srf(nsrf)%flag(iff)<=lev_files(iff)) THEN
    412456      zx_tmp_fi2d(1 : klon) = fevap(1 : klon, nsrf)
    413       CALL histwrite_phy(nid_files(iff),o_evap_srf(nsrf)%name,
     457      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     458     $o_evap_srf(nsrf)%name,
    414459     $           itau_w,zx_tmp_fi2d)
    415460      ENDIF
     
    417462       IF (o_sens_srf(nsrf)%flag(iff)<=lev_files(iff)) THEN
    418463       zx_tmp_fi2d(1 : klon) = fluxt( 1 : klon, 1, nsrf)
    419        CALL histwrite_phy(nid_files(iff),
     464       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    420465     $                    o_sens_srf(nsrf)%name,itau_w,
    421466     $      zx_tmp_fi2d)
     
    424469        IF (o_lat_srf(nsrf)%flag(iff)<=lev_files(iff)) THEN
    425470        zx_tmp_fi2d(1 : klon) = fluxlat( 1 : klon, nsrf)
    426         CALL histwrite_phy(nid_files(iff),
     471        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    427472     $                 o_lat_srf(nsrf)%name,itau_w,
    428473     $                                   zx_tmp_fi2d)
     
    431476        IF (o_flw_srf(nsrf)%flag(iff)<=lev_files(iff)) THEN
    432477        zx_tmp_fi2d(1 : klon) = fsollw( 1 : klon, nsrf)
    433         CALL histwrite_phy(nid_files(iff),
     478        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    434479     $                     o_flw_srf(nsrf)%name,itau_w,
    435480     $      zx_tmp_fi2d)
     
    438483        IF (o_fsw_srf(nsrf)%flag(iff)<=lev_files(iff)) THEN
    439484        zx_tmp_fi2d(1 : klon) = fsolsw( 1 : klon, nsrf)
    440         CALL histwrite_phy(nid_files(iff),
     485        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    441486     $                   o_fsw_srf(nsrf)%name,itau_w,
    442487     $      zx_tmp_fi2d)
     
    445490        IF (o_wbils_srf(nsrf)%flag(iff)<=lev_files(iff)) THEN
    446491        zx_tmp_fi2d(1 : klon) = wfbils( 1 : klon, nsrf)
    447         CALL histwrite_phy(nid_files(iff),
     492        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    448493     $                   o_wbils_srf(nsrf)%name,itau_w,
    449494     $      zx_tmp_fi2d)
     
    452497        IF (o_wbilo_srf(nsrf)%flag(iff)<=lev_files(iff)) THEN
    453498        zx_tmp_fi2d(1 : klon) = wfbilo( 1 : klon, nsrf)
    454         CALL histwrite_phy(nid_files(iff),
     499        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    455500     $                    o_wbilo_srf(nsrf)%name,itau_w,
    456501     $      zx_tmp_fi2d)
     
    459504       if (iflag_pbl>1 .and. lev_histday.gt.10 ) then
    460505        IF (o_tke_srf(nsrf)%flag(iff)<=lev_files(iff)) THEN
    461         CALL histwrite_phy(nid_files(iff),
     506        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    462507     $                   o_tke_srf(nsrf)%name,itau_w,
    463508     $                    pbl_tke(:,1:klev,nsrf))
    464509       ENDIF
    465510
     511      IF (.NOT.clef_stations(iff)) THEN
    466512        IF (o_tke_max_srf(nsrf)%flag(iff)<=lev_files(iff)) THEN
    467         CALL histwrite_phy(nid_files(iff),
     513        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    468514     $                    o_tke_max_srf(nsrf)%name,itau_w,
    469515     $      pbl_tke(:,1:klev,nsrf))
    470516        ENDIF
     517      ENDIF
    471518       endif
    472519      ENDDO
    473520
    474521        IF (o_cdrm%flag(iff)<=lev_files(iff)) THEN
    475       CALL histwrite_phy(nid_files(iff),o_cdrm%name,itau_w,cdragm)
     522      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     523     $o_cdrm%name,itau_w,cdragm)
    476524        ENDIF
    477525
    478526        IF (o_cdrh%flag(iff)<=lev_files(iff)) THEN
    479       CALL histwrite_phy(nid_files(iff),o_cdrh%name,itau_w,cdragh)
     527      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     528     $o_cdrh%name,itau_w,cdragh)
    480529        ENDIF
    481530
    482531        IF (o_cldl%flag(iff)<=lev_files(iff)) THEN
    483       CALL histwrite_phy(nid_files(iff),o_cldl%name,itau_w,cldl)
     532      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     533     $o_cldl%name,itau_w,cldl)
    484534        ENDIF
    485535
    486536        IF (o_cldm%flag(iff)<=lev_files(iff)) THEN
    487       CALL histwrite_phy(nid_files(iff),o_cldm%name,itau_w,cldm)
     537      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     538     $o_cldm%name,itau_w,cldm)
    488539        ENDIF
    489540
    490541        IF (o_cldh%flag(iff)<=lev_files(iff)) THEN
    491       CALL histwrite_phy(nid_files(iff),o_cldh%name,itau_w,cldh)
     542      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     543     $o_cldh%name,itau_w,cldh)
    492544        ENDIF
    493545
    494546        IF (o_cldt%flag(iff)<=lev_files(iff)) THEN
    495       CALL histwrite_phy(nid_files(iff),o_cldt%name,
     547      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     548     $o_cldt%name,
    496549     &                   itau_w,cldt)
    497550        ENDIF
    498551
    499552        IF (o_cldq%flag(iff)<=lev_files(iff)) THEN
    500       CALL histwrite_phy(nid_files(iff),o_cldq%name,itau_w,cldq)
     553      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     554     $o_cldq%name,itau_w,cldq)
    501555        ENDIF
    502556
    503557        IF (o_lwp%flag(iff)<=lev_files(iff)) THEN
    504558      zx_tmp_fi2d(1:klon) = flwp(1:klon)
    505       CALL histwrite_phy(nid_files(iff),
     559      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    506560     s                   o_lwp%name,itau_w,zx_tmp_fi2d)
    507561        ENDIF
     
    509563        IF (o_iwp%flag(iff)<=lev_files(iff)) THEN
    510564      zx_tmp_fi2d(1:klon) = fiwp(1:klon)
    511       CALL histwrite_phy(nid_files(iff),
     565      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    512566     s                    o_iwp%name,itau_w,zx_tmp_fi2d)
    513567        ENDIF
    514568
    515569        IF (o_ue%flag(iff)<=lev_files(iff)) THEN
    516       CALL histwrite_phy(nid_files(iff),o_ue%name,itau_w,ue)
     570      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     571     $o_ue%name,itau_w,ue)
    517572        ENDIF
    518573
    519574        IF (o_ve%flag(iff)<=lev_files(iff)) THEN
    520       CALL histwrite_phy(nid_files(iff),o_ve%name,itau_w,ve)
     575      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     576     $o_ve%name,itau_w,ve)
    521577        ENDIF
    522578
    523579        IF (o_uq%flag(iff)<=lev_files(iff)) THEN
    524       CALL histwrite_phy(nid_files(iff),o_uq%name,itau_w,uq)
     580      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     581     $o_uq%name,itau_w,uq)
    525582        ENDIF
    526583
    527584        IF (o_vq%flag(iff)<=lev_files(iff)) THEN
    528       CALL histwrite_phy(nid_files(iff),o_vq%name,itau_w,vq)
     585      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     586     $o_vq%name,itau_w,vq)
    529587        ENDIF
    530588
    531589      IF(iflag_con.GE.3) THEN ! sb
    532590        IF (o_cape%flag(iff)<=lev_files(iff)) THEN
    533       CALL histwrite_phy(nid_files(iff),o_cape%name,itau_w,cape)
     591      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     592     $o_cape%name,itau_w,cape)
    534593        ENDIF
    535594
    536595        IF (o_pbase%flag(iff)<=lev_files(iff)) THEN
    537       CALL histwrite_phy(nid_files(iff),o_pbase%name,itau_w,ema_pcb)
     596      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     597     $o_pbase%name,itau_w,ema_pcb)
    538598        ENDIF
    539599
    540600        IF (o_ptop%flag(iff)<=lev_files(iff)) THEN
    541       CALL histwrite_phy(nid_files(iff),o_ptop%name,itau_w,ema_pct)
     601      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     602     $o_ptop%name,itau_w,ema_pct)
    542603        ENDIF
    543604
    544605        IF (o_fbase%flag(iff)<=lev_files(iff)) THEN
    545       CALL histwrite_phy(nid_files(iff),o_fbase%name,itau_w,ema_cbmf)
     606      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     607     $o_fbase%name,itau_w,ema_cbmf)
    546608        ENDIF
    547609
    548610        IF (o_prw%flag(iff)<=lev_files(iff)) THEN
    549       CALL histwrite_phy(nid_files(iff),o_prw%name,itau_w,prw)
    550         ENDIF
    551 
     611      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     612     $o_prw%name,itau_w,prw)
     613        ENDIF
     614
     615      IF (.NOT.clef_stations(iff)) THEN
    552616      IF (o_cape_max%flag(iff)<=lev_files(iff)) THEN
    553       CALL histwrite_phy(nid_files(iff),o_cape_max%name,itau_w,cape)
     617      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     618     $o_cape_max%name,itau_w,cape)
     619      ENDIF
    554620      ENDIF
    555621
    556622       IF (o_upwd%flag(iff)<=lev_files(iff)) THEN
    557       CALL histwrite_phy(nid_files(iff),o_upwd%name,itau_w,upwd)
     623      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     624     $o_upwd%name,itau_w,upwd)
    558625       ENDIF
    559626
    560627       IF (o_Ma%flag(iff)<=lev_files(iff)) THEN
    561       CALL histwrite_phy(nid_files(iff),o_Ma%name,itau_w,Ma)
     628      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     629     $o_Ma%name,itau_w,Ma)
    562630       ENDIF
    563631
    564632       IF (o_dnwd%flag(iff)<=lev_files(iff)) THEN
    565       CALL histwrite_phy(nid_files(iff),o_dnwd%name,itau_w,dnwd)
     633      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     634     $o_dnwd%name,itau_w,dnwd)
    566635       ENDIF
    567636
    568637       IF (o_dnwd0%flag(iff)<=lev_files(iff)) THEN
    569       CALL histwrite_phy(nid_files(iff),o_dnwd0%name,itau_w,dnwd0)
     638      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     639     $o_dnwd0%name,itau_w,dnwd0)
    570640       ENDIF
    571641
    572642       IF (o_ftime_con%flag(iff)<=lev_files(iff)) THEN
    573643        zx_tmp_fi2d=float(itau_con)/float(itap)
    574       CALL histwrite_phy(nid_files(iff),o_ftime_con%name,
     644      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     645     $o_ftime_con%name,
    575646     s                   itau_w,zx_tmp_fi2d)
    576647       ENDIF
     
    582653         zx_tmp_fi3d=dnwd+dnwd0+upwd
    583654        endif
    584       CALL histwrite_phy(nid_files(iff),o_mc%name,itau_w,zx_tmp_fi3d)
     655      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     656     $o_mc%name,itau_w,zx_tmp_fi3d)
    585657       ENDIF
    586658     
     
    588660
    589661        IF (o_s_pblh%flag(iff)<=lev_files(iff)) THEN
    590       CALL histwrite_phy(nid_files(iff),o_s_pblh%name,itau_w,s_pblh)
     662      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     663     $o_s_pblh%name,itau_w,s_pblh)
    591664        ENDIF
    592665
    593666        IF (o_s_pblt%flag(iff)<=lev_files(iff)) THEN
    594       CALL histwrite_phy(nid_files(iff),o_s_pblt%name,itau_w,s_pblt)
     667      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     668     $o_s_pblt%name,itau_w,s_pblt)
    595669        ENDIF
    596670
    597671        IF (o_s_lcl%flag(iff)<=lev_files(iff)) THEN
    598       CALL histwrite_phy(nid_files(iff),o_s_lcl%name,itau_w,s_lcl)
     672      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     673     $o_s_lcl%name,itau_w,s_lcl)
    599674        ENDIF
    600675
    601676        IF (o_s_therm%flag(iff)<=lev_files(iff)) THEN
    602       CALL histwrite_phy(nid_files(iff),o_s_therm%name,itau_w,s_therm)
     677      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     678     $o_s_therm%name,itau_w,s_therm)
    603679        ENDIF
    604680
    605681!IM : Les champs suivants (s_capCL, s_oliqCL, s_cteiCL, s_trmb1, s_trmb2, s_trmb3) ne sont pas definis dans HBTM.F
    606682!       IF (o_s_capCL%flag(iff)<=lev_files(iff)) THEN
    607 !     CALL histwrite_phy(nid_files(iff),o_s_capCL%name,itau_w,s_capCL)
     683!     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     684!    $o_s_capCL%name,itau_w,s_capCL)
    608685!       ENDIF
    609686
    610687!       IF (o_s_oliqCL%flag(iff)<=lev_files(iff)) THEN
    611 !     CALL histwrite_phy(nid_files(iff),o_s_oliqCL%name,itau_w,s_oliqCL)
     688!     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     689!    $o_s_oliqCL%name,itau_w,s_oliqCL)
    612690!       ENDIF
    613691
    614692!       IF (o_s_cteiCL%flag(iff)<=lev_files(iff)) THEN
    615 !     CALL histwrite_phy(nid_files(iff),o_s_cteiCL%name,itau_w,s_cteiCL)
     693!     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     694!    $o_s_cteiCL%name,itau_w,s_cteiCL)
    616695!       ENDIF
    617696
    618697!       IF (o_s_trmb1%flag(iff)<=lev_files(iff)) THEN
    619 !     CALL histwrite_phy(nid_files(iff),o_s_trmb1%name,itau_w,s_trmb1)
     698!     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     699!    $o_s_trmb1%name,itau_w,s_trmb1)
    620700!       ENDIF
    621701
    622702!       IF (o_s_trmb2%flag(iff)<=lev_files(iff)) THEN
    623 !     CALL histwrite_phy(nid_files(iff),o_s_trmb2%name,itau_w,s_trmb2)
     703!     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     704!    $o_s_trmb2%name,itau_w,s_trmb2)
    624705!       ENDIF
    625706
    626707!       IF (o_s_trmb3%flag(iff)<=lev_files(iff)) THEN
    627 !     CALL histwrite_phy(nid_files(iff),o_s_trmb3%name,itau_w,s_trmb3)
     708!     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     709!    $o_s_trmb3%name,itau_w,s_trmb3)
    628710!       ENDIF
    629711
     
    632714        ll=0
    633715        DO k=1, nlevSTD
    634 !         IF(k.GE.2.AND.k.LE.12) bb2=clevSTD(k)
    635 !         IF(k.GE.13.AND.k.LE.17) bb3=clevSTD(k)
    636716         bb2=clevSTD(k)
    637717         IF(bb2.EQ."850".OR.bb2.EQ."700".OR.
    638718     $      bb2.EQ."500".OR.bb2.EQ."200".OR.
     719     $      bb2.EQ."100".OR.
    639720     $      bb2.EQ."50".OR.bb2.EQ."10") THEN
    640721
     
    642723          ll=ll+1
    643724       IF (o_uSTDlevs(ll)%flag(iff)<=lev_files(iff)) THEN
    644        CALL histwrite_phy(nid_files(iff),o_uSTDlevs(ll)%name,
     725       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     726     $o_uSTDlevs(ll)%name,
    645727     &                    itau_w,uwriteSTD(:,k,iff))
    646728       ENDIF
    647729
    648730       IF (o_vSTDlevs(ll)%flag(iff)<=lev_files(iff)) THEN
    649       CALL histwrite_phy(nid_files(iff),o_vSTDlevs(ll)%name, 
     731      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     732     $o_vSTDlevs(ll)%name, 
    650733     &                   itau_w,vwriteSTD(:,k,iff))
    651734       ENDIF
    652735
    653736       IF (o_wSTDlevs(ll)%flag(iff)<=lev_files(iff)) THEN
    654       CALL histwrite_phy(nid_files(iff),o_wSTDlevs(ll)%name,
     737      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     738     $o_wSTDlevs(ll)%name,
    655739     &                    itau_w,wwriteSTD(:,k,iff))
    656740       ENDIF
    657741
    658742       IF (o_zSTDlevs(ll)%flag(iff)<=lev_files(iff)) THEN
    659       CALL histwrite_phy(nid_files(iff),o_zSTDlevs(ll)%name,
     743      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     744     $o_zSTDlevs(ll)%name,
    660745     &               itau_w,phiwriteSTD(:,k,iff))
    661746       ENDIF
    662747
    663748       IF (o_qSTDlevs(ll)%flag(iff)<=lev_files(iff)) THEN
    664       CALL histwrite_phy(nid_files(iff),o_qSTDlevs(ll)%name,
     749      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     750     $o_qSTDlevs(ll)%name,
    665751     &                   itau_w, qwriteSTD(:,k,iff))
    666752       ENDIF
    667753
    668754       IF (o_tSTDlevs(ll)%flag(iff)<=lev_files(iff)) THEN
    669       CALL histwrite_phy(nid_files(iff),o_tSTDlevs(ll)%name,
     755      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     756     $o_tSTDlevs(ll)%name,
    670757     &                   itau_w, twriteSTD(:,k,iff))
    671758       ENDIF
     
    685772       ENDIF
    686773      ENDDO
    687       CALL histwrite_phy(nid_files(iff),
     774      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    688775     s                   o_t_oce_sic%name,itau_w,zx_tmp_fi2d)
    689776      ENDIF
     
    693780      IF (iflag_coupl.EQ.1) THEN
    694781       IF (o_ale_bl%flag(iff)<=lev_files(iff)) THEN
    695        CALL histwrite_phy(nid_files(iff),o_ale_bl%name,itau_w,ale_bl)
     782       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     783     $o_ale_bl%name,itau_w,ale_bl)
    696784       ENDIF
    697785       IF (o_alp_bl%flag(iff)<=lev_files(iff)) THEN
    698        CALL histwrite_phy(nid_files(iff),o_alp_bl%name,itau_w,alp_bl)
     786       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     787     $o_alp_bl%name,itau_w,alp_bl)
    699788       ENDIF
    700789      ENDIF !iflag_coupl.EQ.1
     
    705794      IF (iflag_wake.EQ.1) THEN
    706795       IF (o_ale_wk%flag(iff)<=lev_files(iff)) THEN
    707        CALL histwrite_phy(nid_files(iff),o_ale_wk%name,itau_w,ale_wake)
     796       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     797     $o_ale_wk%name,itau_w,ale_wake)
    708798       ENDIF
    709799       IF (o_alp_wk%flag(iff)<=lev_files(iff)) THEN
    710        CALL histwrite_phy(nid_files(iff),o_alp_wk%name,itau_w,alp_wake)
     800       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     801     $o_alp_wk%name,itau_w,alp_wake)
    711802       ENDIF
    712803
    713804       IF (o_ale%flag(iff)<=lev_files(iff)) THEN
    714        CALL histwrite_phy(nid_files(iff),o_ale%name,itau_w,ale)
     805       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     806     $o_ale%name,itau_w,ale)
    715807       ENDIF
    716808       IF (o_alp%flag(iff)<=lev_files(iff)) THEN
    717        CALL histwrite_phy(nid_files(iff),o_alp%name,itau_w,alp)
     809       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     810     $o_alp%name,itau_w,alp)
    718811       ENDIF
    719812       IF (o_cin%flag(iff)<=lev_files(iff)) THEN
    720        CALL histwrite_phy(nid_files(iff),o_cin%name,itau_w,cin)
     813       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     814     $o_cin%name,itau_w,cin)
    721815       ENDIF
    722816       IF (o_wape%flag(iff)<=lev_files(iff)) THEN
    723        CALL histwrite_phy(nid_files(iff),o_WAPE%name,itau_w,wake_pe)
     817       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     818     $o_WAPE%name,itau_w,wake_pe)
    724819       ENDIF
    725820       IF (o_wake_h%flag(iff)<=lev_files(iff)) THEN
    726       CALL histwrite_phy(nid_files(iff),o_wake_h%name,itau_w,wake_h)
     821      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     822     $o_wake_h%name,itau_w,wake_h)
    727823       ENDIF
    728824
    729825       IF (o_wake_s%flag(iff)<=lev_files(iff)) THEN
    730       CALL histwrite_phy(nid_files(iff),o_wake_s%name,itau_w,wake_s)
     826      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     827     $o_wake_s%name,itau_w,wake_s)
    731828       ENDIF
    732829
    733830        IF (o_wake_deltat%flag(iff)<=lev_files(iff)) THEN
    734        CALL histwrite_phy(nid_files(iff),o_wake_deltat%name,
     831       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     832     $o_wake_deltat%name,
    735833     $                     itau_w,wake_deltat)
    736834        ENDIF
    737835
    738836        IF (o_wake_deltaq%flag(iff)<=lev_files(iff)) THEN
    739        CALL histwrite_phy(nid_files(iff),o_wake_deltaq%name,
     837       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     838     $o_wake_deltaq%name,
    740839     $                    itau_w,wake_deltaq)
    741840        ENDIF
    742841
    743842        IF (o_wake_omg%flag(iff)<=lev_files(iff)) THEN
    744        CALL histwrite_phy(nid_files(iff),
     843       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    745844     s                    o_wake_omg%name,itau_w,wake_omg)
    746845        ENDIF
     
    750849     &                                        /pdtphys
    751850           CALL histwrite_phy(nid_files(iff),
     851     $clef_stations(iff),
    752852     &                       o_dtwak%name,itau_w,zx_tmp_fi3d)
    753853         ENDIF
     
    755855        IF (o_dqwak%flag(iff)<=lev_files(iff)) THEN
    756856        zx_tmp_fi3d(1:klon,1:klev)=d_q_wake(1:klon,1:klev)/pdtphys
    757         CALL histwrite_phy(nid_files(iff),
     857        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    758858     &                     o_dqwak%name,itau_w,zx_tmp_fi3d)
    759859        ENDIF
     
    761861
    762862        IF (o_Vprecip%flag(iff)<=lev_files(iff)) THEN
    763        CALL histwrite_phy(nid_files(iff),o_Vprecip%name,itau_w,Vprecip)
     863       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     864     $o_Vprecip%name,itau_w,Vprecip)
    764865        ENDIF
    765866
    766867        IF (o_ftd%flag(iff)<=lev_files(iff)) THEN
    767        CALL histwrite_phy(nid_files(iff),o_ftd%name,itau_w,ftd)
     868       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     869     $o_ftd%name,itau_w,ftd)
    768870        ENDIF
    769871
    770872        IF (o_fqd%flag(iff)<=lev_files(iff)) THEN
    771        CALL histwrite_phy(nid_files(iff),o_fqd%name,itau_w,fqd)
     873       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     874     $o_fqd%name,itau_w,fqd)
    772875        ENDIF
    773876      ENDIF !(iflag_con.EQ.3)
     
    776879      IF ( o_slab_bils%flag(iff)<=lev_files(iff))
    777880     $     CALL histwrite_phy(
    778      $     nid_files(iff),o_slab_bils%name,itau_w,slab_wfbils)
     881     $     nid_files(iff),clef_stations(iff),
     882     $o_slab_bils%name,itau_w,slab_wfbils)
    779883
    780884      ENDIF !type_ocean == force/slab
    781885
    782886      IF (o_weakinv%flag(iff)<=lev_files(iff)) THEN
    783       CALL histwrite_phy(nid_files(iff),
     887      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    784888     s                  o_weakinv%name,itau_w,weak_inversion)
    785889      ENDIF
    786890
    787       IF (o_dthmin%flag(iff)<=lev_files(iff)) THEN
    788       CALL histwrite_phy(nid_files(iff),o_dthmin%name,itau_w,dthmin)
    789       ENDIF
     891!     IF (o_dthmin%flag(iff)<=lev_files(iff)) THEN
     892!     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     893!    $o_dthmin%name,itau_w,dthmin)
     894!     ENDIF
    790895
    791896       IF (o_cldtau%flag(iff)<=lev_files(iff)) THEN
    792        CALL histwrite_phy(nid_files(iff),o_cldtau%name,itau_w,cldtau)
     897       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     898     $o_cldtau%name,itau_w,cldtau)
    793899       ENDIF
    794900
    795901       IF (o_cldemi%flag(iff)<=lev_files(iff)) THEN
    796        CALL histwrite_phy(nid_files(iff),o_cldemi%name,itau_w,cldemi)
     902       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     903     $o_cldemi%name,itau_w,cldemi)
    797904       ENDIF
    798905
    799906      IF (o_pr_con_l%flag(iff)<=lev_files(iff)) THEN
    800       CALL histwrite_phy(nid_files(iff),
     907      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    801908     s         o_pr_con_l%name,itau_w,pmflxr(:,1:klev))
    802909      ENDIF
    803910
    804911      IF (o_pr_con_i%flag(iff)<=lev_files(iff)) THEN
    805       CALL histwrite_phy(nid_files(iff),
     912      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    806913     s         o_pr_con_i%name,itau_w,pmflxs(:,1:klev))
    807914      ENDIF
    808915
    809916      IF (o_pr_lsc_l%flag(iff)<=lev_files(iff)) THEN
    810       CALL histwrite_phy(nid_files(iff),
     917      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    811918     s        o_pr_lsc_l%name,itau_w,prfl(:,1:klev))
    812919      ENDIF
    813920
    814921      IF (o_pr_lsc_i%flag(iff)<=lev_files(iff)) THEN
    815       CALL histwrite_phy(nid_files(iff),
     922      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    816923     s        o_pr_lsc_i%name,itau_w,psfl(:,1:klev))
    817924      ENDIF
    818925
    819926      IF (o_re%flag(iff)<=lev_files(iff)) THEN
    820       CALL histwrite_phy(nid_files(iff),o_re%name,itau_w,re)
     927      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     928     $o_re%name,itau_w,re)
    821929      ENDIF
    822930
    823931      IF (o_fl%flag(iff)<=lev_files(iff)) THEN
    824       CALL histwrite_phy(nid_files(iff),o_fl%name,itau_w,fl)
     932      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     933     $o_fl%name,itau_w,fl)
    825934      ENDIF
    826935
     
    831940       zx_tmp_fi2d(i)=MIN(100.,rh2m(i)*100.)
    832941      ENDDO
    833       CALL histwrite_phy(nid_files(iff),o_rh2m%name,itau_w,zx_tmp_fi2d)
    834       ENDIF
    835 
     942      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     943     $o_rh2m%name,itau_w,zx_tmp_fi2d)
     944      ENDIF
     945
     946      IF (.NOT.clef_stations(iff)) THEN
    836947      IF (o_rh2m_min%flag(iff)<=lev_files(iff)) THEN
    837948      DO i=1, klon
    838949       zx_tmp_fi2d(i)=MIN(100.,rh2m(i)*100.)
    839950      ENDDO
    840       CALL histwrite_phy(nid_files(iff),o_rh2m_min%name,
     951      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     952     $o_rh2m_min%name,
    841953     s               itau_w,zx_tmp_fi2d)
    842954      ENDIF
     
    846958       zx_tmp_fi2d(i)=MIN(100.,rh2m(i)*100.)
    847959      ENDDO
    848       CALL histwrite_phy(nid_files(iff),o_rh2m_max%name,
     960      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     961     $o_rh2m_max%name,
    849962     s              itau_w,zx_tmp_fi2d)
    850963      ENDIF
     964      ENDIF
    851965
    852966
    853967      IF (o_qsat2m%flag(iff)<=lev_files(iff)) THEN
    854       CALL histwrite_phy(nid_files(iff),o_qsat2m%name,itau_w,qsat2m)
     968      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     969     $o_qsat2m%name,itau_w,qsat2m)
    855970      ENDIF
    856971
    857972      IF (o_tpot%flag(iff)<=lev_files(iff)) THEN
    858       CALL histwrite_phy(nid_files(iff),o_tpot%name,itau_w,tpot)
     973      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     974     $o_tpot%name,itau_w,tpot)
    859975      ENDIF
    860976
    861977       IF (o_tpote%flag(iff)<=lev_files(iff)) THEN
    862       CALL histwrite_phy(nid_files(iff),o_tpote%name,itau_w,tpote)
     978      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     979     $o_tpote%name,itau_w,tpote)
    863980       ENDIF
    864981
    865982      IF (o_SWnetOR%flag(iff)<=lev_files(iff)) THEN
    866983      zx_tmp_fi2d(1 : klon) = fsolsw( 1 : klon, is_ter)
    867       CALL histwrite_phy(nid_files(iff),
     984      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    868985     s                   o_SWnetOR%name,itau_w, zx_tmp_fi2d)
    869986      ENDIF
     
    871988      IF (o_SWdownOR%flag(iff)<=lev_files(iff)) THEN
    872989      zx_tmp_fi2d(1:klon) = solsw(1:klon)/(1.-albsol1(1:klon))
    873       CALL histwrite_phy(nid_files(iff),
     990      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    874991     s                   o_SWdownOR%name,itau_w, zx_tmp_fi2d)
    875992      ENDIF
    876993
    877994      IF (o_LWdownOR%flag(iff)<=lev_files(iff)) THEN
    878       CALL histwrite_phy(nid_files(iff),
     995      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    879996     s                  o_LWdownOR%name,itau_w,sollwdown)
    880997      ENDIF
    881998
    882999      IF (o_snowl%flag(iff)<=lev_files(iff)) THEN
    883       CALL histwrite_phy(nid_files(iff),o_snowl%name,itau_w,snow_lsc)
     1000      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1001     $o_snowl%name,itau_w,snow_lsc)
    8841002      ENDIF
    8851003
    8861004      IF (o_solldown%flag(iff)<=lev_files(iff)) THEN
    887       CALL histwrite_phy(nid_files(iff),
     1005      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    8881006     s                   o_solldown%name,itau_w,sollwdown)
    8891007      ENDIF
    8901008
    8911009      IF (o_dtsvdfo%flag(iff)<=lev_files(iff)) THEN
    892       CALL histwrite_phy(nid_files(iff),
     1010      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    8931011     s                 o_dtsvdfo%name,itau_w,d_ts(:,is_oce))
    8941012      ENDIF
    8951013
    8961014      IF (o_dtsvdft%flag(iff)<=lev_files(iff)) THEN
    897       CALL histwrite_phy(nid_files(iff),
     1015      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    8981016     s                   o_dtsvdft%name,itau_w,d_ts(:,is_ter))
    8991017      ENDIF
    9001018
    9011019       IF (o_dtsvdfg%flag(iff)<=lev_files(iff)) THEN
    902         CALL histwrite_phy(nid_files(iff),
     1020        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    9031021     $                   o_dtsvdfg%name,itau_w, d_ts(:,is_lic))
    9041022       ENDIF
    9051023
    9061024       IF (o_dtsvdfi%flag(iff)<=lev_files(iff)) THEN
    907       CALL histwrite_phy(nid_files(iff),
     1025      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    9081026     s                   o_dtsvdfi%name,itau_w,d_ts(:,is_sic))
    9091027       ENDIF
    9101028
    9111029       IF (o_rugs%flag(iff)<=lev_files(iff)) THEN
    912       CALL histwrite_phy(nid_files(iff),o_rugs%name,itau_w,zxrugs)
     1030      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1031     $o_rugs%name,itau_w,zxrugs)
    9131032       ENDIF
    9141033
     
    9181037
    9191038          IF (o_od550aer%flag(iff)<=lev_files(iff)) THEN
    920              CALL histwrite_phy(nid_files(iff),o_od550aer%name,itau_w,
     1039             CALL histwrite_phy(nid_files(iff),
     1040     $clef_stations(iff),
     1041     $o_od550aer%name,itau_w,
    9211042     $            od550aer)
    9221043          ENDIF
    9231044          IF (o_od865aer%flag(iff)<=lev_files(iff)) THEN
    924              CALL histwrite_phy(nid_files(iff),o_od865aer%name,itau_w,
     1045             CALL histwrite_phy(nid_files(iff),
     1046     $clef_stations(iff),
     1047     $o_od865aer%name,itau_w,
    9251048     $            od865aer)
    9261049          ENDIF
    9271050          IF (o_absvisaer%flag(iff)<=lev_files(iff)) THEN
    928              CALL histwrite_phy(nid_files(iff),o_absvisaer%name,itau_w,
     1051             CALL histwrite_phy(nid_files(iff),
     1052     $clef_stations(iff),
     1053     $o_absvisaer%name,itau_w,
    9291054     $            absvisaer)
    9301055          ENDIF
    9311056          IF (o_od550lt1aer%flag(iff)<=lev_files(iff)) THEN
    932             CALL histwrite_phy(nid_files(iff),o_od550lt1aer%name,itau_w,
     1057            CALL histwrite_phy(nid_files(iff),
     1058     $clef_stations(iff),
     1059     $o_od550lt1aer%name,itau_w,
    9331060     $            od550lt1aer)
    9341061          ENDIF
    9351062
    9361063          IF (o_sconcso4%flag(iff)<=lev_files(iff)) THEN
    937               CALL histwrite_phy(nid_files(iff),o_sconcso4%name,itau_w,
     1064              CALL histwrite_phy(nid_files(iff),
     1065     $clef_stations(iff),
     1066     $o_sconcso4%name,itau_w,
    9381067     $            sconcso4)
    9391068          ENDIF
    9401069          IF (o_sconcoa%flag(iff)<=lev_files(iff)) THEN
    941               CALL histwrite_phy(nid_files(iff),o_sconcoa%name,itau_w,
     1070              CALL histwrite_phy(nid_files(iff),
     1071     $clef_stations(iff),
     1072     $o_sconcoa%name,itau_w,
    9421073     $            sconcoa)
    9431074          ENDIF
    9441075          IF (o_sconcbc%flag(iff)<=lev_files(iff)) THEN
    945               CALL histwrite_phy(nid_files(iff),o_sconcbc%name,itau_w,
     1076              CALL histwrite_phy(nid_files(iff),
     1077     $clef_stations(iff),
     1078     $o_sconcbc%name,itau_w,
    9461079     $            sconcbc)
    9471080          ENDIF
    9481081          IF (o_sconcss%flag(iff)<=lev_files(iff)) THEN
    949               CALL histwrite_phy(nid_files(iff),o_sconcss%name,itau_w,
     1082              CALL histwrite_phy(nid_files(iff),
     1083     $clef_stations(iff),
     1084     $o_sconcss%name,itau_w,
    9501085     $            sconcss)
    9511086          ENDIF
    9521087          IF (o_sconcdust%flag(iff)<=lev_files(iff)) THEN
    953               CALL histwrite_phy(nid_files(iff),o_sconcdust%name,itau_w,
     1088              CALL histwrite_phy(nid_files(iff),
     1089     $clef_stations(iff),
     1090     $o_sconcdust%name,itau_w,
    9541091     $            sconcdust)
    9551092          ENDIF
    9561093         
    9571094          IF (o_concso4%flag(iff)<=lev_files(iff)) THEN
    958               CALL histwrite_phy(nid_files(iff),o_concso4%name,itau_w,
     1095              CALL histwrite_phy(nid_files(iff),
     1096     $clef_stations(iff),
     1097     $o_concso4%name,itau_w,
    9591098     $            concso4)
    9601099          ENDIF
    9611100          IF (o_concoa%flag(iff)<=lev_files(iff)) THEN
    962               CALL histwrite_phy(nid_files(iff),o_concoa%name,itau_w,
     1101              CALL histwrite_phy(nid_files(iff),
     1102     $clef_stations(iff),
     1103     $o_concoa%name,itau_w,
    9631104     $            concoa)
    9641105          ENDIF
    9651106          IF (o_concbc%flag(iff)<=lev_files(iff)) THEN
    966               CALL histwrite_phy(nid_files(iff),o_concbc%name,itau_w,
     1107              CALL histwrite_phy(nid_files(iff),
     1108     $clef_stations(iff),
     1109     $o_concbc%name,itau_w,
    9671110     $            concbc)
    9681111          ENDIF
    9691112          IF (o_concss%flag(iff)<=lev_files(iff)) THEN
    970               CALL histwrite_phy(nid_files(iff),o_concss%name,itau_w,
     1113              CALL histwrite_phy(nid_files(iff),
     1114     $clef_stations(iff),
     1115     $o_concss%name,itau_w,
    9711116     $            concss)
    9721117          ENDIF
    9731118          IF (o_concdust%flag(iff)<=lev_files(iff)) THEN
    974               CALL histwrite_phy(nid_files(iff),o_concdust%name,itau_w,
     1119              CALL histwrite_phy(nid_files(iff),
     1120     $clef_stations(iff),
     1121     $o_concdust%name,itau_w,
    9751122     $            concdust)
    9761123          ENDIF
    9771124         
    9781125          IF (o_loadso4%flag(iff)<=lev_files(iff)) THEN
    979               CALL histwrite_phy(nid_files(iff),o_loadso4%name,itau_w,
     1126              CALL histwrite_phy(nid_files(iff),
     1127     $clef_stations(iff),
     1128     $o_loadso4%name,itau_w,
    9801129     $            loadso4)
    9811130          ENDIF
    9821131          IF (o_loadoa%flag(iff)<=lev_files(iff)) THEN
    983               CALL histwrite_phy(nid_files(iff),o_loadoa%name,itau_w,
     1132              CALL histwrite_phy(nid_files(iff),
     1133     $clef_stations(iff),
     1134     $o_loadoa%name,itau_w,
    9841135     $            loadoa)
    9851136          ENDIF
    9861137          IF (o_loadbc%flag(iff)<=lev_files(iff)) THEN
    987               CALL histwrite_phy(nid_files(iff),o_loadbc%name,itau_w,
     1138              CALL histwrite_phy(nid_files(iff),
     1139     $clef_stations(iff),
     1140     $o_loadbc%name,itau_w,
    9881141     $            loadbc)
    9891142          ENDIF
    9901143          IF (o_loadss%flag(iff)<=lev_files(iff)) THEN
    991               CALL histwrite_phy(nid_files(iff),o_loadss%name,itau_w,
     1144              CALL histwrite_phy(nid_files(iff),
     1145     $clef_stations(iff),
     1146     $o_loadss%name,itau_w,
    9921147     $            loadss)
    9931148          ENDIF
    9941149          IF (o_loaddust%flag(iff)<=lev_files(iff)) THEN
    995               CALL histwrite_phy(nid_files(iff),o_loaddust%name,itau_w,
     1150              CALL histwrite_phy(nid_files(iff),
     1151     $clef_stations(iff),
     1152     $o_loaddust%name,itau_w,
    9961153     $            loaddust)
    9971154          ENDIF
     
    10001157            IF (o_tausumaero(naero)%flag(iff)<=lev_files(iff)) THEN
    10011158                CALL histwrite_phy(nid_files(iff),
     1159     $clef_stations(iff),
    10021160     $              o_tausumaero(naero)%name,itau_w,
    10031161     $              tausum_aero(:,2,naero) )
     
    10091167       IF (ok_ade) THEN
    10101168          IF (o_topswad%flag(iff)<=lev_files(iff)) THEN
    1011              CALL histwrite_phy(nid_files(iff),o_topswad%name,itau_w,
     1169             CALL histwrite_phy(nid_files(iff),
     1170     $clef_stations(iff),
     1171     $o_topswad%name,itau_w,
    10121172     $            topswad_aero)
    10131173          ENDIF
    10141174          IF (o_solswad%flag(iff)<=lev_files(iff)) THEN
    1015              CALL histwrite_phy(nid_files(iff),o_solswad%name,itau_w,
     1175             CALL histwrite_phy(nid_files(iff),
     1176     $clef_stations(iff),
     1177     $o_solswad%name,itau_w,
    10161178     $            solswad_aero)
    10171179          ENDIF
     
    10201182        if (new_aod) then             
    10211183        IF (o_swtoaas_nat%flag(iff)<=lev_files(iff)) THEN
    1022         CALL histwrite_phy(nid_files(iff),o_swtoaas_nat%name,itau_w,
     1184        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1185     $o_swtoaas_nat%name,itau_w,
    10231186     $      topsw_aero(:,1))
    10241187        ENDIF
    10251188
    10261189        IF (o_swsrfas_nat%flag(iff)<=lev_files(iff)) THEN
    1027         CALL histwrite_phy(nid_files(iff),o_swsrfas_nat%name,itau_w,
     1190        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1191     $o_swsrfas_nat%name,itau_w,
    10281192     $      solsw_aero(:,1))
    10291193        ENDIF
    10301194
    10311195        IF (o_swtoacs_nat%flag(iff)<=lev_files(iff)) THEN
    1032         CALL histwrite_phy(nid_files(iff),o_swtoacs_nat%name,itau_w,
     1196        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1197     $o_swtoacs_nat%name,itau_w,
    10331198     $      topsw0_aero(:,1))
    10341199        ENDIF
    10351200
    10361201        IF (o_swsrfcs_nat%flag(iff)<=lev_files(iff)) THEN
    1037         CALL histwrite_phy(nid_files(iff),o_swsrfcs_nat%name,itau_w,
     1202        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1203     $o_swsrfcs_nat%name,itau_w,
    10381204     $      solsw0_aero(:,1))
    10391205        ENDIF
     
    10411207!ant
    10421208        IF (o_swtoaas_ant%flag(iff)<=lev_files(iff)) THEN
    1043         CALL histwrite_phy(nid_files(iff),o_swtoaas_ant%name,itau_w,
     1209        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1210     $o_swtoaas_ant%name,itau_w,
    10441211     $      topsw_aero(:,2))
    10451212        ENDIF
    10461213
    10471214        IF (o_swsrfas_ant%flag(iff)<=lev_files(iff)) THEN
    1048         CALL histwrite_phy(nid_files(iff),o_swsrfas_ant%name,itau_w,
     1215        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1216     $o_swsrfas_ant%name,itau_w,
    10491217     $      solsw_aero(:,2))
    10501218        ENDIF
    10511219
    10521220        IF (o_swtoacs_ant%flag(iff)<=lev_files(iff)) THEN
    1053         CALL histwrite_phy(nid_files(iff),o_swtoacs_ant%name,itau_w,
     1221        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1222     $o_swtoacs_ant%name,itau_w,
    10541223     $      topsw0_aero(:,2))
    10551224        ENDIF
    10561225
    10571226        IF (o_swsrfcs_ant%flag(iff)<=lev_files(iff)) THEN
    1058         CALL histwrite_phy(nid_files(iff),o_swsrfcs_ant%name,itau_w,
     1227        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1228     $o_swsrfcs_ant%name,itau_w,
    10591229     $      solsw0_aero(:,2))
    10601230        ENDIF
     
    10641234        if (.not. aerosol_couple) then
    10651235        IF (o_swtoacf_nat%flag(iff)<=lev_files(iff)) THEN
    1066         CALL histwrite_phy(nid_files(iff),o_swtoacf_nat%name,itau_w,
     1236        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1237     $o_swtoacf_nat%name,itau_w,
    10671238     $      topswcf_aero(:,1))
    10681239        ENDIF
    10691240
    10701241        IF (o_swsrfcf_nat%flag(iff)<=lev_files(iff)) THEN
    1071         CALL histwrite_phy(nid_files(iff),o_swsrfcf_nat%name,itau_w,
     1242        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1243     $o_swsrfcf_nat%name,itau_w,
    10721244     $      solswcf_aero(:,1))
    10731245        ENDIF
    10741246
    10751247        IF (o_swtoacf_ant%flag(iff)<=lev_files(iff)) THEN
    1076         CALL histwrite_phy(nid_files(iff),o_swtoacf_ant%name,itau_w,
     1248        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1249     $o_swtoacf_ant%name,itau_w,
    10771250     $      topswcf_aero(:,2))
    10781251        ENDIF
    10791252
    10801253        IF (o_swsrfcf_ant%flag(iff)<=lev_files(iff)) THEN
    1081         CALL histwrite_phy(nid_files(iff),o_swsrfcf_ant%name,itau_w,
     1254        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1255     $o_swsrfcf_ant%name,itau_w,
    10821256     $      solswcf_aero(:,2))
    10831257        ENDIF
    10841258
    10851259        IF (o_swtoacf_zero%flag(iff)<=lev_files(iff)) THEN
    1086         CALL histwrite_phy(nid_files(iff),o_swtoacf_zero%name,itau_w,
     1260        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1261     $o_swtoacf_zero%name,itau_w,
    10871262     $      topswcf_aero(:,3))
    10881263        ENDIF
    10891264
    10901265        IF (o_swsrfcf_zero%flag(iff)<=lev_files(iff)) THEN
    1091         CALL histwrite_phy(nid_files(iff),o_swsrfcf_zero%name,itau_w,
     1266        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1267     $o_swsrfcf_zero%name,itau_w,
    10921268     $      solswcf_aero(:,3))
    10931269        ENDIF
     
    11011277       IF (ok_aie) THEN
    11021278          IF (o_topswai%flag(iff)<=lev_files(iff)) THEN
    1103              CALL histwrite_phy(nid_files(iff),o_topswai%name,itau_w,
     1279             CALL histwrite_phy(nid_files(iff),
     1280     $clef_stations(iff),
     1281     $o_topswai%name,itau_w,
    11041282     $            topswai_aero)
    11051283          ENDIF
    11061284          IF (o_solswai%flag(iff)<=lev_files(iff)) THEN
    1107              CALL histwrite_phy(nid_files(iff),o_solswai%name,itau_w,
     1285             CALL histwrite_phy(nid_files(iff),
     1286     $clef_stations(iff),
     1287     $o_solswai%name,itau_w,
    11081288     $            solswai_aero)
    11091289          ENDIF
    11101290          IF (o_scdnc%flag(iff)<=lev_files(iff)) THEN
    1111              CALL histwrite_phy(nid_files(iff),o_scdnc%name,itau_w,
     1291             CALL histwrite_phy(nid_files(iff),
     1292     $clef_stations(iff),
     1293     $o_scdnc%name,itau_w,
    11121294     $            scdnc)
    11131295          ENDIF
    11141296          IF (o_cldncl%flag(iff)<=lev_files(iff)) THEN
    1115              CALL histwrite_phy(nid_files(iff),o_cldncl%name,itau_w,
     1297             CALL histwrite_phy(nid_files(iff),
     1298     $clef_stations(iff),
     1299     $o_cldncl%name,itau_w,
    11161300     $            cldncl)
    11171301          ENDIF
    1118           IF (o_reffclws%flag(iff)<=lev_files(iff)) THEN
    1119              CALL histwrite_phy(nid_files(iff),o_reffclws%name,itau_w,
     1302         IF (o_reffclws%flag(iff)<=lev_files(iff)) THEN
     1303            CALL histwrite_phy(nid_files(iff),
     1304     $clef_stations(iff),
     1305     $o_reffclws%name,itau_w,
    11201306     $            reffclws)
    1121           ENDIF
    1122           IF (o_reffclwc%flag(iff)<=lev_files(iff)) THEN
    1123              CALL histwrite_phy(nid_files(iff),o_reffclwc%name,itau_w,
     1307         ENDIF
     1308         IF (o_reffclwc%flag(iff)<=lev_files(iff)) THEN
     1309            CALL histwrite_phy(nid_files(iff),
     1310     $clef_stations(iff),
     1311     $o_reffclwc%name,itau_w,
    11241312     $            reffclwc)
    1125           ENDIF
     1313         ENDIF
    11261314          IF (o_cldnvi%flag(iff)<=lev_files(iff)) THEN
    1127              CALL histwrite_phy(nid_files(iff),o_cldnvi%name,itau_w,
     1315             CALL histwrite_phy(nid_files(iff),
     1316     $clef_stations(iff),
     1317     $o_cldnvi%name,itau_w,
    11281318     $            cldnvi)
    11291319          ENDIF
    11301320          IF (o_lcc%flag(iff)<=lev_files(iff)) THEN
    1131              CALL histwrite_phy(nid_files(iff),o_lcc%name,itau_w,
     1321             CALL histwrite_phy(nid_files(iff),
     1322     $clef_stations(iff),
     1323     $o_lcc%name,itau_w,
    11321324     $            lcc)
    11331325          ENDIF
    11341326          IF (o_lcc3d%flag(iff)<=lev_files(iff)) THEN
    1135              CALL histwrite_phy(nid_files(iff),o_lcc3d%name,itau_w,
     1327             CALL histwrite_phy(nid_files(iff),
     1328     $clef_stations(iff),
     1329     $o_lcc3d%name,itau_w,
    11361330     $            lcc3d)
    11371331          ENDIF
    11381332          IF (o_lcc3dcon%flag(iff)<=lev_files(iff)) THEN
    1139              CALL histwrite_phy(nid_files(iff),o_lcc3dcon%name,itau_w,
     1333             CALL histwrite_phy(nid_files(iff),
     1334     $clef_stations(iff),
     1335     $o_lcc3dcon%name,itau_w,
    11401336     $            lcc3dcon)
    11411337          ENDIF
    11421338          IF (o_lcc3dstra%flag(iff)<=lev_files(iff)) THEN
    1143              CALL histwrite_phy(nid_files(iff),o_lcc3dstra%name,itau_w,
     1339             CALL histwrite_phy(nid_files(iff),
     1340     $clef_stations(iff),
     1341     $o_lcc3dstra%name,itau_w,
    11441342     $            lcc3dstra)
    11451343          ENDIF
    11461344          IF (o_reffclwtop%flag(iff)<=lev_files(iff)) THEN
    1147              CALL histwrite_phy(nid_files(iff),o_reffclwtop%name,itau_w,
     1345             CALL histwrite_phy(nid_files(iff),
     1346     $clef_stations(iff),
     1347     $o_reffclwtop%name,itau_w,
    11481348     $            reffclwtop)
    11491349          ENDIF
     
    11531353       IF (ok_ade .OR. ok_aie) then
    11541354          IF (o_ec550aer%flag(iff)<=lev_files(iff)) THEN
    1155              CALL histwrite_phy(nid_files(iff),o_ec550aer%name,itau_w,
     1355             CALL histwrite_phy(nid_files(iff),
     1356     $clef_stations(iff),
     1357     $o_ec550aer%name,itau_w,
    11561358     &            ec550aer)
    11571359          ENDIF
     
    11591361
    11601362       IF (o_lwcon%flag(iff)<=lev_files(iff)) THEN
    1161       CALL histwrite_phy(nid_files(iff),o_lwcon%name,itau_w,flwc)
     1363      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1364     $o_lwcon%name,itau_w,flwc)
    11621365       ENDIF
    11631366
    11641367       IF (o_iwcon%flag(iff)<=lev_files(iff)) THEN
    1165       CALL histwrite_phy(nid_files(iff),o_iwcon%name,itau_w,fiwc)
     1368      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1369     $o_iwcon%name,itau_w,fiwc)
    11661370       ENDIF
    11671371
    11681372       IF (o_temp%flag(iff)<=lev_files(iff)) THEN
    1169       CALL histwrite_phy(nid_files(iff),o_temp%name,itau_w,t_seri)
     1373      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1374     $o_temp%name,itau_w,t_seri)
    11701375       ENDIF
    11711376
    11721377       IF (o_theta%flag(iff)<=lev_files(iff)) THEN
    1173       CALL histwrite_phy(nid_files(iff),o_theta%name,itau_w,theta)
     1378      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1379     $o_theta%name,itau_w,theta)
    11741380       ENDIF
    11751381
    11761382       IF (o_ovapinit%flag(iff)<=lev_files(iff)) THEN
    1177       CALL histwrite_phy(nid_files(iff),o_ovapinit%name,itau_w,
     1383      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1384     $o_ovapinit%name,itau_w,
    11781385     $ qx(:,:,ivap))
    11791386       ENDIF
    11801387
    11811388       IF (o_ovap%flag(iff)<=lev_files(iff)) THEN
    1182       CALL histwrite_phy(nid_files(iff),
     1389      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    11831390     $                   o_ovap%name,itau_w,q_seri)
    11841391       ENDIF
    11851392
    11861393       IF (o_geop%flag(iff)<=lev_files(iff)) THEN
    1187       CALL histwrite_phy(nid_files(iff),o_geop%name,itau_w,zphi)
     1394      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1395     $o_geop%name,itau_w,zphi)
    11881396       ENDIF
    11891397
    11901398       IF (o_vitu%flag(iff)<=lev_files(iff)) THEN
    1191       CALL histwrite_phy(nid_files(iff),o_vitu%name,itau_w,u_seri)
     1399      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1400     $o_vitu%name,itau_w,u_seri)
    11921401       ENDIF
    11931402
    11941403       IF (o_vitv%flag(iff)<=lev_files(iff)) THEN
    1195       CALL histwrite_phy(nid_files(iff),o_vitv%name,itau_w,v_seri)
     1404      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1405     $o_vitv%name,itau_w,v_seri)
    11961406       ENDIF
    11971407
    11981408       IF (o_vitw%flag(iff)<=lev_files(iff)) THEN
    1199       CALL histwrite_phy(nid_files(iff),o_vitw%name,itau_w,omega)
     1409      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1410     $o_vitw%name,itau_w,omega)
    12001411       ENDIF
    12011412
    12021413        IF (o_pres%flag(iff)<=lev_files(iff)) THEN
    1203       CALL histwrite_phy(nid_files(iff),o_pres%name,itau_w,pplay)
     1414      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1415     $o_pres%name,itau_w,pplay)
    12041416        ENDIF
    12051417
    12061418        IF (o_paprs%flag(iff)<=lev_files(iff)) THEN
    1207       CALL histwrite_phy(nid_files(iff),o_paprs%name,
     1419      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1420     $o_paprs%name,
    12081421     s                    itau_w,paprs(:,1:klev))
    12091422        ENDIF
    12101423
     1424        IF (o_zfull%flag(iff)<=lev_files(iff)) THEN
     1425         DO i=1, klon
     1426          zx_tmp_fi3d1(i,1)= pphis(i)/RG
     1427!020611   zx_tmp_fi3d(i,1)= pphis(i)/RG
     1428         ENDDO
     1429         DO k=1, klev
     1430!020611        DO k=1, klev-1
     1431         DO i=1, klon
     1432!020611         zx_tmp_fi3d(i,k+1)= zx_tmp_fi3d(i,k) - (t_seri(i,k) *RD *
     1433          zx_tmp_fi3d1(i,k+1)= zx_tmp_fi3d1(i,k) - (t_seri(i,k) *RD *
     1434     $    (paprs(i,k+1) - paprs(i,k))) / ( pplay(i,k) * RG )
     1435         ENDDO
     1436         ENDDO
     1437      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1438     $o_zfull%name,itau_w,zx_tmp_fi3d1(:,2:klevp1))
     1439!020611    $o_zfull%name,itau_w,zx_tmp_fi3d)
     1440        ENDIF
     1441
     1442        IF (o_zhalf%flag(iff)<=lev_files(iff)) THEN
     1443         DO i=1, klon
     1444          zx_tmp_fi3d(i,1)= pphis(i)/RG - (
     1445     $    (t_seri(i,1)+zxtsol(i))/2. *RD *
     1446     $    (pplay(i,1) - paprs(i,1)))/( (paprs(i,1)+pplay(i,1))/2. * RG)
     1447         ENDDO
     1448         DO k=1, klev-1
     1449         DO i=1, klon
     1450          zx_tmp_fi3d(i,k+1)= zx_tmp_fi3d(i,k) - (
     1451     $    (t_seri(i,k)+t_seri(i,k+1))/2. *RD *
     1452     $    (pplay(i,k+1) - pplay(i,k))) / ( paprs(i,k) * RG )
     1453         ENDDO
     1454         ENDDO
     1455      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1456     $o_zhalf%name,itau_w,zx_tmp_fi3d)
     1457        ENDIF
     1458
    12111459       IF (o_rneb%flag(iff)<=lev_files(iff)) THEN
    1212       CALL histwrite_phy(nid_files(iff),o_rneb%name,itau_w,cldfra)
     1460      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1461     $o_rneb%name,itau_w,cldfra)
    12131462       ENDIF
    12141463
    12151464       IF (o_rnebcon%flag(iff)<=lev_files(iff)) THEN
    1216       CALL histwrite_phy(nid_files(iff),o_rnebcon%name,itau_w,rnebcon)
     1465      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1466     $o_rnebcon%name,itau_w,rnebcon)
    12171467       ENDIF
    12181468
    12191469       IF (o_rhum%flag(iff)<=lev_files(iff)) THEN
    1220       CALL histwrite_phy(nid_files(iff),o_rhum%name,itau_w,zx_rh)
     1470      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1471     $o_rhum%name,itau_w,zx_rh)
    12211472       ENDIF
    12221473
    12231474      IF (o_ozone%flag(iff)<=lev_files(iff)) THEN
    1224          CALL histwrite_phy(nid_files(iff), o_ozone%name, itau_w,
     1475         CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1476     $o_ozone%name, itau_w,
    12251477     $        wo(:, :, 1) * dobson_u * 1e3 / zmasse / rmo3 * rmd)
    12261478      ENDIF
     
    12281480      IF (o_ozone_light%flag(iff)<=lev_files(iff) .and.
    12291481     $     read_climoz == 2) THEN
    1230          CALL histwrite_phy(nid_files(iff), o_ozone_light%name, itau_w,
     1482         CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1483     $o_ozone_light%name, itau_w,
    12311484     $        wo(:, :, 2) * dobson_u * 1e3 / zmasse / rmo3 * rmd)
    12321485      ENDIF
    12331486
    12341487       IF (o_dtphy%flag(iff)<=lev_files(iff)) THEN
    1235       CALL histwrite_phy(nid_files(iff),o_dtphy%name,itau_w,d_t)
     1488      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1489     $o_dtphy%name,itau_w,d_t)
    12361490       ENDIF
    12371491
    12381492       IF (o_dqphy%flag(iff)<=lev_files(iff)) THEN
    1239       CALL histwrite_phy(nid_files(iff),
     1493      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    12401494     s                  o_dqphy%name,itau_w, d_qx(:,:,ivap))
    12411495       ENDIF
     
    12441498        IF (o_albe_srf(nsrf)%flag(iff)<=lev_files(iff)) THEN
    12451499        zx_tmp_fi2d(1 : klon) = falb1( 1 : klon, nsrf)
    1246         CALL histwrite_phy(nid_files(iff),
     1500        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    12471501     s                    o_albe_srf(nsrf)%name,itau_w,
    12481502     $                     zx_tmp_fi2d)
     
    12511505        IF (o_rugs_srf(nsrf)%flag(iff)<=lev_files(iff)) THEN 
    12521506        zx_tmp_fi2d(1 : klon) = frugs( 1 : klon, nsrf)
    1253         CALL histwrite_phy(nid_files(iff),
     1507        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    12541508     s                     o_rugs_srf(nsrf)%name,itau_w,
    12551509     $      zx_tmp_fi2d)
     
    12581512        IF (o_ages_srf(nsrf)%flag(iff)<=lev_files(iff)) THEN
    12591513        zx_tmp_fi2d(1 : klon) = agesno( 1 : klon, nsrf)
    1260         CALL histwrite_phy(nid_files(iff),
     1514        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    12611515     s                     o_ages_srf(nsrf)%name,itau_w
    12621516     $    ,zx_tmp_fi2d)
     
    12651519
    12661520       IF (o_alb1%flag(iff)<=lev_files(iff)) THEN
    1267       CALL histwrite_phy(nid_files(iff),o_alb1%name,itau_w,albsol1)
     1521      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1522     $o_alb1%name,itau_w,albsol1)
    12681523       ENDIF
    12691524
    12701525       IF (o_alb2%flag(iff)<=lev_files(iff)) THEN
    1271       CALL histwrite_phy(nid_files(iff),o_alb2%name,itau_w,albsol2)
     1526      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1527     $o_alb2%name,itau_w,albsol2)
    12721528       ENDIF
    12731529
     
    12821538      enddo
    12831539       IF (o_tke%flag(iff)<=lev_files(iff)) THEN
    1284       CALL histwrite_phy(nid_files(iff),o_tke%name,itau_w,zx_tmp_fi3d)
    1285        ENDIF
    1286 
     1540      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1541     $o_tke%name,itau_w,zx_tmp_fi3d)
     1542       ENDIF
     1543
     1544      IF (.NOT.clef_stations(iff)) THEN
    12871545       IF (o_tke_max%flag(iff)<=lev_files(iff)) THEN
    1288       CALL histwrite_phy(nid_files(iff),
     1546      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    12891547     s                   o_tke_max%name,itau_w,zx_tmp_fi3d)
    12901548       ENDIF
     1549      ENDIF
    12911550      endif
    12921551
    12931552       IF (o_kz%flag(iff)<=lev_files(iff)) THEN
    1294       CALL histwrite_phy(nid_files(iff),o_kz%name,itau_w,coefh)
    1295        ENDIF
    1296 
     1553      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1554     $o_kz%name,itau_w,coefh)
     1555       ENDIF
     1556
     1557      IF (.NOT.clef_stations(iff)) THEN
    12971558       IF (o_kz_max%flag(iff)<=lev_files(iff)) THEN
    1298       CALL histwrite_phy(nid_files(iff),o_kz_max%name,itau_w,coefh)
    1299        ENDIF
     1559      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1560     $o_kz_max%name,itau_w,coefh)
     1561       ENDIF
     1562      ENDIF
    13001563
    13011564       IF (o_clwcon%flag(iff)<=lev_files(iff)) THEN
    1302       CALL histwrite_phy(nid_files(iff),o_clwcon%name,itau_w,clwcon0)
     1565      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1566     $o_clwcon%name,itau_w,clwcon0)
    13031567       ENDIF
    13041568
    13051569       IF (o_dtdyn%flag(iff)<=lev_files(iff)) THEN
    1306       CALL histwrite_phy(nid_files(iff),o_dtdyn%name,itau_w,d_t_dyn)
     1570      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1571     $o_dtdyn%name,itau_w,d_t_dyn)
    13071572       ENDIF
    13081573
    13091574       IF (o_dqdyn%flag(iff)<=lev_files(iff)) THEN
    1310       CALL histwrite_phy(nid_files(iff),o_dqdyn%name,itau_w,d_q_dyn)
     1575      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1576     $o_dqdyn%name,itau_w,d_q_dyn)
    13111577       ENDIF
    13121578
    13131579       IF (o_dudyn%flag(iff)<=lev_files(iff)) THEN
    1314       CALL histwrite_phy(nid_files(iff),o_dudyn%name,itau_w,d_u_dyn)
     1580      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1581     $o_dudyn%name,itau_w,d_u_dyn)
    13151582       ENDIF                                                   
    13161583
    13171584       IF (o_dvdyn%flag(iff)<=lev_files(iff)) THEN                 
    1318       CALL histwrite_phy(nid_files(iff),o_dvdyn%name,itau_w,d_v_dyn) 
     1585      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1586     $o_dvdyn%name,itau_w,d_v_dyn) 
    13191587       ENDIF                                                     
    13201588
    1321        IF (o_dtcon%flag(iff)<=lev_files(iff)) THEN
     1589      IF (o_dtcon%flag(iff)<=lev_files(iff)) THEN
    13221590      zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys
    1323       CALL histwrite_phy(nid_files(iff),o_dtcon%name,itau_w,zx_tmp_fi3d)
    1324        ENDIF
     1591      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1592     $o_dtcon%name,itau_w,zx_tmp_fi3d)
     1593      ENDIF                                                     
     1594
     1595      if(iflag_thermals.eq.1)then
     1596      IF (o_tntc%flag(iff)<=lev_files(iff)) THEN
     1597      zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys +
     1598     $                           d_t_ajsb(1:klon,1:klev)/pdtphys
     1599      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1600     $o_tntc%name,itau_w,zx_tmp_fi3d)
     1601      ENDIF
     1602      else if(iflag_thermals.gt.1.and.iflag_wake.EQ.1)then
     1603      IF (o_tntc%flag(iff)<=lev_files(iff)) THEN
     1604      zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys +
     1605     $                           d_t_ajs(1:klon,1:klev)/pdtphys +
     1606     $                           d_t_wake(1:klon,1:klev)/pdtphys
     1607      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1608     $o_tntc%name,itau_w,zx_tmp_fi3d)
     1609      ENDIF
     1610      endif
    13251611
    13261612       IF (o_ducon%flag(iff)<=lev_files(iff)) THEN
    13271613      zx_tmp_fi3d(1:klon,1:klev)=d_u_con(1:klon,1:klev)/pdtphys
    1328       CALL histwrite_phy(nid_files(iff),o_ducon%name,itau_w,zx_tmp_fi3d)
     1614      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1615     $o_ducon%name,itau_w,zx_tmp_fi3d)
    13291616       ENDIF
    13301617
    13311618       IF (o_dqcon%flag(iff)<=lev_files(iff)) THEN
    13321619      zx_tmp_fi3d(1:klon,1:klev)=d_q_con(1:klon,1:klev)/pdtphys
    1333       CALL histwrite_phy(nid_files(iff),o_dqcon%name,itau_w,zx_tmp_fi3d)
    1334        ENDIF
     1620      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1621     $o_dqcon%name,itau_w,zx_tmp_fi3d)
     1622       ENDIF
     1623
     1624      if(iflag_thermals.eq.1)then
     1625       IF (o_tnhusc%flag(iff)<=lev_files(iff)) THEN
     1626      zx_tmp_fi3d(1:klon,1:klev)=d_q_con(1:klon,1:klev)/pdtphys
     1627      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1628     $o_tnhusc%name,itau_w,zx_tmp_fi3d)
     1629       ENDIF
     1630      else if(iflag_thermals.gt.1.and.iflag_wake.EQ.1)then
     1631      IF (o_tnhusc%flag(iff)<=lev_files(iff)) THEN
     1632      zx_tmp_fi3d(1:klon,1:klev)=d_q_con(1:klon,1:klev)/pdtphys +
     1633     $                           d_q_ajs(1:klon,1:klev)/pdtphys +
     1634     $                           d_q_wake(1:klon,1:klev)/pdtphys
     1635      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1636     $o_tnhusc%name,itau_w,zx_tmp_fi3d)
     1637      ENDIF
     1638      endif
    13351639
    13361640       IF (o_dtlsc%flag(iff)<=lev_files(iff)) THEN
    13371641      zx_tmp_fi3d(1:klon,1:klev)=d_t_lsc(1:klon,1:klev)/pdtphys
    1338       CALL histwrite_phy(nid_files(iff),o_dtlsc%name,itau_w,zx_tmp_fi3d)
     1642      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1643     $o_dtlsc%name,itau_w,zx_tmp_fi3d)
    13391644       ENDIF
    13401645
     
    13421647      zx_tmp_fi3d(1:klon, 1:klev)=(d_t_lsc(1:klon,1:klev)+
    13431648     $                           d_t_eva(1:klon,1:klev))/pdtphys
    1344       CALL histwrite_phy(nid_files(iff),
     1649      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    13451650     s                   o_dtlschr%name,itau_w,zx_tmp_fi3d)
    13461651       ENDIF
     
    13481653       IF (o_dqlsc%flag(iff)<=lev_files(iff)) THEN
    13491654      zx_tmp_fi3d(1:klon,1:klev)=d_q_lsc(1:klon,1:klev)/pdtphys
    1350       CALL histwrite_phy(nid_files(iff),o_dqlsc%name,itau_w,zx_tmp_fi3d)
     1655      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1656     $o_dqlsc%name,itau_w,zx_tmp_fi3d)
    13511657       ENDIF
    13521658
    13531659       IF (o_dtvdf%flag(iff)<=lev_files(iff)) THEN
    13541660      zx_tmp_fi3d(1:klon,1:klev)=d_t_vdf(1:klon,1:klev)/pdtphys
    1355       CALL histwrite_phy(nid_files(iff),o_dtvdf%name,itau_w,zx_tmp_fi3d)
     1661      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1662     $o_dtvdf%name,itau_w,zx_tmp_fi3d)
    13561663       ENDIF
    13571664
    13581665       IF (o_dqvdf%flag(iff)<=lev_files(iff)) THEN
    13591666      zx_tmp_fi3d(1:klon,1:klev)=d_q_vdf(1:klon,1:klev)/pdtphys
    1360       CALL histwrite_phy(nid_files(iff),o_dqvdf%name,itau_w,zx_tmp_fi3d)
     1667      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1668     $o_dqvdf%name,itau_w,zx_tmp_fi3d)
    13611669       ENDIF
    13621670
    13631671       IF (o_dteva%flag(iff)<=lev_files(iff)) THEN
    13641672      zx_tmp_fi3d(1:klon,1:klev)=d_t_eva(1:klon,1:klev)/pdtphys
    1365       CALL histwrite_phy(nid_files(iff),o_dteva%name,itau_w,zx_tmp_fi3d)
     1673      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1674     $o_dteva%name,itau_w,zx_tmp_fi3d)
    13661675       ENDIF
    13671676
    13681677       IF (o_dqeva%flag(iff)<=lev_files(iff)) THEN
    13691678      zx_tmp_fi3d(1:klon,1:klev)=d_q_eva(1:klon,1:klev)/pdtphys
    1370       CALL histwrite_phy(nid_files(iff),o_dqeva%name,itau_w,zx_tmp_fi3d)
     1679      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1680     $o_dqeva%name,itau_w,zx_tmp_fi3d)
    13711681       ENDIF
    13721682
     
    13741684      zpt_conv = 0.
    13751685      where (ptconv) zpt_conv = 1.
    1376       CALL histwrite_phy(nid_files(iff),o_ptconv%name,itau_w,zpt_conv)
     1686      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1687     $o_ptconv%name,itau_w,zpt_conv)
    13771688       ENDIF
    13781689
    13791690       IF (o_ratqs%flag(iff)<=lev_files(iff)) THEN
    1380       CALL histwrite_phy(nid_files(iff),o_ratqs%name,itau_w,ratqs)
     1691      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1692     $o_ratqs%name,itau_w,ratqs)
    13811693       ENDIF
    13821694
    13831695       IF (o_dtthe%flag(iff)<=lev_files(iff)) THEN
    1384       zx_tmp_fi3d(1:klon,1:klev)=d_t_ajs(1:klon,1:klev)/pdtphys
    1385       CALL histwrite_phy(nid_files(iff),o_dtthe%name,itau_w,zx_tmp_fi3d)
     1696      zx_tmp_fi3d(1:klon,1:klev)=d_t_ajs(1:klon,1:klev)/pdtphys -
     1697     $                           d_t_ajsb(1:klon,1:klev)/pdtphys
     1698      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1699     $o_dtthe%name,itau_w,zx_tmp_fi3d)
    13861700       ENDIF
    13871701
     
    13901704! Pour l instant 0 a y reflichir pour les thermiques
    13911705         zx_tmp_fi2d=0.
    1392         CALL histwrite_phy(nid_files(iff),o_ftime_th%name,
     1706        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1707     $o_ftime_th%name,
    13931708     s                     itau_w,zx_tmp_fi2d)
    13941709        ENDIF
    13951710
    13961711        IF (o_f_th%flag(iff)<=lev_files(iff)) THEN
    1397         CALL histwrite_phy(nid_files(iff),o_f_th%name,itau_w,fm_therm)
     1712        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1713     $o_f_th%name,itau_w,fm_therm)
    13981714        ENDIF
    13991715
    14001716        IF (o_e_th%flag(iff)<=lev_files(iff)) THEN
    1401         CALL histwrite_phy(nid_files(iff),o_e_th%name,itau_w,entr_therm)
     1717        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1718     $o_e_th%name,itau_w,entr_therm)
    14021719        ENDIF
    14031720
    14041721        IF (o_w_th%flag(iff)<=lev_files(iff)) THEN
    1405         CALL histwrite_phy(nid_files(iff),o_w_th%name,itau_w,zw2)
     1722        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1723     $o_w_th%name,itau_w,zw2)
    14061724        ENDIF
    14071725
    14081726        IF (o_q_th%flag(iff)<=lev_files(iff)) THEN
    1409         CALL histwrite_phy(nid_files(iff),o_q_th%name,itau_w,zqasc)
     1727        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1728     $o_q_th%name,itau_w,zqasc)
    14101729        ENDIF
    14111730
    14121731        IF (o_lambda_th%flag(iff)<=lev_files(iff)) THEN
    1413         CALL histwrite_phy(nid_files(iff),
     1732        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
    14141733     s                     o_lambda_th%name,itau_w,lambda_th)
    14151734        ENDIF
    14161735
    14171736        IF (o_a_th%flag(iff)<=lev_files(iff)) THEN
    1418         CALL histwrite_phy(nid_files(iff),o_a_th%name,itau_w,fraca)
     1737        CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1738     $o_a_th%name,itau_w,fraca)
    14191739        ENDIF
    14201740
    14211741       IF (o_d_th%flag(iff)<=lev_files(iff)) THEN
    1422        CALL histwrite_phy(nid_files(iff),o_d_th%name,itau_w,detr_therm)
    1423        ENDIF
    1424 
    1425 !IM   ENDIF !iflag_thermals
     1742       CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1743     $o_d_th%name,itau_w,detr_therm)
     1744       ENDIF
    14261745
    14271746       IF (o_f0_th%flag(iff)<=lev_files(iff)) THEN
    1428       CALL histwrite_phy(nid_files(iff),o_f0_th%name,itau_w,f0)
     1747      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1748     $o_f0_th%name,itau_w,f0)
    14291749       ENDIF
    14301750
    14311751       IF (o_f0_th%flag(iff)<=lev_files(iff)) THEN
    1432       CALL histwrite_phy(nid_files(iff),o_zmax_th%name,itau_w,zmax0)
     1752      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1753     $o_zmax_th%name,itau_w,zmax0)
    14331754       ENDIF
    14341755
    14351756       IF (o_dqthe%flag(iff)<=lev_files(iff)) THEN
    1436       zx_tmp_fi3d(1:klon,1:klev)=d_q_ajs(1:klon,1:klev)/pdtphys
    1437       CALL histwrite_phy(nid_files(iff),o_dqthe%name,itau_w,zx_tmp_fi3d)
     1757      zx_tmp_fi3d(1:klon,1:klev)=d_q_ajs(1:klon,1:klev)/pdtphys -
     1758     $                           d_q_ajsb(1:klon,1:klev)/pdtphys
     1759      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1760     $o_dqthe%name,itau_w,zx_tmp_fi3d)
    14381761       ENDIF
    14391762
     
    14421765       IF (o_dtajs%flag(iff)<=lev_files(iff)) THEN
    14431766      zx_tmp_fi3d(1:klon,1:klev)=d_t_ajsb(1:klon,1:klev)/pdtphys
    1444       CALL histwrite_phy(nid_files(iff),o_dtajs%name,itau_w,zx_tmp_fi3d)
     1767      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1768     $o_dtajs%name,itau_w,zx_tmp_fi3d)
    14451769       ENDIF
    14461770
    14471771       IF (o_dqajs%flag(iff)<=lev_files(iff)) THEN
    14481772      zx_tmp_fi3d(1:klon,1:klev)=d_q_ajsb(1:klon,1:klev)/pdtphys
    1449       CALL histwrite_phy(nid_files(iff),o_dqajs%name,itau_w,zx_tmp_fi3d)
     1773      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1774     $o_dqajs%name,itau_w,zx_tmp_fi3d)
    14501775       ENDIF
    14511776
    14521777       IF (o_dtswr%flag(iff)<=lev_files(iff)) THEN
    14531778      zx_tmp_fi3d(1:klon,1:klev)=heat(1:klon,1:klev)/RDAY
    1454       CALL histwrite_phy(nid_files(iff),o_dtswr%name,itau_w,zx_tmp_fi3d)
     1779      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1780     $o_dtswr%name,itau_w,zx_tmp_fi3d)
    14551781       ENDIF
    14561782
    14571783       IF (o_dtsw0%flag(iff)<=lev_files(iff)) THEN
    14581784      zx_tmp_fi3d(1:klon,1:klev)=heat0(1:klon,1:klev)/RDAY
    1459       CALL histwrite_phy(nid_files(iff),o_dtsw0%name,itau_w,zx_tmp_fi3d)
     1785      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1786     $o_dtsw0%name,itau_w,zx_tmp_fi3d)
    14601787       ENDIF
    14611788
    14621789       IF (o_dtlwr%flag(iff)<=lev_files(iff)) THEN
    14631790      zx_tmp_fi3d(1:klon,1:klev)=-1.*cool(1:klon,1:klev)/RDAY
    1464       CALL histwrite_phy(nid_files(iff),o_dtlwr%name,itau_w,zx_tmp_fi3d)
     1791      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1792     $o_dtlwr%name,itau_w,zx_tmp_fi3d)
    14651793       ENDIF
    14661794
    14671795       IF (o_dtlw0%flag(iff)<=lev_files(iff)) THEN
    14681796      zx_tmp_fi3d(1:klon,1:klev)=-1.*cool0(1:klon,1:klev)/RDAY
    1469       CALL histwrite_phy(nid_files(iff),o_dtlw0%name,itau_w,zx_tmp_fi3d)
     1797      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1798     $o_dtlw0%name,itau_w,zx_tmp_fi3d)
    14701799       ENDIF
    14711800
    14721801       IF (o_dtec%flag(iff)<=lev_files(iff)) THEN
    14731802      zx_tmp_fi3d(1:klon,1:klev)=d_t_ec(1:klon,1:klev)
    1474       CALL histwrite_phy(nid_files(iff),o_dtec%name,itau_w,zx_tmp_fi3d)
     1803      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1804     $o_dtec%name,itau_w,zx_tmp_fi3d)
    14751805       ENDIF
    14761806
    14771807       IF (o_duvdf%flag(iff)<=lev_files(iff)) THEN
    14781808      zx_tmp_fi3d(1:klon,1:klev)=d_u_vdf(1:klon,1:klev)/pdtphys
    1479       CALL histwrite_phy(nid_files(iff),o_duvdf%name,itau_w,zx_tmp_fi3d)
     1809      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1810     $o_duvdf%name,itau_w,zx_tmp_fi3d)
    14801811       ENDIF
    14811812
    14821813       IF (o_dvvdf%flag(iff)<=lev_files(iff)) THEN
    14831814      zx_tmp_fi3d(1:klon,1:klev)=d_v_vdf(1:klon,1:klev)/pdtphys
    1484       CALL histwrite_phy(nid_files(iff),o_dvvdf%name,itau_w,zx_tmp_fi3d)
     1815      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1816     $o_dvvdf%name,itau_w,zx_tmp_fi3d)
    14851817       ENDIF
    14861818
     
    14881820      IF (o_duoro%flag(iff)<=lev_files(iff)) THEN
    14891821      zx_tmp_fi3d(1:klon,1:klev)=d_u_oro(1:klon,1:klev)/pdtphys
    1490       CALL histwrite_phy(nid_files(iff),o_duoro%name,itau_w,zx_tmp_fi3d)
     1822      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1823     $o_duoro%name,itau_w,zx_tmp_fi3d)
    14911824       ENDIF
    14921825
    14931826      IF (o_dvoro%flag(iff)<=lev_files(iff)) THEN
    14941827      zx_tmp_fi3d(1:klon,1:klev)=d_v_oro(1:klon,1:klev)/pdtphys
    1495       CALL histwrite_phy(nid_files(iff),o_dvoro%name,itau_w,zx_tmp_fi3d)
     1828      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1829     $o_dvoro%name,itau_w,zx_tmp_fi3d)
     1830      ENDIF
     1831
     1832      IF (o_dtoro%flag(iff)<=lev_files(iff)) THEN
     1833      zx_tmp_fi3d(1:klon,1:klev)=d_t_oro(1:klon,1:klev)/pdtphys
     1834      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1835     $o_dtoro%name,itau_w,zx_tmp_fi3d)
    14961836      ENDIF
    14971837       ENDIF
     
    15001840       IF (o_dulif%flag(iff)<=lev_files(iff)) THEN
    15011841      zx_tmp_fi3d(1:klon,1:klev)=d_u_lif(1:klon,1:klev)/pdtphys
    1502       CALL histwrite_phy(nid_files(iff),o_dulif%name,itau_w,zx_tmp_fi3d)
     1842      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1843     $o_dulif%name,itau_w,zx_tmp_fi3d)
    15031844       ENDIF
    15041845
    15051846        IF (o_dvlif%flag(iff)<=lev_files(iff)) THEN
    15061847      zx_tmp_fi3d(1:klon,1:klev)=d_v_lif(1:klon,1:klev)/pdtphys
    1507       CALL histwrite_phy(nid_files(iff),o_dvlif%name,itau_w,zx_tmp_fi3d)
     1848      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1849     $o_dvlif%name,itau_w,zx_tmp_fi3d)
     1850       ENDIF
     1851
     1852        IF (o_dtlif%flag(iff)<=lev_files(iff)) THEN
     1853      zx_tmp_fi3d(1:klon,1:klev)=d_t_lif(1:klon,1:klev)/pdtphys
     1854      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1855     $o_dtlif%name,itau_w,zx_tmp_fi3d)
    15081856       ENDIF
    15091857        ENDIF
     
    15121860       IF (o_duhin%flag(iff)<=lev_files(iff)) THEN
    15131861      zx_tmp_fi3d(1:klon,1:klev)=d_u_hin(1:klon,1:klev)/pdtphys
    1514       CALL histwrite_phy(nid_files(iff),o_duhin%name,itau_w,zx_tmp_fi3d)
     1862      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1863     $o_duhin%name,itau_w,zx_tmp_fi3d)
    15151864       ENDIF
    15161865
    15171866        IF (o_dvhin%flag(iff)<=lev_files(iff)) THEN
    15181867      zx_tmp_fi3d(1:klon,1:klev)=d_v_hin(1:klon,1:klev)/pdtphys
    1519       CALL histwrite_phy(nid_files(iff),o_dvhin%name,itau_w,zx_tmp_fi3d)
    1520        ENDIF
    1521         ENDIF
     1868      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1869     $o_dvhin%name,itau_w,zx_tmp_fi3d)
     1870       ENDIF
     1871
     1872        IF (o_dthin%flag(iff)<=lev_files(iff)) THEN
     1873      zx_tmp_fi3d(1:klon,1:klev)=d_t_hin(1:klon,1:klev)/pdtphys
     1874      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1875     $o_dthin%name,itau_w,zx_tmp_fi3d)
     1876       ENDIF
     1877        ENDIF
     1878
     1879       IF (o_rsu%flag(iff)<=lev_files(iff)) THEN
     1880      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1881     $o_rsu%name,itau_w,swup)
     1882       ENDIF
     1883       IF (o_rsd%flag(iff)<=lev_files(iff)) THEN
     1884      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1885     $o_rsd%name,itau_w,swdn)
     1886       ENDIF
     1887       IF (o_rlu%flag(iff)<=lev_files(iff)) THEN
     1888      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1889     $o_rlu%name,itau_w,lwup)
     1890       ENDIF
     1891       IF (o_rld%flag(iff)<=lev_files(iff)) THEN
     1892      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1893     $o_rld%name,itau_w,lwdn)
     1894       ENDIF
     1895
     1896       IF (o_rsucs%flag(iff)<=lev_files(iff)) THEN
     1897      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1898     $o_rsucs%name,itau_w,swup0)
     1899       ENDIF
     1900       IF (o_rsdcs%flag(iff)<=lev_files(iff)) THEN
     1901      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1902     $o_rsdcs%name,itau_w,swdn0)
     1903       ENDIF
     1904       IF (o_rlucs%flag(iff)<=lev_files(iff)) THEN
     1905      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1906     $o_rlucs%name,itau_w,lwup0)
     1907       ENDIF
     1908       IF (o_rldcs%flag(iff)<=lev_files(iff)) THEN
     1909      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1910     $o_rldcs%name,itau_w,lwdn0)
     1911       ENDIF
     1912
     1913       IF (o_tnt%flag(iff)<=lev_files(iff)) THEN
     1914      zx_tmp_fi3d(1:klon,1:klev)=d_t(1:klon,1:klev)+
     1915     $d_t_dyn(1:klon,1:klev)
     1916      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1917     $o_tnt%name,itau_w,zx_tmp_fi3d)
     1918       ENDIF
     1919
     1920       IF (o_tntr%flag(iff)<=lev_files(iff)) THEN
     1921      zx_tmp_fi3d(1:klon,1:klev)=heat(1:klon,1:klev)/RDAY -
     1922     $cool(1:klon,1:klev)/RDAY
     1923      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1924     $o_tntr%name,itau_w,zx_tmp_fi3d)
     1925       ENDIF
     1926
     1927       IF (o_tntscpbl%flag(iff)<=lev_files(iff)) THEN
     1928      zx_tmp_fi3d(1:klon,1:klev)= (d_t_lsc(1:klon,1:klev)+
     1929     $                             d_t_eva(1:klon,1:klev)+
     1930     $                             d_t_vdf(1:klon,1:klev))/pdtphys
     1931      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1932     $o_tntscpbl%name,itau_w,zx_tmp_fi3d)
     1933       ENDIF
     1934
     1935       IF (o_tnhus%flag(iff)<=lev_files(iff)) THEN
     1936      zx_tmp_fi3d(1:klon,1:klev)=d_qx(1:klon,1:klev,ivap)+
     1937     $d_q_dyn(1:klon,1:klev)
     1938      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1939     $o_tnhus%name,itau_w,zx_tmp_fi3d)
     1940       ENDIF
     1941
     1942       IF (o_tnhusscpbl%flag(iff)<=lev_files(iff)) THEN
     1943      zx_tmp_fi3d(1:klon,1:klev)=d_q_lsc(1:klon,1:klev)/pdtphys+
     1944     $                           d_q_eva(1:klon,1:klev)/pdtphys
     1945      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1946     $o_tnhusscpbl%name,itau_w,zx_tmp_fi3d)
     1947       ENDIF
     1948
     1949       IF (o_evu%flag(iff)<=lev_files(iff)) THEN
     1950      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1951     $o_evu%name,itau_w,coefm)
     1952       ENDIF
     1953
     1954       IF (o_h2o%flag(iff)<=lev_files(iff)) THEN
     1955      zx_tmp_fi3d(1:klon,1:klev)=q_seri(1:klon,1:klev)+
     1956     $                           ql_seri(1:klon,1:klev)
     1957      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1958     $o_h2o%name,itau_w,zx_tmp_fi3d)
     1959       ENDIF
     1960
     1961       IF (o_mcd%flag(iff)<=lev_files(iff)) THEN
     1962      zx_tmp_fi3d(1:klon,1:klev)=-1 * (dnwd(1:klon,1:klev)+
     1963     $                                 dnwd0(1:klon,1:klev))
     1964      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1965     $o_mcd%name,itau_w,zx_tmp_fi3d)
     1966       ENDIF
     1967
     1968       IF (o_dmc%flag(iff)<=lev_files(iff)) THEN
     1969      zx_tmp_fi3d(1:klon,1:klev)=upwd(1:klon,1:klev) +
     1970     $  dnwd(1:klon,1:klev)+ dnwd0(1:klon,1:klev)
     1971      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1972     $o_dmc%name,itau_w,zx_tmp_fi3d)
     1973       ENDIF
     1974
     1975       IF (o_ref_liq%flag(iff)<=lev_files(iff)) THEN
     1976      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1977     $o_ref_liq%name,itau_w,ref_liq)
     1978       ENDIF
     1979
     1980       IF (o_ref_ice%flag(iff)<=lev_files(iff)) THEN
     1981      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1982     $o_ref_ice%name,itau_w,ref_ice)
     1983       ENDIF
     1984
     1985      if (RCO2_per.NE.RCO2_act.OR.RCH4_per.NE.RCH4_act.OR.
     1986     $ RN2O_per.NE.RN2O_act.OR.RCFC11_per.NE.RCFC11_act.OR.
     1987     $ RCFC12_per.NE.RCFC12_act) THEN
     1988
     1989       IF (o_rsut4co2%flag(iff)<=lev_files(iff)) THEN
     1990      zx_tmp_fi2d(1 : klon) = swupp ( 1 : klon, klevp1 )
     1991      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1992     $o_rsut4co2%name,itau_w,zx_tmp_fi2d)
     1993       ENDIF
     1994
     1995       IF (o_rlut4co2%flag(iff)<=lev_files(iff)) THEN
     1996      zx_tmp_fi2d(1 : klon) = lwupp ( 1 : klon, klevp1 )
     1997      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     1998     $o_rlut4co2%name,itau_w,zx_tmp_fi2d)
     1999       ENDIF
     2000
     2001       IF (o_rsutcs4co2%flag(iff)<=lev_files(iff)) THEN
     2002      zx_tmp_fi2d(1 : klon) = swup0p ( 1 : klon, klevp1 )
     2003      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     2004     $o_rsutcs4co2%name,itau_w,zx_tmp_fi2d)
     2005       ENDIF
     2006
     2007       IF (o_rlutcs4co2%flag(iff)<=lev_files(iff)) THEN
     2008      zx_tmp_fi2d(1 : klon) = lwup0p ( 1 : klon, klevp1 )
     2009      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     2010     $o_rlutcs4co2%name,itau_w,zx_tmp_fi2d)
     2011       ENDIF
     2012
     2013       IF (o_rsu4co2%flag(iff)<=lev_files(iff)) THEN
     2014      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     2015     $o_rsu4co2%name,itau_w,swupp)
     2016       ENDIF
     2017
     2018       IF (o_rlu4co2%flag(iff)<=lev_files(iff)) THEN
     2019      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     2020     $o_rlu4co2%name,itau_w,lwupp)
     2021       ENDIF
     2022
     2023       IF (o_rsucs4co2%flag(iff)<=lev_files(iff)) THEN
     2024      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     2025     $o_rsucs4co2%name,itau_w,swup0p)
     2026       ENDIF
     2027
     2028       IF (o_rlucs4co2%flag(iff)<=lev_files(iff)) THEN
     2029      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     2030     $o_rlucs4co2%name,itau_w,lwup0p)
     2031       ENDIF
     2032
     2033       IF (o_rsd4co2%flag(iff)<=lev_files(iff)) THEN
     2034      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     2035     $o_rsd4co2%name,itau_w,swdnp)
     2036       ENDIF
     2037
     2038       IF (o_rld4co2%flag(iff)<=lev_files(iff)) THEN
     2039      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     2040     $o_rld4co2%name,itau_w,lwdnp)
     2041       ENDIF
     2042
     2043       IF (o_rsdcs4co2%flag(iff)<=lev_files(iff)) THEN
     2044      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     2045     $o_rsdcs4co2%name,itau_w,swdn0p)
     2046       ENDIF
     2047
     2048       IF (o_rldcs4co2%flag(iff)<=lev_files(iff)) THEN
     2049      CALL histwrite_phy(nid_files(iff),clef_stations(iff),
     2050     $o_rldcs4co2%name,itau_w,lwdn0p)
     2051       ENDIF
     2052
     2053      endif
    15222054
    15232055        IF (nqtot.GE.3 .AND. o_trac(1)%flag(iff)<=lev_files(iff)) THEN
    15242056           CALL histwrite_phy(nid_files(iff),
     2057     $clef_stations(iff),
    15252058     s          o_trac(1)%name,itau_w,qx(:,:,3))
    15262059        ENDIF
     
    15282061        IF (nqtot.GE.4 .AND. o_trac(2)%flag(iff)<=lev_files(iff)) THEN
    15292062           CALL histwrite_phy(nid_files(iff),
     2063     $clef_stations(iff),
    15302064     s          o_trac(2)%name,itau_w,qx(:,:,4))
    15312065        ENDIF
     
    15352069      if (ok_sync) then
    15362070c$OMP MASTER
    1537         call histsync(nid_files(iff))
     2071      call histsync(nid_files(iff))
    15382072c$OMP END MASTER
    15392073      endif
  • LMDZ4/branches/LMDZ4_AR5/libf/phylmd/phys_state_var_mod.F90

    r1398 r1534  
    274274      REAL,ALLOCATABLE,SAVE :: albpla(:)
    275275!$OMP THREADPRIVATE(albpla)
     276
     277!IM ajout variables CFMIP2/CMIP5
     278      REAL,ALLOCATABLE,SAVE :: heatp(:,:), coolp(:,:)
     279!$OMP THREADPRIVATE(heatp, coolp)
     280      REAL,ALLOCATABLE,SAVE :: heat0p(:,:), cool0p(:,:)
     281!$OMP THREADPRIVATE(heat0p, cool0p)
     282      REAL,ALLOCATABLE,SAVE :: radsolp(:), topswp(:), toplwp(:)
     283!$OMP THREADPRIVATE(radsolp, topswp, toplwp)
     284      REAL,ALLOCATABLE,SAVE :: albplap(:)
     285!$OMP THREADPRIVATE(albplap)
     286      REAL,ALLOCATABLE,SAVE :: solswp(:), sollwp(:)
     287!$OMP THREADPRIVATE(solswp, sollwp)
     288      REAL,ALLOCATABLE,SAVE :: sollwdownp(:)
     289!$OMP THREADPRIVATE(sollwdownp)
     290      REAL,ALLOCATABLE,SAVE :: topsw0p(:),toplw0p(:)
     291      REAL,ALLOCATABLE,SAVE :: solsw0p(:),sollw0p(:)
     292!$OMP THREADPRIVATE(topsw0p,toplw0p,solsw0p,sollw0p)
     293      REAL,ALLOCATABLE,SAVE :: lwdn0p(:,:), lwdnp(:,:)
     294      REAL,ALLOCATABLE,SAVE :: lwup0p(:,:), lwupp(:,:)
     295!$OMP THREADPRIVATE(lwdn0p, lwdnp, lwup0p, lwupp)
     296      REAL,ALLOCATABLE,SAVE :: swdn0p(:,:), swdnp(:,:)
     297      REAL,ALLOCATABLE,SAVE :: swup0p(:,:), swupp(:,:)
     298!$OMP THREADPRIVATE(swdn0p, swdnp, swup0p, swupp)
     299
    276300! pbase : cloud base pressure
    277301! bbase : cloud base buoyancy
     
    439463      ALLOCATE(topsw0(klon),toplw0(klon),solsw0(klon),sollw0(klon))
    440464      ALLOCATE(albpla(klon))
     465!IM ajout variables CFMIP2/CMIP5
     466      ALLOCATE(heatp(klon,klev), coolp(klon,klev))
     467      ALLOCATE(heat0p(klon,klev), cool0p(klon,klev))
     468      ALLOCATE(radsolp(klon), topswp(klon), toplwp(klon))
     469      ALLOCATE(albplap(klon))
     470      ALLOCATE(solswp(klon), sollwp(klon))
     471      ALLOCATE(sollwdownp(klon))
     472      ALLOCATE(topsw0p(klon),toplw0p(klon))
     473      ALLOCATE(solsw0p(klon),sollw0p(klon))
     474      ALLOCATE(lwdn0p(klon,klevp1), lwdnp(klon,klevp1))
     475      ALLOCATE(lwup0p(klon,klevp1), lwupp(klon,klevp1))
     476      ALLOCATE(swdn0p(klon,klevp1), swdnp(klon,klevp1))
     477      ALLOCATE(swup0p(klon,klevp1), swupp(klon,klevp1))
     478
    441479      ALLOCATE(cape(klon))
    442480      ALLOCATE(pbase(klon),bbase(klon))
     
    532570      deallocate(topsw0,toplw0,solsw0,sollw0)
    533571      deallocate(albpla)
     572!IM ajout variables CFMIP2/CMIP5
     573      deallocate(heatp, coolp)
     574      deallocate(heat0p, cool0p)
     575      deallocate(radsolp, topswp, toplwp)
     576      deallocate(albplap)
     577      deallocate(solswp, sollwp)
     578      deallocate(sollwdownp)
     579      deallocate(topsw0p,toplw0p)
     580      deallocate(solsw0p,sollw0p)
     581      deallocate(lwdn0p, lwdnp)
     582      deallocate(lwup0p, lwupp)
     583      deallocate(swdn0p, swdnp)
     584      deallocate(swup0p, swupp)
    534585      deallocate(cape)
    535586      deallocate(pbase,bbase)
  • LMDZ4/branches/LMDZ4_AR5/libf/phylmd/physiq.F

    r1533 r1534  
    4242      use radlwsw_m, only: radlwsw
    4343
     44!IM stations CFMIP
     45      USE CFMIP_point_locations
    4446      IMPLICIT none
    4547c======================================================================
     
    676678cAA
    677679      REAL coefh(klon,klev)     ! coef d'echange pour phytrac, valable pour 2<=k<=klev
     680      REAL coefm(klon,klev)     ! coef d'echange pour U, V
    678681      REAL u1(klon)             ! vents dans la premiere couche U
    679682      REAL v1(klon)             ! vents dans la premiere couche V
     
    986989      REAL zx_tmp_fi2d(klon)      ! variable temporaire grille physique
    987990      REAL zx_tmp_fi3d(klon,klev) ! variable temporaire pour champs 3D
     991      REAL zx_tmp_fi3d1(klon,klev+1) !variable temporaire pour champs 3D (kelvp1)
    988992c#ifdef histNMC
    989993cym   A voir plus tard !!!!
     
    10161020      REAL ue_lay(klon,klev) ! transport zonal de l'energie a chaque niveau vert.
    10171021      REAL uq_lay(klon,klev) ! transport zonal de l'eau a chaque niveau vert.
    1018 c
    1019 cIM 280405 END
    10201022c
    10211023      INTEGER nhori, nvert, nvert1, nvert3
     
    11591161      REAL grain(1), gtsol(1), gt2m(1), gprw(1)
    11601162
     1163cIM stations CFMIP
     1164      INTEGER, SAVE :: nCFMIP
     1165c$OMP THREADPRIVATE(nCFMIP)
     1166      INTEGER, PARAMETER :: npCFMIP=120
     1167      INTEGER, ALLOCATABLE, SAVE :: tabCFMIP(:)
     1168      REAL, ALLOCATABLE, SAVE :: lonCFMIP(:), latCFMIP(:)
     1169c$OMP THREADPRIVATE(tabCFMIP, lonCFMIP, latCFMIP)
     1170      INTEGER, ALLOCATABLE, SAVE :: tabijGCM(:)
     1171      REAL, ALLOCATABLE, SAVE :: lonGCM(:), latGCM(:)
     1172c$OMP THREADPRIVATE(tabijGCM, lonGCM, latGCM)
     1173      INTEGER, ALLOCATABLE, SAVE :: iGCM(:), jGCM(:)
     1174c$OMP THREADPRIVATE(iGCM, jGCM)
     1175      logical, dimension(nfiles)            :: phys_out_filestations
     1176      logical, parameter :: lNMC=.FALSE.
     1177
     1178cIM betaCRF
     1179      REAL, SAVE :: pfree, beta_pbl, beta_free
     1180c$OMP THREADPRIVATE(pfree, beta_pbl, beta_free)
     1181      REAL, SAVE :: lon1_beta,  lon2_beta, lat1_beta, lat2_beta
     1182c$OMP THREADPRIVATE(lon1_beta,  lon2_beta, lat1_beta, lat2_beta)
     1183      LOGICAL, SAVE :: mskocean_beta
     1184c$OMP THREADPRIVATE(mskocean_beta)
     1185      REAL, dimension(klon, klev) :: beta       ! facteur sur cldtaurad et cldemirad pour evaluer les retros liees aux CRF
     1186      REAL, dimension(klon, klev) :: cldtaurad  ! epaisseur optique pour radlwsw,COSP
     1187      REAL, dimension(klon, klev) :: cldemirad  ! emissivite pour radlwsw,COSP
     1188
    11611189cIM for NMC files
    11621190      missing_val=nf90_fill_real
     
    14431471
    14441472c================================================================================
    1445 
     1473cIM stations CFMIP
     1474      nCFMIP=npCFMIP
     1475      OPEN(98,file='npCFMIP_param.data',status='old',
     1476     $          form='formatted',err=999)
     1477      READ(98,*,end=998) nCFMIP
     1478998   CONTINUE
     1479      CLOSE(98)
     1480999   CONTINUE
     1481      IF(nCFMIP.GT.npCFMIP) THEN
     1482       print*,'nCFMIP > npCFMIP : augmenter npCFMIP et recompiler'
     1483       CALL abort
     1484      else
     1485       print*,'physiq npCFMIP=',npCFMIP,'nCFMIP=',nCFMIP
     1486      ENDIF
     1487c
     1488      ALLOCATE(tabCFMIP(nCFMIP))
     1489      ALLOCATE(lonCFMIP(nCFMIP), latCFMIP(nCFMIP))
     1490      ALLOCATE(tabijGCM(nCFMIP))
     1491      ALLOCATE(lonGCM(nCFMIP), latGCM(nCFMIP))
     1492      ALLOCATE(iGCM(nCFMIP), jGCM(nCFMIP))
     1493c
     1494c lecture des nCFMIP stations CFMIP, de leur numero
     1495c et des coordonnees geographiques lonCFMIP, latCFMIP
     1496c
     1497         CALL read_CFMIP_point_locations(nCFMIP, tabCFMIP,
     1498     $lonCFMIP, latCFMIP)
     1499c
     1500c identification des
     1501c 1) coordonnees lonGCM, latGCM des points CFMIP dans la grille de LMDZ
     1502c 2) indices points tabijGCM de la grille physique 1d sur klon points
     1503c 3) indices iGCM, jGCM de la grille physique 2d
     1504c
     1505         CALL LMDZ_CFMIP_point_locations(nCFMIP, lonCFMIP, latCFMIP,
     1506     $tabijGCM, lonGCM, latGCM, iGCM, jGCM)
     1507c
    14461508         ENDIF !debut
    1447 
     1509 
    14481510           DO i=1,klon
    14491511             rugoro(i) = f_rugoro * MAX(1.0e-05, zstd(i)*zsig(i)/2.0)
     
    14831545     .                   lmt_pas
    14841546c
    1485 cIM 030306 END
    1486 
    14871547      capemaxcels = 't_max(X)'
    14881548      t2mincels = 't_min(X)'
     
    15011561
    15021562c$OMP MASTER
    1503        call phys_output_open(jjmp1,nlevSTD,clevSTD,nbteta,
    1504      &                        ctetaSTD,dtime,ok_veget,
    1505      &                        type_ocean,iflag_pbl,ok_mensuel,ok_journe,
    1506      &                        ok_hf,ok_instan,ok_LES,ok_ade,ok_aie,
    1507      &                        read_climoz, new_aod, aerosol_couple)
     1563       call phys_output_open(rlon,rlat,nCFMIP,tabijGCM,
     1564     &                       iGCM,jGCM,lonGCM,latGCM,
     1565     &                       jjmp1,nlevSTD,clevSTD,
     1566     &                       nbteta, ctetaSTD, dtime,ok_veget,
     1567     &                       type_ocean,iflag_pbl,ok_mensuel,ok_journe,
     1568     &                       ok_hf,ok_instan,ok_LES,ok_ade,ok_aie,
     1569     &                       read_climoz, phys_out_filestations,
     1570     &                       new_aod, aerosol_couple
     1571     &                        )
    15081572c$OMP END MASTER
    15091573c$OMP BARRIER
     
    15251589#endif
    15261590
    1527 cIM 250308bad guide        ecrit_hf2mth = 30*1/ecrit_hf
    15281591         ecrit_hf2mth = ecrit_mth/ecrit_hf
    15291592
     
    15381601         ecrit_reg = ecrit_reg * un_jour
    15391602         ecrit_tra = ecrit_tra * un_jour
    1540          ecrit_ISCCP = ecrit_ISCCP * un_jour
    15411603         ecrit_LES = ecrit_LES * un_jour
    15421604c
     
    15441606     .   ecrit_hf,ecrit_day,ecrit_mth,ecrit_reg,ecrit_tra,ecrit_ISCCP,
    15451607     .   ecrit_hf2mth
    1546 cIM 030306 END
    1547 
    15481608
    15491609cXXXPB Positionner date0 pour initialisation de ORCHIDEE
     
    16031663      END IF
    16041664C$omp end single
     1665c
     1666cIM betaCRF
     1667      pfree=70000. !Pa
     1668      beta_pbl=1.
     1669      beta_free=1.
     1670      lon1_beta=-180.
     1671      lon2_beta=+180.
     1672      lat1_beta=90.
     1673      lat2_beta=-90.
     1674      mskocean_beta=.FALSE.
     1675
     1676      OPEN(99,file='beta_crf.data',status='old',
     1677     $          form='formatted',err=9999)
     1678      READ(99,*,end=9998) pfree
     1679      READ(99,*,end=9998) beta_pbl
     1680      READ(99,*,end=9998) beta_free
     1681      READ(99,*,end=9998) lon1_beta
     1682      READ(99,*,end=9998) lon2_beta
     1683      READ(99,*,end=9998) lat1_beta
     1684      READ(99,*,end=9998) lat2_beta
     1685      READ(99,*,end=9998) mskocean_beta
     16869998  Continue
     1687      CLOSE(99)
     16889999  Continue
     1689      WRITE(*,*)'pfree=',pfree
     1690      WRITE(*,*)'beta_pbl=',beta_pbl
     1691      WRITE(*,*)'beta_free=',beta_free
     1692      WRITE(*,*)'lon1_beta=',lon1_beta
     1693      WRITE(*,*)'lon2_beta=',lon2_beta
     1694      WRITE(*,*)'lat1_beta=',lat1_beta
     1695      WRITE(*,*)'lat2_beta=',lat2_beta
     1696      WRITE(*,*)'mskocean_beta=',mskocean_beta
    16051697      ENDIF
    16061698!
     
    19061998     s     zxtsol,    zxfluxlat, zt2m,    qsat2m,
    19071999     s     d_t_vdf,   d_q_vdf,   d_u_vdf, d_v_vdf,
    1908      s     coefh,     slab_wfbils,               
     2000     s     coefh,     coefm,     slab_wfbils,               
    19092001     d     qsol,      zq2m,      s_pblh,  s_lcl,
    19102002     d     s_capCL,   s_oliqCL,  s_cteiCL,s_pblT,
     
    29333025         mass_solu_aero_pi(:,:) = ccm(:,:,2)
    29343026      END IF
    2935 
     3027c
    29363028      if (ok_newmicro) then
    29373029      CALL newmicro (paprs, pplay,ok_newmicro,
     
    29543046      endif
    29553047c
     3048cIM betaCRF
     3049c
     3050      cldtaurad = cldtau
     3051      cldemirad = cldemi
     3052c
     3053      if(lon1_beta.EQ.-180..AND.lon2_beta.EQ.180..AND.
     3054     $lat1_beta.EQ.90..AND.lat2_beta.EQ.-90.) THEN
     3055c
     3056c global
     3057c
     3058       DO k=1, klev
     3059       DO i=1, klon
     3060        if (pplay(i,k).GE.pfree) THEN
     3061         beta(i,k) = beta_pbl
     3062        else
     3063         beta(i,k) = beta_free
     3064        endif
     3065        if (mskocean_beta) THEN
     3066         beta(i,k) = beta(i,k) * pctsrf(i,is_oce)
     3067        endif
     3068        cldtaurad(i,k) = cldtau(i,k) * beta(i,k)
     3069        cldemirad(i,k) = cldemi(i,k) * beta(i,k)
     3070       ENDDO
     3071       ENDDO
     3072c
     3073      else
     3074c
     3075c regional
     3076c
     3077       DO k=1, klev
     3078       DO i=1,klon
     3079c
     3080        if (rlon(i).ge.lon1_beta.AND.rlon(i).le.lon2_beta.AND.
     3081     $      rlat(i).le.lat1_beta.AND.rlat(i).ge.lat2_beta) THEN
     3082         if (pplay(i,k).GE.pfree) THEN
     3083          beta(i,k) = beta_pbl
     3084         else
     3085          beta(i,k) = beta_free
     3086         endif
     3087         if (mskocean_beta) THEN
     3088          beta(i,k) = beta(i,k) * pctsrf(i,is_oce)
     3089         endif
     3090        cldtaurad(i,k) = cldtau(i,k) * beta(i,k)
     3091        cldemirad(i,k) = cldemi(i,k) * beta(i,k)
     3092        endif
     3093c
     3094       ENDDO
     3095       ENDDO
     3096c
     3097      endif
     3098c
    29563099c Appeler le rayonnement mais calculer tout d'abord l'albedo du sol.
    29573100c
     
    29823125     e        paprs, pplay,zxtsol,albsol1, albsol2, t_seri,q_seri,
    29833126     e        wo(:, :, 1),
    2984      e        cldfra, cldemi, cldtau,
     3127     e        cldfra, cldemirad, cldtaurad,
    29853128     s        heat,heat0,cool,cool0,radsol,albpla,
    29863129     s        topsw,toplw,solsw,sollw,
     
    30003143#endif
    30013144      ELSE
    3002 
     3145c
     3146cIM calcul radiatif pour le cas actuel
     3147c
     3148       RCO2 = RCO2_act
     3149       RCH4 = RCH4_act
     3150       RN2O = RN2O_act
     3151       RCFC11 = RCFC11_act
     3152       RCFC12 = RCFC12_act
     3153c
    30033154         CALL radlwsw
    30043155     e        (dist, rmu0, fract,
    30053156     e        paprs, pplay,zxtsol,albsol1, albsol2,
    30063157     e        t_seri,q_seri,wo,
    3007      e        cldfra, cldemi, cldtau,
     3158     e        cldfra, cldemirad, cldtaurad,
    30083159     e        ok_ade, ok_aie,
    30093160     e        tau_aero, piz_aero, cg_aero,
     
    30233174     o        topswcf_aero, solswcf_aero)
    30243175         
    3025 
     3176c
     3177cIM 2eme calcul radiatif pour le cas perturbe ou au moins un
     3178cIM des taux doit etre different du taux actuel
     3179cIM Par defaut on a les taux perturbes egaux aux taux actuels
     3180c
     3181       if (RCO2_per.NE.RCO2_act.OR.RCH4_per.NE.RCH4_act.OR.
     3182     $RN2O_per.NE.RN2O_act.OR.RCFC11_per.NE.RCFC11_act.OR.
     3183     $RCFC12_per.NE.RCFC12_act) THEN
     3184c
     3185       RCO2 = RCO2_per
     3186       RCH4 = RCH4_per
     3187       RN2O = RN2O_per
     3188       RCFC11 = RCFC11_per
     3189       RCFC12 = RCFC12_per
     3190c
     3191         CALL radlwsw
     3192     e        (dist, rmu0, fract,
     3193     e        paprs, pplay,zxtsol,albsol1, albsol2,
     3194     e        t_seri,q_seri,wo,
     3195     e        cldfra, cldemi, cldtau,
     3196     e        ok_ade, ok_aie,
     3197     e        tau_aero, piz_aero, cg_aero,
     3198     e        cldtaupi,new_aod,
     3199     e        zqsat, flwc, fiwc,
     3200     s        heatp,heat0p,coolp,cool0p,radsolp,albplap,
     3201     s        topswp,toplwp,solswp,sollwp,
     3202     s        sollwdownp,
     3203     s        topsw0p,toplw0p,solsw0p,sollw0p,
     3204     s        lwdn0p, lwdnp, lwup0p, lwupp,
     3205     s        swdn0p, swdnp, swup0p, swupp,
     3206     s        topswad_aerop, solswad_aerop,
     3207     s        topswai_aerop, solswai_aerop,
     3208     o        topswad0_aerop, solswad0_aerop,
     3209     o        topsw_aerop, topsw0_aerop,
     3210     o        solsw_aerop, solsw0_aerop,
     3211     o        topswcf_aerop, solswcf_aerop)
     3212       endif
     3213c
    30263214      ENDIF ! aerosol_couple
    30273215      itaprad = 0
     
    31843372c
    31853373c  ajout des tendances
    3186         CALL add_phys_tend(d_u_hin,d_v_hin,d_t_hin,dq0,dql0,'lif')
     3374        CALL add_phys_tend(d_u_hin,d_v_hin,d_t_hin,dq0,dql0,'hin')
    31873375
    31883376      ENDIF
     
    32603448     $                   prfl(:,1:klev),psfl(:,1:klev),
    32613449     $                   pmflxr(:,1:klev),pmflxs(:,1:klev),
    3262      $                   mr_ozone,cldtau, cldemi)
     3450     $                   mr_ozone,cldtaurad, cldemirad)
    32633451
    32643452!     L          calipso2D,calipso3D,cfadlidar,parasolrefl,atb,betamol,
     
    34163604      vwriteSTD(:,:,5)=vlevSTD(:,:)
    34173605      wwriteSTD(:,:,5)=wlevSTD(:,:)
     3606c
     3607cIM initialisation 6eme fichier de sortie
     3608      twriteSTD(:,:,6)=tlevSTD(:,:)
     3609      qwriteSTD(:,:,6)=qlevSTD(:,:)
     3610      rhwriteSTD(:,:,6)=rhlevSTD(:,:)
     3611      phiwriteSTD(:,:,6)=philevSTD(:,:)
     3612      uwriteSTD(:,:,6)=ulevSTD(:,:)
     3613      vwriteSTD(:,:,6)=vlevSTD(:,:)
     3614      wwriteSTD(:,:,6)=wlevSTD(:,:)
    34183615cIM for NMC files
    34193616      DO n=1, nlevSTD3
  • LMDZ4/branches/LMDZ4_AR5/libf/phylmd/phystokenc.F

    r1146 r1534  
    123123      logical,save :: first=.true.
    124124c$OMP THREADPRIVATE(first)
     125      logical, parameter :: lstokenc=.FALSE.
    125126c
    126127c   Couche limite:
     
    169170      ndex2d = 0
    170171      ndex3d = 0
    171       i=itap 
     172      i=itap
    172173cym      CALL gr_fi_ecrit(1,klon,iim,jjm+1,pphis,zx_tmp_2d)
    173       CALL histwrite_phy(physid,"phis",i,pphis)
     174      CALL histwrite_phy(physid,lstokenc,"phis",i,pphis)
    174175c
    175176      i=itap
    176177cym      CALL gr_fi_ecrit(1,klon,iim,jjm+1,paire,zx_tmp_2d)
    177       CALL histwrite_phy(physid,"aire",i,paire)
     178      CALL histwrite_phy(physid,lstokenc,"aire",i,paire)
    178179
    179180      iadvtr=iadvtr+1
     
    282283ccccc
    283284cym         CALL gr_fi_ecrit(klev,klon,iim,jjm+1, t, zx_tmp_3d)
    284          CALL histwrite_phy(physid,"t",itap,t)
     285         CALL histwrite_phy(physid,lstokenc,"t",itap,t)
    285286
    286287cym         CALL gr_fi_ecrit(klev,klon,iim,jjm+1, mfu, zx_tmp_3d)
    287       CALL histwrite_phy(physid,"mfu",itap,mfu)
     288      CALL histwrite_phy(physid,lstokenc,"mfu",itap,mfu)
    288289cym     CALL gr_fi_ecrit(klev,klon,iim,jjm+1, mfd, zx_tmp_3d)
    289       CALL histwrite_phy(physid,"mfd",itap,mfd)
     290      CALL histwrite_phy(physid,lstokenc,"mfd",itap,mfd)
    290291cym        CALL gr_fi_ecrit(klev,klon,iim,jjm+1, en_u, zx_tmp_3d)
    291       CALL histwrite_phy(physid,"en_u",itap,en_u)
     292      CALL histwrite_phy(physid,lstokenc,"en_u",itap,en_u)
    292293cym        CALL gr_fi_ecrit(klev,klon,iim,jjm+1, de_u, zx_tmp_3d)
    293       CALL histwrite_phy(physid,"de_u",itap,de_u)
     294      CALL histwrite_phy(physid,lstokenc,"de_u",itap,de_u)
    294295cym        CALL gr_fi_ecrit(klev,klon,iim,jjm+1, en_d, zx_tmp_3d)
    295       CALL histwrite_phy(physid,"en_d",itap,en_d)
     296      CALL histwrite_phy(physid,lstokenc,"en_d",itap,en_d)
    296297cym        CALL gr_fi_ecrit(klev,klon,iim,jjm+1, de_d, zx_tmp_3d)       
    297       CALL histwrite_phy(physid,"de_d",itap,de_d)
     298      CALL histwrite_phy(physid,lstokenc,"de_d",itap,de_d)
    298299cym        CALL gr_fi_ecrit(klev,klon,iim,jjm+1, coefh, zx_tmp_3d)         
    299       CALL histwrite_phy(physid,"coefh",itap,coefh)     
     300      CALL histwrite_phy(physid,lstokenc,"coefh",itap,coefh)   
    300301
    301302c ajou...
     
    307308
    308309cym      CALL gr_fi_ecrit(klev,klon,iim,jjm+1, fm_therm1, zx_tmp_3d)
    309       CALL histwrite_phy(physid,"fm_th",itap,fm_therm1)
     310      CALL histwrite_phy(physid,lstokenc,"fm_th",itap,fm_therm1)
    310311c
    311312cym      CALL gr_fi_ecrit(klev,klon,iim,jjm+1, entr_therm, zx_tmp_3d)
    312       CALL histwrite_phy(physid,"en_th",itap,entr_therm)
     313      CALL histwrite_phy(physid,lstokenc,"en_th",itap,entr_therm)
    313314cccc
    314315cym       CALL gr_fi_ecrit(klev,klon,iim,jjm+1,frac_impa,zx_tmp_3d)
    315         CALL histwrite_phy(physid,"frac_impa",itap,frac_impa)
     316        CALL histwrite_phy(physid,lstokenc,"frac_impa",itap,
     317     $frac_impa)
    316318
    317319cym        CALL gr_fi_ecrit(klev,klon,iim,jjm+1,frac_nucl,zx_tmp_3d)
    318         CALL histwrite_phy(physid,"frac_nucl",itap,frac_nucl)
     320        CALL histwrite_phy(physid,lstokenc,"frac_nucl",itap,
     321     $frac_nucl)
    319322 
    320323cym        CALL gr_fi_ecrit(1, klon,iim,jjm+1, pyu1,zx_tmp_2d)
    321       CALL histwrite_phy(physid,"pyu1",itap,pyu1)
     324      CALL histwrite_phy(physid,lstokenc,"pyu1",itap,pyu1)
    322325       
    323326cym     CALL gr_fi_ecrit(1, klon,iim,jjm+1, pyv1,zx_tmp_2d)
    324       CALL histwrite_phy(physid,"pyv1",itap,pyv1)
     327      CALL histwrite_phy(physid,lstokenc,"pyv1",itap,pyv1)
    325328       
    326329cym     CALL gr_fi_ecrit(1,klon,iim,jjm+1, pftsol1, zx_tmp_2d)
    327       CALL histwrite_phy(physid,"ftsol1",itap,pftsol1)
     330      CALL histwrite_phy(physid,lstokenc,"ftsol1",itap,pftsol1)
    328331cym         CALL gr_fi_ecrit(1,klon,iim,jjm+1, pftsol2, zx_tmp_2d)
    329       CALL histwrite_phy(physid,"ftsol2",itap,pftsol2)
     332      CALL histwrite_phy(physid,lstokenc,"ftsol2",itap,pftsol2)
    330333cym          CALL gr_fi_ecrit(1,klon,iim,jjm+1, pftsol3, zx_tmp_2d)
    331       CALL histwrite_phy(physid,"ftsol3",itap,pftsol3)
     334      CALL histwrite_phy(physid,lstokenc,"ftsol3",itap,pftsol3)
    332335cym         CALL gr_fi_ecrit(1,klon,iim,jjm+1, pftsol4, zx_tmp_2d)
    333       CALL histwrite_phy(physid,"ftsol4",itap,pftsol4)
     336      CALL histwrite_phy(physid,lstokenc,"ftsol4",itap,pftsol4)
    334337
    335338cym        CALL gr_fi_ecrit(1,klon,iim,jjm+1, ppsrf1, zx_tmp_2d)
    336       CALL histwrite_phy(physid,"psrf1",itap,ppsrf1)
     339      CALL histwrite_phy(physid,lstokenc,"psrf1",itap,ppsrf1)
    337340cym        CALL gr_fi_ecrit(1,klon,iim,jjm+1, ppsrf2, zx_tmp_2d)
    338       CALL histwrite_phy(physid,"psrf2",itap,ppsrf2)
     341      CALL histwrite_phy(physid,lstokenc,"psrf2",itap,ppsrf2)
    339342cym        CALL gr_fi_ecrit(1,klon,iim,jjm+1, ppsrf3, zx_tmp_2d)
    340       CALL histwrite_phy(physid,"psrf3",itap,ppsrf3)
     343      CALL histwrite_phy(physid,lstokenc,"psrf3",itap,ppsrf3)
    341344cym        CALL gr_fi_ecrit(1,klon,iim,jjm+1, ppsrf4, zx_tmp_2d)
    342       CALL histwrite_phy(physid,"psrf4",itap,ppsrf4)
     345      CALL histwrite_phy(physid,lstokenc,"psrf4",itap,ppsrf4)
    343346
    344347c$OMP MASTER
  • LMDZ4/branches/LMDZ4_AR5/libf/phylmd/write_histdayNMC.h

    r1374 r1534  
    1515ccc
    1616      IF(lev_histdayNMC.EQ.nlevSTD) THEN
    17        CALL histwrite_phy(nid_daynmc,"tnondef",itau_w,tnondef(:,:,2))
    18        CALL histwrite_phy(nid_daynmc,"ta",itau_w,twriteSTD(:,:,2))
    19        CALL histwrite_phy(nid_daynmc,"zg",itau_w,phiwriteSTD(:,:,2))
    20        CALL histwrite_phy(nid_daynmc,"hus",itau_w,qwriteSTD(:,:,2))
    21        CALL histwrite_phy(nid_daynmc,"hur",itau_w,rhwriteSTD(:,:,2))
    22        CALL histwrite_phy(nid_daynmc,"ua",itau_w,uwriteSTD(:,:,2))
    23        CALL histwrite_phy(nid_daynmc,"va",itau_w,vwriteSTD(:,:,2))
    24        CALL histwrite_phy(nid_daynmc,"wap",itau_w,wwriteSTD(:,:,2))
     17       CALL histwrite_phy(nid_daynmc,lNMC,"tnondef",itau_w,
     18     $tnondef(:,:,2))
     19       CALL histwrite_phy(nid_daynmc,lNMC,"ta",itau_w,
     20     $twriteSTD(:,:,2))
     21       CALL histwrite_phy(nid_daynmc,lNMC,"zg",itau_w,
     22     $phiwriteSTD(:,:,2))
     23       CALL histwrite_phy(nid_daynmc,lNMC,"hus",itau_w,
     24     $qwriteSTD(:,:,2))
     25       CALL histwrite_phy(nid_daynmc,lNMC,"hur",itau_w,
     26     $rhwriteSTD(:,:,2))
     27       CALL histwrite_phy(nid_daynmc,lNMC,"ua",itau_w,
     28     $uwriteSTD(:,:,2))
     29       CALL histwrite_phy(nid_daynmc,lNMC,"va",itau_w,
     30     $vwriteSTD(:,:,2))
     31       CALL histwrite_phy(nid_daynmc,lNMC,"wap",itau_w,
     32     $wwriteSTD(:,:,2))
    2533      ELSE IF(lev_histdayNMC.EQ.nlevSTD8) THEN
    26        CALL histwrite_phy(nid_daynmc,"tnondef",itau_w,tnondefSTD8)
    27        CALL histwrite_phy(nid_daynmc,"ta",itau_w,twriteSTD8)
    28        CALL histwrite_phy(nid_daynmc,"zg",itau_w,phiwriteSTD8)
    29        CALL histwrite_phy(nid_daynmc,"hus",itau_w,qwriteSTD8)
    30        CALL histwrite_phy(nid_daynmc,"hur",itau_w,rhwriteSTD8)
    31        CALL histwrite_phy(nid_daynmc,"ua",itau_w,uwriteSTD8)
    32        CALL histwrite_phy(nid_daynmc,"va",itau_w,vwriteSTD8)
    33        CALL histwrite_phy(nid_daynmc,"wap",itau_w,wwriteSTD8)
     34       CALL histwrite_phy(nid_daynmc,lNMC,"tnondef",itau_w,
     35     $tnondefSTD8)
     36       CALL histwrite_phy(nid_daynmc,lNMC,"ta",itau_w,
     37     $twriteSTD8)
     38       CALL histwrite_phy(nid_daynmc,lNMC,"zg",itau_w,
     39     $phiwriteSTD8)
     40       CALL histwrite_phy(nid_daynmc,lNMC,"hus",itau_w,
     41     $qwriteSTD8)
     42       CALL histwrite_phy(nid_daynmc,lNMC,"hur",itau_w,
     43     $rhwriteSTD8)
     44       CALL histwrite_phy(nid_daynmc,lNMC,"ua",itau_w,
     45     $uwriteSTD8)
     46       CALL histwrite_phy(nid_daynmc,lNMC,"va",itau_w,
     47     $vwriteSTD8)
     48       CALL histwrite_phy(nid_daynmc,lNMC,"wap",itau_w,
     49     $wwriteSTD8)
    3450      ENDIF
    3551c
  • LMDZ4/branches/LMDZ4_AR5/libf/phylmd/write_histhfNMC.h

    r1419 r1534  
    1414c nout=3 : in=pdtphys,    out=hf
    1515ccc
    16        CALL histwrite_phy(nid_hfnmc,"tnondef",itau_w,tnondef(:,:,3))
     16      CALL histwrite_phy(nid_hfnmc,lNMC,"tnondef",itau_w,
     17     $tnondef(:,:,3))
    1718c
    18        CALL histwrite_phy(nid_hfnmc,"ta",itau_w,twriteSTD3)
     19       CALL histwrite_phy(nid_hfnmc,lNMC,"ta",itau_w,
     20     $twriteSTD3)
    1921c
    20        CALL histwrite_phy(nid_hfnmc,"zg",itau_w,phiwriteSTD3)
     22       CALL histwrite_phy(nid_hfnmc,lNMC,"zg",itau_w,
     23     $phiwriteSTD3)
    2124c
    22        CALL histwrite_phy(nid_hfnmc,"hus",itau_w,qwriteSTD3)
     25       CALL histwrite_phy(nid_hfnmc,lNMC,"hus",itau_w,
     26     $qwriteSTD3)
    2327c
    24        CALL histwrite_phy(nid_hfnmc,"hur",itau_w,rhwriteSTD3)
     28       CALL histwrite_phy(nid_hfnmc,lNMC,"hur",itau_w,
     29     $rhwriteSTD3)
    2530c
    26        CALL histwrite_phy(nid_hfnmc,"ua",itau_w,uwriteSTD3)
     31       CALL histwrite_phy(nid_hfnmc,lNMC,"ua",itau_w,
     32     $uwriteSTD3)
    2733c
    28        CALL histwrite_phy(nid_hfnmc,"va",itau_w,vwriteSTD3)
     34       CALL histwrite_phy(nid_hfnmc,lNMC,"va",itau_w,
     35     $vwriteSTD3)
    2936c
    30        CALL histwrite_phy(nid_hfnmc,"wap",itau_w,wwriteSTD3)
     37       CALL histwrite_phy(nid_hfnmc,lNMC,"wap",itau_w,
     38     $wwriteSTD3)
    3139c
    3240       IF (1.EQ.0) THEN
     
    4250       ENDDO !k=1, nlevSTD
    4351c
    44        CALL histwrite_phy(nid_hfnmc,"psbg",itau_w,zx_tmp_fiNC)
     52       CALL histwrite_phy(nid_hfnmc,lNMC,"psbg",itau_w,
     53     $zx_tmp_fiNC)
    4554c
    46        CALL histwrite_phy(nid_hfnmc,"uv",itau_w,uvsumSTD(:,:,3))
     55       CALL histwrite_phy(nid_hfnmc,lNMC,"uv",itau_w,
     56     $uvsumSTD(:,:,3))
    4757c
    48        CALL histwrite_phy(nid_hfnmc,"vq",itau_w,vqsumSTD(:,:,3))
     58       CALL histwrite_phy(nid_hfnmc,lNMC,"vq",itau_w,
     59     $vqsumSTD(:,:,3))
    4960c
    50        CALL histwrite_phy(nid_hfnmc,"vT",itau_w,vTsumSTD(:,:,3))
     61       CALL histwrite_phy(nid_hfnmc,lNMC,"vT",itau_w,
     62     $vTsumSTD(:,:,3))
    5163c
    52        CALL histwrite_phy(nid_hfnmc,"wq",itau_w,wqsumSTD(:,:,3))
     64       CALL histwrite_phy(nid_hfnmc,lNMC,"wq",itau_w,
     65     $wqsumSTD(:,:,3))
    5366c
    54        CALL histwrite_phy(nid_hfnmc,"vphi",itau_w,vphisumSTD(:,:,3))
     67      CALL histwrite_phy(nid_hfnmc,lNMC,"vphi",itau_w,
     68     $vphisumSTD(:,:,3))
    5569c
    56        CALL histwrite_phy(nid_hfnmc,"wT",itau_w,wTsumSTD(:,:,3))
     70       CALL histwrite_phy(nid_hfnmc,lNMC,"wT",itau_w,
     71     $wTsumSTD(:,:,3))
    5772c
    58        CALL histwrite_phy(nid_hfnmc,"uxu",itau_w,u2sumSTD(:,:,3))
     73       CALL histwrite_phy(nid_hfnmc,lNMC,"uxu",itau_w,
     74     $u2sumSTD(:,:,3))
    5975c
    60        CALL histwrite_phy(nid_hfnmc,"vxv",itau_w,v2sumSTD(:,:,3))
     76       CALL histwrite_phy(nid_hfnmc,lNMC,"vxv",itau_w,
     77     $v2sumSTD(:,:,3))
    6178c
    62        CALL histwrite_phy(nid_hfnmc,"TxT",itau_w,T2sumSTD(:,:,3))
     79       CALL histwrite_phy(nid_hfnmc,lNMC,"TxT",itau_w,
     80     $T2sumSTD(:,:,3))
    6381c
    6482       ENDIF !(1.EQ.0) THEN
  • LMDZ4/branches/LMDZ4_AR5/libf/phylmd/write_histmthNMC.h

    r1398 r1534  
    1414c nout=3 : in=pdtphys,    out=hf
    1515ccc
    16        CALL histwrite_phy(nid_mthnmc,"tnondef",itau_w,tnondef(:,:,1))
     16      CALL histwrite_phy(nid_mthnmc,lNMC,"tnondef",itau_w,
     17     $tnondef(:,:,1))
    1718c
    18        CALL histwrite_phy(nid_mthnmc,"ta",itau_w,twriteSTD(:,:,1))
     19      CALL histwrite_phy(nid_mthnmc,lNMC,"ta",itau_w,
     20     $twriteSTD(:,:,1))
    1921c
    20        CALL histwrite_phy(nid_mthnmc,"zg",itau_w,phiwriteSTD(:,:,1))
     22      CALL histwrite_phy(nid_mthnmc,lNMC,"zg",itau_w,
     23     $phiwriteSTD(:,:,1))
    2124c
    22        CALL histwrite_phy(nid_mthnmc,"hus",itau_w,qwriteSTD(:,:,1))
     25       CALL histwrite_phy(nid_mthnmc,lNMC,"hus",itau_w,
     26     $qwriteSTD(:,:,1))
    2327c
    24        CALL histwrite_phy(nid_mthnmc,"hur",itau_w,rhwriteSTD(:,:,1))
     28       CALL histwrite_phy(nid_mthnmc,lNMC,"hur",itau_w,
     29     $rhwriteSTD(:,:,1))
    2530c
    26        CALL histwrite_phy(nid_mthnmc,"ua",itau_w,uwriteSTD(:,:,1))
     31       CALL histwrite_phy(nid_mthnmc,lNMC,"ua",itau_w,
     32     $uwriteSTD(:,:,1))
    2733c
    28        CALL histwrite_phy(nid_mthnmc,"va",itau_w,vwriteSTD(:,:,1))
     34       CALL histwrite_phy(nid_mthnmc,lNMC,"va",itau_w,
     35     $vwriteSTD(:,:,1))
    2936c
    30        CALL histwrite_phy(nid_mthnmc,"wap",itau_w,wwriteSTD(:,:,1))
     37       CALL histwrite_phy(nid_mthnmc,lNMC,"wap",itau_w,
     38     $wwriteSTD(:,:,1))
    3139c
    3240       DO k=1, nlevSTD
     
    4048       ENDDO !k=1, nlevSTD
    4149c
    42        CALL histwrite_phy(nid_mthnmc,"psbg",itau_w,zx_tmp_fiNC)
     50      CALL histwrite_phy(nid_mthnmc,lNMC,"psbg",itau_w,
     51     $zx_tmp_fiNC)
    4352c
    44        CALL histwrite_phy(nid_mthnmc,"uv",itau_w,uvsumSTD(:,:,1))
     53      CALL histwrite_phy(nid_mthnmc,lNMC,"uv",itau_w,
     54     $uvsumSTD(:,:,1))
    4555c
    46        CALL histwrite_phy(nid_mthnmc,"vq",itau_w,vqsumSTD(:,:,1))
     56      CALL histwrite_phy(nid_mthnmc,lNMC,"vq",itau_w,
     57     $vqsumSTD(:,:,1))
    4758c
    48        CALL histwrite_phy(nid_mthnmc,"vT",itau_w,vTsumSTD(:,:,1))
     59      CALL histwrite_phy(nid_mthnmc,lNMC,"vT",itau_w,
     60     $vTsumSTD(:,:,1))
    4961c
    50        CALL histwrite_phy(nid_mthnmc,"wq",itau_w,wqsumSTD(:,:,1))
     62      CALL histwrite_phy(nid_mthnmc,lNMC,"wq",itau_w,
     63     $wqsumSTD(:,:,1))
    5164c
    52        CALL histwrite_phy(nid_mthnmc,"vphi",itau_w,vphisumSTD(:,:,1))
     65      CALL histwrite_phy(nid_mthnmc,lNMC,"vphi",itau_w,
     66     $vphisumSTD(:,:,1))
    5367c
    54        CALL histwrite_phy(nid_mthnmc,"wT",itau_w,wTsumSTD(:,:,1))
     68       CALL histwrite_phy(nid_mthnmc,lNMC,"wT",itau_w,
     69     $wTsumSTD(:,:,1))
    5570c
    56        CALL histwrite_phy(nid_mthnmc,"uxu",itau_w,u2sumSTD(:,:,1))
     71       CALL histwrite_phy(nid_mthnmc,lNMC,"uxu",itau_w,
     72     $u2sumSTD(:,:,1))
    5773c
    58        CALL histwrite_phy(nid_mthnmc,"vxv",itau_w,v2sumSTD(:,:,1))
     74       CALL histwrite_phy(nid_mthnmc,lNMC,"vxv",itau_w,
     75     $v2sumSTD(:,:,1))
    5976c
    60        CALL histwrite_phy(nid_mthnmc,"TxT",itau_w,T2sumSTD(:,:,1))
     77       CALL histwrite_phy(nid_mthnmc,lNMC,"TxT",itau_w,
     78     $T2sumSTD(:,:,1))
    6179c
    6280       DO k=1, nlevSTD
     
    6987        ENDDO
    7088       ENDDO !k=1, nlevSTD
    71        CALL histwrite_phy(nid_mthnmc,"tro3",itau_w,
     89       CALL histwrite_phy(nid_mthnmc,lNMC,"tro3",itau_w,
    7290     $ zx_tmp_fiNC)
    7391c
     
    83101       ENDDO !k=1, nlevSTD
    84102c
    85         CALL histwrite_phy(nid_mthnmc,"tro3_daylight",itau_w,
    86      $  zx_tmp_fiNC)
     103        CALL histwrite_phy(nid_mthnmc,lNMC,"tro3_daylight",
     104     $itau_w, zx_tmp_fiNC)
    87105       endif
    88106c
Note: See TracChangeset for help on using the changeset viewer.