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 2128 for branches/devukmo2010/NEMO/OPA_SRC/DIA – NEMO

Ignore:
Timestamp:
2010-09-28T14:29:51+02:00 (14 years ago)
Author:
rfurner
Message:

merged branches OBS, ASM, Rivers, BDY & mixed_dynldf ready for vn3.3 merge

Location:
branches/devukmo2010/NEMO/OPA_SRC/DIA
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • branches/devukmo2010/NEMO/OPA_SRC/DIA/diafwb.F90

    r1581 r2128  
    3030   LOGICAL, PUBLIC, PARAMETER ::   lk_diafwb = .TRUE.    !: fresh water budget flag 
    3131 
    32    REAL(wp)               ::   a_emp ,          & 
     32   REAL(wp)               ::   a_fwf ,          & 
    3333      &                        a_sshb, a_sshn, a_salb, a_saln 
    3434   REAL(wp), DIMENSION(4) ::   a_flxi, a_flxo, a_temi, a_temo, a_sali, a_salo 
     
    5959      REAL(wp) ::  ztemi(4), ztemo(4), zsali(4), zsalo(4), zflxi(4), zflxo(4) 
    6060      REAL(wp) ::  zt, zs, zu   
    61       REAL(wp) ::  zsm0, zempnew 
     61      REAL(wp) ::  zsm0, zfwfnew 
    6262      !!---------------------------------------------------------------------- 
    6363 
     
    6565      zsm0 = 34.72654 
    6666 
    67       ! To compute emp mean value mean emp 
     67      ! To compute fwf mean value mean fwf 
    6868 
    6969      IF( kt == nit000 ) THEN 
    7070 
    71          a_emp    = 0.e0 
     71         a_fwf    = 0.e0 
    7272         a_sshb   = 0.e0 ! valeur de ssh au debut de la simulation 
    7373         a_salb   = 0.e0 ! valeur de sal au debut de la simulation 
     
    8787      ENDIF 
    8888       
    89       a_emp    = SUM( e1t(:,:) * e2t(:,:) * emp   (:,:) * tmask_i(:,:) ) 
    90       IF( lk_mpp )   CALL mpp_sum( a_emp    )       ! sum over the global domain 
     89      a_fwf    = SUM( e1t(:,:) * e2t(:,:) * ( emp(:,:)-rnf(:,:) ) * tmask_i(:,:) )  
     90      IF( lk_mpp )   CALL mpp_sum( a_fwf    )       ! sum over the global domain 
    9191 
    9292      IF( kt == nitend ) THEN 
     
    9595         zarea = 0.e0 
    9696         zvol  = 0.e0 
    97          zempnew = 0.e0 
     97         zfwfnew = 0.e0 
    9898         ! Mean sea level at nitend 
    9999         a_sshn = SUM( e1t(:,:) * e2t(:,:) * sshn(:,:) * tmask_i(:,:) ) 
     
    115115          
    116116         ! Conversion in m3 
    117          a_emp    = a_emp * rdttra(1) * 1.e-3  
     117         a_fwf    = a_fwf * rdttra(1) * 1.e-3  
    118118          
    119          ! emp correction to bring back the mean ssh to zero 
    120          zempnew = a_sshn / ( ( nitend - nit000 + 1 ) * rdt ) * 1.e3 / zarea 
     119         ! fwf correction to bring back the mean ssh to zero 
     120         zfwfnew = a_sshn / ( ( nitend - nit000 + 1 ) * rdt ) * 1.e3 / zarea 
    121121 
    122122      ENDIF 
     
    362362         WRITE(inum,*) 
    363363         WRITE(inum,*)    'Net freshwater budget ' 
    364          WRITE(inum,9010) '  emp    = ',a_emp,   ' m3 =', a_emp   /(FLOAT(nitend-nit000+1)*rdttra(1)) * 1.e-6,' Sv' 
     364         WRITE(inum,9010) '  fwf    = ',a_fwf,   ' m3 =', a_fwf   /(FLOAT(nitend-nit000+1)*rdttra(1)) * 1.e-6,' Sv' 
    365365         WRITE(inum,*) 
    366366         WRITE(inum,9010) '  zarea =',zarea 
  • branches/devukmo2010/NEMO/OPA_SRC/DIA/diawri.F90

    r1792 r2128  
    346346!!$            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    347347!!$#endif 
    348          CALL histdef( nid_T, "sowaflup", "Net Upward Water Flux"              , "Kg/m2/s",   &  ! emp 
     348         CALL histdef( nid_T, "sowaflup", "Net Upward Water Flux"              , "Kg/m2/s",   &  ! (emp-rnf) 
    349349            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    350350!!$         CALL histdef( nid_T, "sorunoff", "Runoffs"                            , "Kg/m2/s",   &  ! runoffs 
    351351!!$            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    352          CALL histdef( nid_T, "sowaflcd", "concentration/dilution water flux"  , "kg/m2/s",   &  ! emps 
    353             &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    354          CALL histdef( nid_T, "sosalflx", "Surface Salt Flux"                  , "Kg/m2/s",   &  ! emps * sn 
     352         CALL histdef( nid_T, "sowaflcd", "concentration/dilution water flux"  , "kg/m2/s",   &  ! (emps-rnf) 
     353            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     354         CALL histdef( nid_T, "sosalflx", "Surface Salt Flux"                  , "Kg/m2/s",   &  ! (emps-rnf) * sn 
    355355            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
    356356         CALL histdef( nid_T, "sohefldo", "Net Downward Heat Flux"             , "W/m2"   ,   &  ! qns + qsr 
     
    498498!!$      CALL histwrite( nid_T, "sowaflep", it, fmass(:,:)    , ndim_hT, ndex_hT )   ! atmos=>ocean water flux 
    499499!!$#endif 
    500       CALL histwrite( nid_T, "sowaflup", it, emp           , ndim_hT, ndex_hT )   ! upward water flux 
     500      CALL histwrite( nid_T, "sowaflup", it, ( emp-rnf )   , ndim_hT, ndex_hT )   ! upward water flux 
    501501!!$      CALL histwrite( nid_T, "sorunoff", it, runoff        , ndim_hT, ndex_hT )   ! runoff 
    502       CALL histwrite( nid_T, "sowaflcd", it, emps          , ndim_hT, ndex_hT )   ! c/d water flux 
    503       zw2d(:,:) = emps(:,:) * sn(:,:,1) * tmask(:,:,1) 
     502      CALL histwrite( nid_T, "sowaflcd", it, ( emps-rnf )  , ndim_hT, ndex_hT )   ! c/d water flux 
     503      zw2d(:,:) = ( emps(:,:) - rnf(:,:) ) * sn(:,:,1) * tmask(:,:,1) 
    504504      CALL histwrite( nid_T, "sosalflx", it, zw2d          , ndim_hT, ndex_hT )   ! c/d salt flux 
    505505      CALL histwrite( nid_T, "sohefldo", it, qns + qsr     , ndim_hT, ndex_hT )   ! total heat flux 
     
    700700      CALL histwrite( id_i, "vomecrty", kt, vn       , jpi*jpj*jpk, idex )    ! now j-velocity 
    701701      CALL histwrite( id_i, "vovecrtz", kt, wn       , jpi*jpj*jpk, idex )    ! now k-velocity 
    702       CALL histwrite( id_i, "sowaflup", kt, emp      , jpi*jpj    , idex )    ! freshwater budget 
     702      CALL histwrite( id_i, "sowaflup", kt, (emp-rnf), jpi*jpj    , idex )    ! freshwater budget 
    703703      CALL histwrite( id_i, "sohefldo", kt, qsr + qns, jpi*jpj    , idex )    ! total heat flux 
    704704      CALL histwrite( id_i, "soshfldo", kt, qsr      , jpi*jpj    , idex )    ! solar heat flux 
  • branches/devukmo2010/NEMO/OPA_SRC/DIA/diawri_dimg.h90

    r1685 r2128  
    4242    !!  level 2:  vtau(:,:) * vmask(:,:,1) meridional stress in N. m-2 
    4343    !!  level 3:  qsr + qns                total heat flux (W/m2) 
    44     !!  level 4:  emp (:,:)               E-P flux (mm/day) 
     44    !!  level 4:  ( emp (:,:)-rnf(:,:) )   E-P flux (mm/day) 
    4545    !!  level 5:  tb  (:,:,1)-sst          model SST -forcing sst (degree C) ! deprecated 
    4646    !!  level 6:  bsfb(:,:)         streamfunction (m**3/s) 
     
    5454    !!  level 14: qct(:,:)                 equivalent flux due to treshold SST 
    5555    !!  level 15: fbt(:,:)                 feedback term . 
    56     !!  level 16: emps(:,:)                concentration/dilution water flux 
     56    !!  level 16: ( emps(:,:) - rnf(:,:) ) concentration/dilution water flux 
    5757    !!  level 17: fsalt(:,:)               Ice=>ocean net freshwater 
    5858    !!  level 18: gps(:,:)                 the surface pressure (m). 
     
    167167       fsel(:,:,2 ) = fsel(:,:,2 ) + vtau(:,:) * vmask(:,:,1) 
    168168       fsel(:,:,3 ) = fsel(:,:,3 ) + qsr (:,:) + qns  (:,:)  
    169        fsel(:,:,4 ) = fsel(:,:,4 ) + emp (:,:) 
     169       fsel(:,:,4 ) = fsel(:,:,4 ) + ( emp(:,:)-rnf(:,:) )  
    170170       !        fsel(:,:,5 ) = fsel(:,:,5 ) + tb  (:,:,1)  !RB not used 
    171171       fsel(:,:,6 ) = fsel(:,:,6 ) + sshn(:,:)  
     
    179179       !        fsel(:,:,14) = fsel(:,:,14) + qct(:,:) 
    180180       !        fsel(:,:,15) = fsel(:,:,15) + fbt(:,:) 
    181        fsel(:,:,16) = fsel(:,:,16) + emps(:,:) 
     181       fsel(:,:,16) = fsel(:,:,16) + ( emps(:,:)-rnf(:,:) )  
    182182#ifdef key_diaspr    
    183183       fsel(:,:,18) = fsel(:,:,18) + gps(:,:)/g  
     
    242242          fsel(:,:,2 ) = vtau(:,:) * vmask(:,:,1) 
    243243          fsel(:,:,3 ) = (qsr (:,:) + qns (:,:)) * tmask(:,:,1) 
    244           fsel(:,:,4 ) = emp (:,:) * tmask(:,:,1) 
     244          fsel(:,:,4 ) = ( emp(:,:)-rnf(:,:) ) * tmask(:,:,1)  
    245245          !         fsel(:,:,5 ) = (tb  (:,:,1) - sf_sst(1)%fnow(:,:) ) *tmask(:,:,1) !RB not used 
    246246 
     
    255255          !         fsel(:,:,14) =  qct(:,:) 
    256256          !         fsel(:,:,15) =  fbt(:,:) 
    257           fsel(:,:,16) =  emps(:,:) * tmask(:,:,1) 
     257          fsel(:,:,16) = ( emps(:,:)-rnf(:,:) ) * tmask(:,:,1)  
    258258#ifdef key_diaspr            
    259259          fsel(:,:,18) =      gps(:,:) /g 
Note: See TracChangeset for help on using the changeset viewer.