New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 1482 for trunk/NEMO/OPA_SRC – NEMO

Changeset 1482 for trunk/NEMO/OPA_SRC


Ignore:
Timestamp:
2009-07-03T17:28:06+02:00 (15 years ago)
Author:
smasson
Message:

distribution of iom_put + cleaning of LIM2 outputs, see ticket:437

Location:
trunk/NEMO/OPA_SRC
Files:
19 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/DIA/diahth.F90

    r1152 r1482  
    1515   USE phycst          ! physical constants 
    1616   USE in_out_manager  ! I/O manager 
     17   USE iom 
    1718 
    1819   IMPLICIT NONE 
     
    112113          
    113114      END DO 
     115      CALL iom_put( "thermod", hth )   ! depth of the thermocline 
    114116 
    115117 
     
    151153         END DO 
    152154      END DO 
     155      CALL iom_put( "20d", hd20 )   ! depth of the 20 isotherm 
    153156 
    154157      ! ----------------------- ! 
     
    189192         END DO 
    190193      END DO 
     194      CALL iom_put( "28d", hd28 )   ! depth of the 28 isotherm 
    191195 
    192196      ! ----------------------------------------- ! 
     
    204208                         + zmoy * ( tn(:,:,jk) + tn(:,:,jk+1) ) * fse3w(:,:,jk) * tmask(:,:,jk) 
    205209      END DO 
     210      CALL iom_put( "hc300", htc3 )   ! first 300m heaat content 
    206211 
    207212   END SUBROUTINE dia_hth 
  • trunk/NEMO/OPA_SRC/DIA/diawri.F90

    r1465 r1482  
    2828   USE iom 
    2929   USE ioipsl 
    30  
     30#if defined key_lim2 
     31   USE limwri_2  
     32#endif 
    3133   IMPLICIT NONE 
    3234   PRIVATE 
     
    7274   !!                   instantaeous ocean state and forcing fields 
    7375   !!---------------------------------------------------------------------- 
    74  
     76# if defined key_iomput 
     77   SUBROUTINE dia_wri( kt, kindic ) 
     78      !!--------------------------------------------------------------------- 
     79      !!                  ***  ROUTINE dia_wri  *** 
     80      !!                    
     81      !! ** Purpose :   Standard output of opa: dynamics and tracer fields  
     82      !!      NETCDF format is used by default  
     83      !! 
     84      !! ** Method  :  use iom_put 
     85      !! 
     86      !! History : 
     87      !!   3.2  !  05-11  (B. Lemaire) creation from old diawri 
     88      !!---------------------------------------------------------------------- 
     89      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
     90      INTEGER, INTENT( in ) ::   kindic  !  
     91      !!---------------------------------------------------------------------- 
     92      !  
     93      ! Output the initial state and forcings 
     94      IF( ninist == 1 ) THEN                        
     95         CALL dia_wri_state( 'output.init', kt ) 
     96         ninist = 0 
     97      ENDIF 
     98 
     99      CALL iom_put( "toce"   , tn        )    ! temperature 
     100      CALL iom_put( "soce"   , sn        )    ! salinity 
     101      CALL iom_put( "sst"    , tn(:,:,1) )    ! sea surface temperature 
     102      CALL iom_put( "sss"    , sn(:,:,1) )    ! sea surface salinity 
     103      CALL iom_put( "uoce"   , un        )    ! i-current       
     104      CALL iom_put( "voce"   , vn        )    ! j-current 
     105       
     106      CALL iom_put( "avt"    , avt       )    ! T vert. eddy diff. coef. 
     107      CALL iom_put( "avm"    , avmu      )    ! T vert. eddy visc. coef. 
     108      IF( lk_zdfddm ) THEN 
     109         CALL iom_put( "avs", fsavs(:,:,:) )    ! S vert. eddy diff. coef. 
     110      ENDIF 
     111 
     112   END SUBROUTINE dia_wri 
     113 
     114#else 
    75115   SUBROUTINE dia_wri( kt, kindic ) 
    76116      !!--------------------------------------------------------------------- 
     
    118158      CHARACTER (len=80) :: clname 
    119159      !!---------------------------------------------------------------------- 
    120  
     160      ! 
     161      ! Output the initial state and forcings 
     162      IF( ninist == 1 ) THEN                        
     163         CALL dia_wri_state( 'output.init', kt ) 
     164         ninist = 0 
     165      ENDIF 
     166      ! 
    121167      ! 0. Initialisation 
    122168      ! ----------------- 
     
    417463         WRITE(numout,*) '~~~~~~ ' 
    418464      ENDIF 
    419        
    420 !--------------------------------------------------------------------------- 
    421  
    422       CALL iom_put("votemper",tn) 
    423       CALL iom_put("vosaline",sn) 
    424       CALL iom_put("sosstsst",tn(:,:,1))   ! sea surface temperature 
    425       CALL iom_put("sosaline",sn(:,:,1))   ! sea surface salinity 
    426 #if defined key_dynspg_rl 
    427       CALL iom_put("sobarstf",bsfn)   ! barotropic streamfunction 
    428 #else 
    429       CALL iom_put("sossheig",sshn)   ! sea surface height 
    430 #endif 
    431  
    432       CALL iom_put("sowaflup",emp )   ! upward water flux 
    433       CALL iom_put("sowaflcd",emps)   ! c/d water flux 
    434       zw2d(:,:) = emps(:,:) * sn(:,:,1) * tmask(:,:,1) 
    435       CALL iom_put("sosalflx",zw2d)   ! c/d salt flux 
    436       CALL iom_put("sohefldo",qns + qsr )   ! total heat flux 
    437       CALL iom_put("soshfldo",qsr)   ! solar heat flux 
    438       CALL iom_put("somxl010",hmlp)   ! mixed layer depth 
    439       CALL iom_put("somixhgt",hmld)   ! turbocline depth 
    440       CALL iom_put("soicecov",fr_i)   ! ice fraction  
    441 #if ! defined key_coupled 
    442       CALL iom_put("sohefldp",qrp)   ! heat flux damping 
    443       CALL iom_put("sowafldp",erp)   ! freshwater flux damping 
    444       zw2d(:,:) = erp(:,:) * sn(:,:,1) * tmask(:,:,1) 
    445       CALL iom_put("sosafldp", zw2d)   ! salt flux damping 
    446 #endif 
    447  
    448 #if ( defined key_coupled && ! defined key_lim3 && ! defined key_lim2 )  
    449       CALL iom_put("sohefldp",qrp)   ! heat flux damping 
    450       CALL iom_put("sowafldp",erp)   ! freshwater flux damping 
    451          zw2d(:,:) = erp(:,:) * sn(:,:,1) * tmask(:,:,1) 
    452       CALL iom_put("sosafldp",zw2d)   ! salt flux damping 
    453 #endif 
    454 #if defined key_diaspr 
    455       CALL iom_put("sosurfps",gps)   ! surface pressure 
    456 #endif 
    457          zw2d(:,:) = FLOAT( nmln(:,:) ) * tmask(:,:,1) 
    458       CALL iom_put("sobowlin",zw2d)   ! ??? 
    459  
    460 #if defined key_diahth 
    461       CALL iom_put("sothedep",hth)   ! depth of the thermocline 
    462       CALL iom_put("so20chgt",hd20)   ! depth of the 20 isotherm 
    463       CALL iom_put("so28chgt",hd28)   ! depth of the 28 isotherm 
    464       CALL iom_put("sohtc300",htc3)   ! first 300m heaat content 
    465 #endif 
    466  
    467 #if defined key_coupled  
    468 #  if defined key_lim3 
    469       Must be adapted for LIM3 
    470 #  else 
    471       CALL iom_put("soicetem",tn_ice)   ! surf. ice temperature 
    472       CALL iom_put("soicealb",alb_ice)   ! ice albedo 
    473 #  endif 
    474 #endif 
    475          ! Write fields on U grid 
    476       CALL iom_put("vozocrtx",un)    ! i-current 
    477 #if defined key_diaeiv 
    478       CALL iom_put("vozoeivu",u_eiv)    ! i-eiv current 
    479 #endif 
    480       CALL iom_put("sozotaux",utau)   ! i-wind stress 
    481 #if defined key_dynspg_rl 
    482       CALL lbc_lnk( spgu, 'U', -1. ) 
    483       CALL iom_put("sozospgx",spgu)   ! i-surf. press. grad. 
    484 #endif 
    485  
    486          ! Write fields on V grid 
    487       CALL iom_put("vomecrty",vn)   ! j-current 
    488 #if defined key_diaeiv 
    489       CALL iom_put("vomeeivv",v_eiv)   ! j-eiv current 
    490 #endif 
    491       CALL iom_put("sometauy", vtau)   ! j-wind stress 
    492 #if defined key_dynspg_rl 
    493       CALL lbc_lnk( spgv, 'V', -1. ) 
    494       CALL iom_put("somespgy",spgv)   ! j-surf. pressure grad. 
    495 #endif 
    496  
    497          ! Write fields on W grid 
    498       CALL iom_put("vovecrtz",wn)    ! vert. current 
    499 #   if defined key_diaeiv 
    500       CALL iom_put("voveeivw",w_eiv)    ! vert. eiv current 
    501 #   endif 
    502       CALL iom_put("votkeavt",avt)    ! T vert. eddy diff. coef. 
    503       CALL iom_put("votkeevd",avt_evd)    ! T enhan. vert. eddy diff. coef. 
    504       CALL iom_put("votkeavm",avmu)    ! T vert. eddy visc. coef. 
    505       CALL iom_put("votkeevm",avmu_evd)    ! T enhan. vert. eddy visc. coef. 
    506 #   if defined key_zdftmx 
    507       CALL iom_put("votidavt",av_tide)    ! vert. mix. related to internal tides 
    508       CALL iom_put("voitfavt",av_tide_itf)    ! ITF vert. mix. related to internal tides 
    509 #   endif 
    510       IF( lk_zdfddm ) THEN 
    511          CALL iom_put("voddmavs",fsavs(:,:,:) )    ! S vert. eddy diff. coef. 
    512       ENDIF 
    513 #if defined key_traldf_c2d 
    514       CALL iom_put("soleahtw",ahtw)   ! lateral eddy diff. coef. 
    515 # if defined key_traldf_eiv 
    516       CALL iom_put("soleaeiw",aeiw)   ! EIV coefficient at w-point 
    517 # endif 
    518 #endif 
    519 !--------------------------------------------------------------------------- 
    520465 
    521466      ! Write fields on T grid 
     
    623568#endif 
    624569 
    625       !  Create an output files (output.abort.nc) if S < 0 or u > 20 m/s 
    626       IF( kindic < 0 )   CALL dia_wri_state( 'output.abort', kt ) 
    627  
    628570      ! 3. Close all files 
    629571      ! --------------------------------------- 
     
    636578 
    637579   END SUBROUTINE dia_wri 
    638  
     580# endif 
    639581 
    640582   SUBROUTINE dia_wri_state( cdfile_name, kt ) 
     
    736678         &          jpi, jpj, nh_i, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    737679 
     680#if defined key_lim2 
     681      CALL lim_wri_state_2( kt, id_i, nh_i ) 
     682#else 
    738683      CALL histend( id_i ) 
     684#endif 
    739685 
    740686      ! 2. Start writing data 
  • trunk/NEMO/OPA_SRC/DYN/wzvmod.F90

    r1438 r1482  
    2525   USE obc_par         ! open boundary cond. parameter 
    2626   USE obc_oce 
     27   USE iom 
    2728 
    2829   IMPLICIT NONE 
     
    165166              &                       - fse3t_b(:,:,jk) ) * tmask(:,:,jk) / z2dt 
    166167      END DO 
     168      ! 
     169      CALL iom_put( "woce", wn   )                     ! vert. current 
     170      CALL iom_put( "ssh" , sshn )                     ! sea surface height 
    167171 
    168172      !                                           !------------------------------! 
  • trunk/NEMO/OPA_SRC/IOM/iom.F90

    r1457 r1482  
    100100 
    101101      ! consistency regarding CPP keys... 
    102       CALL iom_init_chkcpp 
     102!!$      CALL iom_init_chkcpp 
    103103 
    104104      ! end file definition 
  • trunk/NEMO/OPA_SRC/LDF/ldfeiv.F90

    r1438 r1482  
    2222   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2323   USE prtctl          ! Print control 
     24   USE iom 
    2425 
    2526   IMPLICIT NONE 
     
    214215      ENDIF 
    215216 
     217      CALL iom_put( "aht2d"    , ahtw )   ! lateral eddy diffusivity 
     218      CALL iom_put( "aht2d_eiv", aeiw )   ! EIV lateral eddy diffusivity 
     219 
    216220   END SUBROUTINE ldf_eiv 
    217221 
  • trunk/NEMO/OPA_SRC/SBC/sbc_ice.F90

    r1469 r1482  
    3333# endif 
    3434 
    35    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) ::   qns_ice   !: non solar heat flux over ice  [W/m2] 
    36    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) ::   qsr_ice   !: solar heat flux over ice      [W/m2] 
    37    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) ::   qla_ice   !: latent flux over ice 
    38    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) ::   dqla_ice  !: latent sensibility over ice 
     35   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) ::   qns_ice   !: non solar heat flux over ice                         [W/m2] 
     36   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) ::   qsr_ice   !: solar heat flux over ice                             [W/m2] 
     37   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) ::   qla_ice   !: latent flux over ice                                 [W/m2] 
     38   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) ::   dqla_ice  !: latent sensibility over ice                          [W/m2/K] 
    3939   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) ::   dqns_ice  !: non solar heat flux sensibility over ice (LW+SEN+LA) [W/m2/K] 
    40    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) ::   tn_ice    !: ice surface temperature       [K] 
     40   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) ::   tn_ice    !: ice surface temperature                              [K] 
    4141   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) ::   alb_ice   !: albedo of ice 
    4242 
    4343   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   utau_ice    !: u-stress over ice (I-point for LIM2 or U,V-point for LIM3)   [N/m2] 
    4444   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   vtau_ice    !: v-stress over ice (I-point for LIM2 or U,V-point for LIM3)   [N/m2] 
    45    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   fr1_i0      !: 1st fraction of sol. rad.  which penetrate inside the ice cover 
    46    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   fr2_i0      !: 2nd fraction of sol. rad.  which penetrate inside the ice cover 
     45   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   fr1_i0      !: 1st fraction of sol. rad. which penetrate inside the ice cover 
     46   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   fr2_i0      !: 2nd fraction of sol. rad. which penetrate inside the ice cover 
    4747   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   emp_ice     !: solid freshwater budget over ice: sublivation - snow 
    4848 
  • trunk/NEMO/OPA_SRC/SBC/sbcblk_clio.F90

    r1465 r1482  
    88   !!   NEMO     2.0  !  2002-08 (C. Ethe, G. Madec) F90: Free form and module 
    99   !!            3.0  !  2008-03 (C. Talandier, G. Madec) surface module + LIM3 
     10   !!            3.2  !  2009-04 (B. Lemaire) Introduce iom_put 
     11   !!---------------------------------------------------------------------- 
     12 
    1013   !!---------------------------------------------------------------------- 
    1114   !!   sbc_blk_clio   : CLIO bulk formulation: read and update required input fields 
     
    7679   REAL(wp)  ::   zeps    = 1.e-20                ! constant values 
    7780   REAL(wp)  ::   zeps0   = 1.e-13   
    78  
     81    
     82   !! * Substitutions 
    7983#  include "vectopt_loop_substitute.h90" 
    8084   !!---------------------------------------------------------------------- 
    81    !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008)  
     85   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)  
    8286   !! $Id$  
    8387   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     
    8589 
    8690CONTAINS 
    87  
    8891 
    8992   SUBROUTINE sbc_blk_clio( kt ) 
     
    397400      emps(:,:) = emp(:,:) 
    398401      ! 
     402      CALL iom_put( "qlw_oce",   zqlw )   ! output downward longwave  heat over the ocean 
     403      CALL iom_put( "qsb_oce", - zqsb )   ! output downward sensible  heat over the ocean 
     404      CALL iom_put( "qla_oce", - zqla )   ! output downward latent    heat over the ocean 
     405      CALL iom_put( "qns_oce",   qns  )   ! output downward non solar heat over the ocean 
     406 
    399407      IF(ln_ctl) THEN 
    400408         CALL prt_ctl(tab2d_1=zqsb , clinfo1=' blk_oce_clio: zqsb   : ', tab2d_2=zqlw , clinfo2=' zqlw  : ') 
     
    544552         END DO 
    545553      END DO 
     554      CALL iom_put( 'snowpre', p_spr )   ! Snow precipitation  
    546555       
    547556      !-----------------------------------------------------------! 
  • trunk/NEMO/OPA_SRC/SBC/sbcblk_core.F90

    r1465 r1482  
    44   !! Ocean forcing:  momentum, heat and freshwater flux formulation 
    55   !!===================================================================== 
    6    !! History :  1.0   !  04-08  (U. Schweckendiek)  Original code 
    7    !!            2.0   !  05-04  (L. Brodeau, A.M. Treguier) additions:  
    8    !!                            -  new bulk routine for efficiency 
    9    !!                            -  WINDS ARE NOW ASSUMED TO BE AT T POINTS in input files !!!! 
    10    !!                            -  file names and file characteristics in namelist  
    11    !!                            -  Implement reading of 6-hourly fields    
    12    !!            3.0   !  06-06  (G. Madec) sbc rewritting 
     6   !! History :  1.0  !  2004-08  (U. Schweckendiek)  Original code 
     7   !!            2.0  !  2005-04  (L. Brodeau, A.M. Treguier) additions:  
     8   !!                           -  new bulk routine for efficiency 
     9   !!                           -  WINDS ARE NOW ASSUMED TO BE AT T POINTS in input files !!!! 
     10   !!                           -  file names and file characteristics in namelist  
     11   !!                           -  Implement reading of 6-hourly fields    
     12   !!            3.0  !  2006-06  (G. Madec) sbc rewritting    
     13   !!            3.2  !  2009-04  (B. Lemaire)  Introduce iom_put 
    1314   !!---------------------------------------------------------------------- 
    1415 
     
    6869#  include "vectopt_loop_substitute.h90" 
    6970   !!---------------------------------------------------------------------- 
    70    !!   OPA 9.0 , LOCEAN-IPSL (2006)  
     71   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)  
    7172   !! $Id$ 
    7273   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     
    190191      !!              - qns     : Non Solar heat flux over the ocean    (W/m2) 
    191192      !!              - evap    : Evaporation over the ocean            (kg/m2/s) 
    192       !!              - tprecip : Total precipitation                   (Kg/m2/s) 
    193       !!              - sprecip : Solid precipitation                   (Kg/m2/s) 
     193      !!              - emp(s)  : evaporation minus precipitation       (kg/m2/s) 
    194194      !! 
    195195      !!  ** Nota  :   sf has to be a dummy argument for AGRIF on NEC 
     
    329329      emp (:,:) = zevap(:,:) - sf(jp_prec)%fnow(:,:) * alpha_precip * tmask(:,:,1) 
    330330!CDIR COLLAPSE 
    331       emps(:,:) = zevap(:,:) - sf(jp_prec)%fnow(:,:) * alpha_precip * tmask(:,:,1) 
     331      emps(:,:) = emp(:,:) 
     332      ! 
     333      CALL iom_put( "qlw_oce",   zqlw )                 ! output downward longwave heat over the ocean 
     334      CALL iom_put( "qsb_oce", - zqsb )                 ! output downward sensible heat over the ocean 
     335      CALL iom_put( "qla_oce", - zqla )                 ! output downward latent   heat over the ocean 
     336      CALL iom_put( "qns_oce",   qns  )                 ! output downward non solar heat over the ocean 
     337      ! 
     338      IF(ln_ctl) THEN 
     339         CALL prt_ctl(tab2d_1=zqsb , clinfo1=' blk_oce_core: zqsb   : ', tab2d_2=zqlw , clinfo2=' zqlw  : ') 
     340         CALL prt_ctl(tab2d_1=zqla , clinfo1=' blk_oce_core: zqla   : ', tab2d_2=qsr  , clinfo2=' qsr   : ') 
     341         CALL prt_ctl(tab2d_1=pst  , clinfo1=' blk_oce_core: pst    : ', tab2d_2=emp  , clinfo2=' emp   : ') 
     342         CALL prt_ctl(tab2d_1=utau , clinfo1=' blk_oce_core: utau   : ', mask1=umask,   & 
     343            &         tab2d_2=vtau , clinfo2=              ' vtau  : ' , mask2=vmask ) 
     344      ENDIF 
    332345      ! 
    333346   END SUBROUTINE blk_oce_core 
     
    377390      REAL(wp) ::             zwndi_t , zwndj_t                  ! relative wind components at T-point 
    378391      REAL(wp), DIMENSION(jpi,jpj) ::   z_wnds_t                 ! wind speed ( = | U10m - U_ice | ) at T-point 
    379       REAL(wp), DIMENSION(jpi,jpj,pdim) ::   z_qlw                ! long wave heat flux over ice 
    380       REAL(wp), DIMENSION(jpi,jpj,pdim) ::   z_qsb                ! sensible  heat flux over ice 
    381       REAL(wp), DIMENSION(jpi,jpj,pdim) ::   z_dqlw               ! sensible  heat flux over ice 
    382       REAL(wp), DIMENSION(jpi,jpj,pdim) ::   z_dqsb               ! sensible  heat flux over ice 
     392      REAL(wp), DIMENSION(jpi,jpj,pdim) ::   z_qlw               ! long wave heat flux over ice 
     393      REAL(wp), DIMENSION(jpi,jpj,pdim) ::   z_qsb               ! sensible  heat flux over ice 
     394      REAL(wp), DIMENSION(jpi,jpj,pdim) ::   z_dqlw              ! long wave heat sensitivity over ice 
     395      REAL(wp), DIMENSION(jpi,jpj,pdim) ::   z_dqsb              ! sensible  heat sensitivity over ice 
    383396      !!--------------------------------------------------------------------- 
    384397 
     
    523536!CDIR COLLAPSE 
    524537      p_spr(:,:) = sf(jp_snow)%fnow(:,:) * alpha_precip      ! solid precipitation [kg/m2/s] 
     538      CALL iom_put( 'snowpre', p_spr )                       ! Snow precipitation  
    525539      ! 
    526540      IF(ln_ctl) THEN 
     
    680694      !!   9.0  !  06-12  (L. Brodeau) Original code for 2Z 
    681695      !!---------------------------------------------------------------------- 
    682       !! * Arguments 
    683696      REAL(wp), INTENT(in)   :: & 
    684697         zt,      &     ! height for T_zt and q_zt                   [m] 
  • trunk/NEMO/OPA_SRC/SBC/sbccpl.F90

    r1472 r1482  
    933933      END SELECT 
    934934      psprecip(:,:) = - pemp_ice(:,:) 
     935      CALL iom_put( 'snowpre', psprecip )     ! Snow precipitation  
    935936      !    
    936937      !                                                           ! runoffs and calving (put in emp_tot) 
  • trunk/NEMO/OPA_SRC/SBC/sbcice_lim_2.F90

    r1481 r1482  
    157157         END SELECT 
    158158 
     159         CALL iom_put( 'utau_ice', utau_ice )     ! Wind stress over ice along i-axis at I-point 
     160         CALL iom_put( 'vtau_ice', vtau_ice )     ! Wind stress over ice along j-axis at I-point 
     161 
    159162         IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    160163            CALL prt_ctl_info( 'Ice Forcings ' ) 
     
    189192         IF( ( MOD( kt+nn_fsbc-1, ninfo ) == 0 .OR. ntmoy == 1 ) .AND. .NOT. lk_mpp )   & 
    190193            &                           CALL lim_dia_2      ( kt )      ! Ice Diagnostics 
     194# if ! defined key_iomput 
    191195                                        CALL lim_wri_2      ( kt )      ! Ice outputs 
     196# endif 
    192197         IF( lrst_ice )                 CALL lim_rst_write_2( kt )      ! Ice restart file 
    193198         ! 
  • trunk/NEMO/OPA_SRC/SBC/sbcmod.F90

    r1465 r1482  
    189189 
    190190      IF( kt == nit000 )   CALL sbc_init         ! Read namsbc namelist : surface module 
    191  
     191      ! 
     192      CALL iom_setkt( kt + nn_fsbc - 1 )         !  in sbc, iom_put is called every nn_fsbc time step 
     193      ! 
    192194      ! ocean to sbc mean sea surface variables (ss._m) 
    193195      ! --------------------------------------- 
     
    238240      !                                                         ! (update freshwater fluxes) 
    239241      ! 
     242      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN 
     243         CALL iom_put( "emp"    , emp       )                   ! upward water flux 
     244         CALL iom_put( "emps"   , emps      )                   ! c/d water flux 
     245         CALL iom_put( "qns+qsr", qns + qsr )                   ! total heat flux   (caution if ln_dm2dc=true, to be  
     246         CALL iom_put( "qns"    , qns       )                   ! solar heat flux    moved after the call to iom_setkt) 
     247         CALL iom_put( "qsr"    ,       qsr )                   ! solar heat flux    moved after the call to iom_setkt) 
     248         IF(  nn_ice > 0 )   CALL iom_put( "ice_cover", fr_i )  ! ice fraction  
     249      ENDIF 
     250      ! 
     251      CALL iom_setkt( kt )           ! iom_put outside of sbc is called at every time step 
     252      ! 
     253      CALL iom_put( "utau", utau )   ! i-wind stress   (stress can be updated at  
     254      CALL iom_put( "vtau", vtau )   ! j-wind stress    each time step in sea-ice) 
     255      ! 
    240256      IF(ln_ctl) THEN         ! print mean trends (used for debugging) 
    241257         CALL prt_ctl(tab2d_1=fr_i   , clinfo1=' fr_i - : ', mask1=tmask, ovlap=1 ) 
  • trunk/NEMO/OPA_SRC/SBC/sbcrnf.F90

    r1303 r1482  
    44   !! Ocean forcing:  river runoff 
    55   !!===================================================================== 
    6    !! History :       !  00-11  (R. Hordoir, E. Durand)  NetCDF FORMAT 
    7    !!            8.5  !  02-09  (G. Madec)  F90: Free form and module 
    8    !!            9.0  !  06-07  (G. Madec)  Surface module  
     6   !! History :  OPA  !  2000-11  (R. Hordoir, E. Durand)  NetCDF FORMAT 
     7   !!   NEMO     1.0  !  2002-09  (G. Madec)  F90: Free form and module 
     8   !!            3.0  !  2006-07  (G. Madec)  Surface module  
     9   !!            3.2  !  2009-04  (B. Lemaire)  Introduce iom_put 
    910   !!---------------------------------------------------------------------- 
    1011 
     
    2829   PUBLIC sbc_rnf          ! routine call in step module 
    2930 
    30    !! * namsbc_rnf namelist 
     31   !                                                     !!* namsbc_rnf namelist * 
    3132   CHARACTER(len=100), PUBLIC ::   cn_dir       = './'    !: Root directory for location of ssr files 
    3233   LOGICAL           , PUBLIC ::   ln_rnf_emp   = .false. !: runoffs into a file to be read or already into precipitation 
     
    4445 
    4546   !!---------------------------------------------------------------------- 
    46    !!   OPA 9.0 , LOCEAN-IPSL (2006)  
     47   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)  
    4748   !! $Id$ 
    4849   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     
    6465      !!---------------------------------------------------------------------- 
    6566      INTEGER, INTENT(in) ::   kt          ! ocean time step 
    66       ! 
     67      !! 
    6768      INTEGER  ::   ji, jj   ! dummy loop indices 
    6869      INTEGER  ::   ierror   ! temporary integer 
     
    103104            emp (:,:) = emp (:,:) - ABS( sf_rnf(1)%fnow(:,:) ) 
    104105            emps(:,:) = emps(:,:) - ABS( sf_rnf(1)%fnow(:,:) ) 
     106            CALL iom_put( "runoffs", sf_rnf(1)%fnow )         ! runoffs 
    105107         ENDIF 
    106108         ! 
  • trunk/NEMO/OPA_SRC/SBC/sbcssr.F90

    r1294 r1482  
    55   !!                   toward observed SST/SSS 
    66   !!====================================================================== 
    7    !! History :  9.0   !  06-06  (G. Madec)  Original code 
     7   !! History :  1.0  !  2006-06  (G. Madec)  Original code 
     8   !!            3.2  !  2009-04  (B. Lemaire)  Introduce iom_put 
    89   !!---------------------------------------------------------------------- 
    910 
     
    2829   PUBLIC   sbc_ssr    ! routine called in sbcmod 
    2930    
    30    REAL(wp), ALLOCATABLE, DIMENSION(:)   ::   buffer   ! Temporary buffer for exchange 
     31   REAL(wp), ALLOCATABLE, DIMENSION(:)  ::   buffer   ! Temporary buffer for exchange 
    3132 
    3233   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_sst   ! structure of input SST (file informations, fields read) 
    3334   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_sss   ! structure of input SSS (file informations, fields read) 
    3435 
    35    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   erp       !: evaporation damping                          [kg/m2/s] 
    36    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qrp       !: heat flux damping                            [w/m2] 
    37  
    38    !! * Namelist namsbc_ssr 
     36   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   erp      !: evaporation damping                          [kg/m2/s] 
     37   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qrp      !: heat flux damping                            [w/m2] 
     38 
     39   !                               !!* Namelist namsbc_ssr * 
    3940   INTEGER ::   nn_sstr, nn_sssr   ! SST/SSS indicator 
    4041   REAL(wp) ::  dqdt   , deds      ! restoring term factor 
     
    4344#  include "domzgr_substitute.h90" 
    4445   !!---------------------------------------------------------------------- 
    45    !!   OPA 9.0 , LOCEAN-IPSL (2006)  
     46   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)  
    4647   !! $Id$ 
    4748   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     
    159160                  END DO 
    160161               END DO 
     162               CALL iom_put( "qrp", qrp )                             ! heat flux damping 
    161163            ENDIF 
    162164            ! 
     
    174176                  END DO 
    175177               END DO 
     178               CALL iom_put( "erp", erp )                             ! freshwater flux damping 
    176179            ELSEIF( nn_sssr == 2 ) THEN               ! Salinity damping term (volume flux, emp and emps) 
    177180!CDIR COLLAPSE 
     
    188191                  END DO 
    189192               END DO 
     193               CALL iom_put( "erp", erp )                             ! freshwater flux damping 
    190194            ENDIF 
    191195            ! 
     
    193197         ! 
    194198      ENDIF 
    195  
    196       !!gm ... to be written                     ! Output sbc fields (using IOM) 
    197       ! prevoir comment obtenir l info sst sss ssr 
    198199      ! 
    199200   END SUBROUTINE sbc_ssr 
  • trunk/NEMO/OPA_SRC/TRA/traadv.F90

    r1152 r1482  
    44   !! Ocean active tracers:  advection trend  
    55   !!============================================================================== 
    6    !! History :  9.0  !  05-11  (G. Madec)  Original code 
     6   !! History :  2.0  !  05-11  (G. Madec)  Original code 
    77   !!---------------------------------------------------------------------- 
    88 
     
    2424   USE in_out_manager  ! I/O manager 
    2525   USE prtctl          ! Print control 
     26   USE iom 
    2627 
    2728   IMPLICIT NONE 
     
    4445#  include "vectopt_loop_substitute.h90" 
    4546   !!---------------------------------------------------------------------- 
    46    !!   OPA 9.0 , LOCEAN-IPSL (2006)  
     47   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)  
    4748   !! $Id$  
    4849   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     
    114115            &                        tab3d_2=sa, clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
    115116      END SELECT 
     117        
     118      CALL iom_put( "uoce_eff", zun )   ! effective i-current       
     119      CALL iom_put( "voce_eff", zvn )   ! effective j-current 
     120      CALL iom_put( "woce_eff", zwn )   ! effective vert. current 
     121 
    116122      !                                              ! print mean trends (used for debugging) 
    117123      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ta, clinfo1=' adv  - Ta: ', mask1=tmask,               & 
  • trunk/NEMO/OPA_SRC/TRA/traadv_eiv.F90

    r1152 r1482  
    2020   USE ldfslp          ! iso-neutral slopes 
    2121   USE in_out_manager  ! I/O manager 
     22   USE iom 
    2223 
    2324   IMPLICIT NONE 
     
    129130      END DO                                        !    End of slab   
    130131      !                                             ! ================= 
    131    END SUBROUTINE tra_adv_eiv 
     132 
     133# if defined key_diaeiv 
     134      CALL iom_put( "uoce_eiv", u_eiv )    ! i-eiv current 
     135      CALL iom_put( "voce_eiv", v_eiv )    ! j-eiv current 
     136      CALL iom_put( "woce_eiv", w_eiv )    ! vert. eiv current 
     137# endif   
     138      !  
     139    END SUBROUTINE tra_adv_eiv 
    132140 
    133141#else 
  • trunk/NEMO/OPA_SRC/TRA/trabbl_adv.h90

    r1152 r1482  
    5151      USE eosbn2                      ! equation of state 
    5252      USE oce, ONLY :   ztrdt => ua   ! use ua as 3D workspace    
    53       USE oce, ONLY :   ztrds => va   ! use va as 3D workspace    
     53      USE oce, ONLY :   ztrds => va   ! use va as 3D workspace  
     54      USE iom                            
    5455      !! 
    5556      INTEGER, INTENT( in ) ::   kt   ! ocean time-step  
     
    444445      ! Boundary condition on w_bbl   (unchanged sign) 
    445446      CALL lbc_lnk( w_bbl, 'W', 1. ) 
     447 
     448      CALL iom_put( "uoce_bbl", u_bbl )   ! bbl i-current       
     449      CALL iom_put( "voce_bbl", v_bbl )   ! bbl j-current 
     450      CALL iom_put( "woce_bbl", w_bbl )   ! bbl vert. current 
    446451      ! 
    447452   END SUBROUTINE tra_bbl_adv 
  • trunk/NEMO/OPA_SRC/ZDF/zdfevd.F90

    r1438 r1482  
    2020   USE zdfkpp          ! KPP vertical mixing 
    2121   USE in_out_manager  ! I/O manager 
     22   USE iom             ! for iom_put 
    2223   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2324 
     
    132133 
    133134      ! update of avt_evd and avmu_evd 
    134       avt_evd (:,:,:) = avt (:,:,:)  - avt_evd (:,:,:)  
    135       avmu_evd(:,:,:) = avmu(:,:,:)  - avmu_evd(:,:,:)  
     135      avt_evd (:,:,:) = avt (:,:,:) - avt_evd (:,:,:)  
     136      avmu_evd(:,:,:) = avmu(:,:,:) - avmu_evd(:,:,:)  
     137      CALL iom_put( "avt_evd", avt_evd  )    ! T enhan. vert. eddy diff. coef. 
     138      CALL iom_put( "avm_evd", avmu_evd )    ! T enhan. vert. eddy visc. coef. 
    136139 
    137140   END SUBROUTINE zdf_evd 
  • trunk/NEMO/OPA_SRC/ZDF/zdfmxl.F90

    r1152 r1482  
    1515   USE in_out_manager  ! I/O manager 
    1616   USE prtctl          ! Print control 
     17   USE iom 
    1718 
    1819   IMPLICIT NONE 
     
    101102         END DO 
    102103      END DO 
     104      CALL iom_put( "mldturb", hmld )   ! turbocline depth 
    103105 
    104106!!gm idea 
     
    136138         END DO 
    137139      END DO 
    138  
     140      CALL iom_put( "mld010", hmlp )   ! mixed layer depth 
     141       
    139142      IF(ln_ctl)   CALL prt_ctl( tab2d_1=REAL(nmln,wp), clinfo1=' nmln : ', tab2d_2=hmld, clinfo2=' hmld : ', ovlap=1 ) 
    140143 
  • trunk/NEMO/OPA_SRC/step.F90

    r1481 r1482  
    190190      IF( lk_bdy     )   CALL bdy_dta( kstp )         ! update dynamic and tracer data at unstructured open boundary 
    191191 
    192       IF( ninist == 1 ) THEN                       ! Output the initial state and forcings 
    193                         CALL dia_wri_state( 'output.init', kstp ) 
    194                         ninist = 0 
    195       ENDIF 
    196  
    197192      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    198193      !                Ocean dynamics : ssh, wn, hdiv, rot                   ! 
     
    260255      IF( lk_traldf_eiv )   CALL ldf_eiv( kstp )                 ! eddy induced velocity coefficient 
    261256#  endif 
     257 
     258      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     259      ! diagnostics and outputs 
     260      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     261                         CALL dia_wri( kstp, indic )         ! ocean model: outputs 
     262      IF( lk_floats  )   CALL flo_stp( kstp )                ! drifting Floats 
     263      IF( lk_diaspr  )   CALL dia_spr( kstp )                ! Surface pressure diagnostics 
     264      IF( lk_diahth  )   CALL dia_hth( kstp )                ! Thermocline depth (20 degres isotherm depth) 
     265      IF( lk_diagap  )   CALL dia_gap( kstp )                ! basin averaged diagnostics 
     266      IF( lk_diahdy  )   CALL dia_hdy( kstp )                ! dynamical heigh diagnostics 
     267      IF( lk_diafwb  )   CALL dia_fwb( kstp )                ! Fresh water budget diagnostics 
     268      IF( ln_diaptr  )   CALL dia_ptr( kstp )                ! Poleward TRansports diagnostics 
    262269 
    263270#if defined key_top 
     
    337344      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    338345                                 CALL stp_ctl( kstp, indic ) 
    339       IF( indic < 0          )   CALL ctl_stop( 'step: indic < 0' ) 
     346      IF( indic < 0          )   THEN 
     347                                 CALL ctl_stop( 'step: indic < 0' ) 
     348                                 CALL dia_wri_state( 'output.abort', kstp ) 
     349      ENDIF 
    340350      IF( kstp == nit000     )   CALL iom_close( numror )             ! close input  ocean restart file 
    341351      IF( lrst_oce           )   CALL rst_write    ( kstp )           ! write output ocean restart file 
     
    343353 
    344354      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    345       ! diagnostics and outputs 
     355      ! Trends 
    346356      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    347357      ! N.B. ua, va, ta, sa arrays are used as workspace in this section 
     
    349359 
    350360      IF( nstop == 0 ) THEN                                 ! Diagnostics: 
    351          IF( lk_floats  )   CALL flo_stp( kstp )                 ! drifting Floats 
    352361         IF( lk_trddyn  )   CALL trd_dwr( kstp )                 ! trends: dynamics  
    353362         IF( lk_trdtra  )   CALL trd_twr( kstp )                 ! trends: active tracers 
    354363         IF( lk_trdmld  )   CALL trd_mld( kstp )                 ! trends: Mixed-layer  
    355364         IF( lk_trdvor  )   CALL trd_vor( kstp )                 ! trends: vorticity budget 
    356          IF( lk_diaspr  )   CALL dia_spr( kstp )                 ! Surface pressure diagnostics 
    357          IF( lk_diahth  )   CALL dia_hth( kstp )                 ! Thermocline depth (20 degres isotherm depth) 
    358          IF( lk_diagap  )   CALL dia_gap( kstp )                 ! basin averaged diagnostics 
    359          IF( lk_diahdy  )   CALL dia_hdy( kstp )                 ! dynamical heigh diagnostics 
    360          IF( lk_diafwb  )   CALL dia_fwb( kstp )                 ! Fresh water budget diagnostics 
    361          IF( ln_diaptr  )   CALL dia_ptr( kstp )                 ! Poleward TRansports diagnostics 
    362          !                                                 ! outputs 
    363                             CALL dia_wri( kstp, indic )          ! ocean model: outputs 
    364365      ENDIF 
    365366 
Note: See TracChangeset for help on using the changeset viewer.