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 3623 for branches – NEMO

Changeset 3623 for branches


Ignore:
Timestamp:
2012-11-21T13:12:48+01:00 (11 years ago)
Author:
acc
Message:

dev_r3385_NOCS04_HAMF; #665. Corrections to passive and off-line tracer modules prior to merge

Location:
branches/2012/dev_r3385_NOCS04_HAMF/NEMOGCM/NEMO
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • branches/2012/dev_r3385_NOCS04_HAMF/NEMOGCM/NEMO/OFF_SRC/dtadyn.F90

    r3414 r3623  
    5252   LOGICAL            ::   ln_degrad  = .false. !: degradation option enabled or not  
    5353 
    54    INTEGER  , PARAMETER ::   jpfld = 19     ! maximum number of files to read 
     54   INTEGER  , PARAMETER ::   jpfld = 20     ! maximum number of fields to read 
    5555   INTEGER  , SAVE      ::   jf_tem         ! index of temperature 
    5656   INTEGER  , SAVE      ::   jf_sal         ! index of salinity 
     
    7272   INTEGER  , SAVE      ::   jf_eiv         ! index of v-eiv 
    7373   INTEGER  , SAVE      ::   jf_eiw         ! index of w-eiv 
     74   INTEGER  , SAVE      ::   jf_sfx         ! index of downward salt flux 
    7475 
    7576   TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_dyn  ! structure of input fields (file informations, fields read) 
     
    250251      un (:,:,:)       = sf_dyn(jf_uwd)%fnow(:,:,:) * umask(:,:,:)    ! u-velocity 
    251252      vn (:,:,:)       = sf_dyn(jf_vwd)%fnow(:,:,:) * vmask(:,:,:)    ! v-velocity  
    252       IF( .NOT.ln_dynwzv ) &                                           ! w-velocity read in file  
     253      IF( .NOT.ln_dynwzv ) &                                          ! w-velocity read in file  
    253254         wn (:,:,:)    = sf_dyn(jf_wwd)%fnow(:,:,:) * tmask(:,:,:)     
    254255      hmld(:,:)        = sf_dyn(jf_mld)%fnow(:,:,1) * tmask(:,:,1)    ! mixed layer depht 
    255256      wndm(:,:)        = sf_dyn(jf_wnd)%fnow(:,:,1) * tmask(:,:,1)    ! wind speed - needed for gas exchange 
    256257      emp (:,:)        = sf_dyn(jf_emp)%fnow(:,:,1) * tmask(:,:,1)    ! E-P 
    257       sfx (:,:)        = emp(:,:)  
    258       fr_i(:,:)        = sf_dyn(jf_ice)%fnow(:,:,1) * tmask(:,:,1)     ! Sea-ice fraction 
     258      sfx (:,:)        = 0.0_wp      ! enable testing with old inputs ! downward salt flux  
     259!     sfx (:,:)        = sf_dyn(jf_sfx)%fnow(:,:,1) * tmask(:,:,1)    ! downward salt flux (v3.5+) 
     260      fr_i(:,:)        = sf_dyn(jf_ice)%fnow(:,:,1) * tmask(:,:,1)    ! Sea-ice fraction 
    259261      qsr (:,:)        = sf_dyn(jf_qsr)%fnow(:,:,1) * tmask(:,:,1)    ! solar radiation 
    260262 
     
    330332      TYPE(FLD_N) :: sn_tem, sn_sal, sn_mld, sn_emp, sn_ice, sn_qsr, sn_wnd  ! informations about the fields to be read 
    331333      TYPE(FLD_N) :: sn_uwd, sn_vwd, sn_wwd, sn_avt, sn_ubl, sn_vbl          !   "                                 " 
    332       TYPE(FLD_N) :: sn_ahu, sn_ahv, sn_ahw, sn_eiu, sn_eiv, sn_eiw          !   "                                 " 
     334      TYPE(FLD_N) :: sn_ahu, sn_ahv, sn_ahw, sn_eiu, sn_eiv, sn_eiw, sn_sfx  !   "                                 " 
    333335      ! 
    334336      NAMELIST/namdta_dyn/cn_dir, ln_dynwzv, ln_dynbbl, ln_degrad,    & 
    335337         &                sn_tem, sn_sal, sn_mld, sn_emp, sn_ice, sn_qsr, sn_wnd,  & 
    336338         &                sn_uwd, sn_vwd, sn_wwd, sn_avt, sn_ubl, sn_vbl,          & 
    337          &                sn_ahu, sn_ahv, sn_ahw, sn_eiu, sn_eiv, sn_eiw 
     339         &                sn_ahu, sn_ahv, sn_ahw, sn_eiu, sn_eiv, sn_eiw, sn_sfx 
    338340 
    339341      !!---------------------------------------------------------------------- 
     
    348350      sn_mld  = FLD_N( 'dyna_grid_T' ,    120    , 'somixght' ,  .true.    , .true. ,   'yearly'  , ''       , ''         ) 
    349351      sn_emp  = FLD_N( 'dyna_grid_T' ,    120    , 'sowaflcd' ,  .true.    , .true. ,   'yearly'  , ''       , ''         ) 
     352!!    sn_emp  = FLD_N( 'dyna_grid_T' ,    120    , 'sowaflup' ,  .true.    , .true. ,   'yearly'  , ''       , ''         ) ! v3.5+ 
     353      sn_sfx  = FLD_N( 'dyna_grid_T' ,    120    , 'sosfldow' ,  .true.    , .true. ,   'yearly'  , ''       , ''         ) ! v3.5+ 
    350354      sn_ice  = FLD_N( 'dyna_grid_T' ,    120    , 'soicecov' ,  .true.    , .true. ,   'yearly'  , ''       , ''         ) 
    351355      sn_qsr  = FLD_N( 'dyna_grid_T' ,    120    , 'soshfldo' ,  .true.    , .true. ,   'yearly'  , ''       , ''         ) 
     
    426430        ENDIF 
    427431      ENDIF 
     432      ! Salt flux and concntration/dilution terms (new from v3.5) !! disabled to allow testing with old input files 
     433!!    jf_sfx = jfld + 1    ;    jfld = jfld + 1 
     434!!    slf_d(jf_sfx) = sn_sfx 
    428435   
    429436      ALLOCATE( sf_dyn(jfld), STAT=ierr )         ! set sf structure 
  • branches/2012/dev_r3385_NOCS04_HAMF/NEMOGCM/NEMO/TOP_SRC/oce_trc.F90

    r3403 r3623  
    227227   USE sbc_oce , ONLY :   emp        =>    emp        !: freshwater budget: volume flux               [Kg/m2/s] 
    228228   USE sbc_oce , ONLY :   emp_b      =>    emp_b      !: freshwater budget: volume flux               [Kg/m2/s] 
    229    USE sbc_oce , ONLY :   sfx        =>    sfx        !: freshwater budget: concentration/dillution   [Kg/m2/s] 
     229   USE sbc_oce , ONLY :   sfx        =>    sfx        !: downward salt flux                          [PSU/m2/s] 
    230230   USE sbc_oce , ONLY :   rnf        =>    rnf        !: river runoff   [Kg/m2/s] 
    231231   USE sbc_oce , ONLY :   ln_dm2dc   =>    ln_dm2dc   !: Daily mean to Diurnal Cycle short wave (qsr)  
  • branches/2012/dev_r3385_NOCS04_HAMF/NEMOGCM/NEMO/TOP_SRC/trc.F90

    r3294 r3623  
    133133   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  fr_i_tm    !: average ice fraction     [m/s] 
    134134   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  emp_tm     !: freshwater budget: volume flux [Kg/m2/s] 
    135    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  emps_tm    !: freshwater budget:concentration/dilution [Kg/m2/s] 
     135   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  sfx_tm     !: downward salt flux [PSU/m2/s] 
    136136   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  emp_b_hold !: hold emp from the beginning of each sub-stepping[m]   
    137137   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  qsr_tm     !: solar radiation average [m] 
     
    173173   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  hdivb_temp, rotb_temp 
    174174   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  hmld_temp, qsr_temp, fr_i_temp,wndm_temp 
    175    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  emp_temp, emps_temp, emp_b_temp 
     175   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::  emp_temp, sfx_temp, emp_b_temp 
    176176   ! 
    177177#if defined key_trabbl 
  • branches/2012/dev_r3385_NOCS04_HAMF/NEMOGCM/NEMO/TOP_SRC/trcsub.F90

    r3403 r3623  
    121121          fr_i_tm  (:,:)         = fr_i_tm  (:,:)         + fr_i  (:,:) 
    122122          emp_tm   (:,:)         = emp_tm   (:,:)         + emp   (:,:)  
    123           emps_tm  (:,:)         = emps_tm  (:,:)         + sfx   (:,:) 
     123          sfx_tm   (:,:)         = sfx_tm   (:,:)         + sfx   (:,:) 
    124124          qsr_tm   (:,:)         = qsr_tm   (:,:)         + qsr   (:,:) 
    125125          wndm_tm  (:,:)         = wndm_tm  (:,:)         + wndm  (:,:) 
     
    209209         emp_temp   (:,:)        = emp   (:,:) 
    210210         emp_b_temp (:,:)        = emp_b (:,:) 
    211          emps_temp  (:,:)        = sfx   (:,:) 
     211         sfx_temp   (:,:)        = sfx   (:,:) 
    212212         qsr_temp   (:,:)        = qsr   (:,:) 
    213213         wndm_temp  (:,:)        = wndm  (:,:) 
     
    313313         fr_i_tm  (:,:)          = fr_i_tm    (:,:)       + fr_i  (:,:) 
    314314         emp_tm   (:,:)          = emp_tm     (:,:)       + emp   (:,:)  
    315          emps_tm  (:,:)          = emps_tm    (:,:)       + sfx   (:,:) 
     315         sfx_tm   (:,:)          = sfx_tm     (:,:)       + sfx   (:,:) 
    316316         qsr_tm   (:,:)          = qsr_tm     (:,:)       + qsr   (:,:) 
    317317         wndm_tm  (:,:)          = wndm_tm    (:,:)       + wndm  (:,:) 
     
    332332            qsr   (:,:)          = qsr_tm     (:,:) * r1_ndttrc  
    333333            emp   (:,:)          = emp_tm     (:,:) * r1_ndttrc  
    334             sfx   (:,:)          = emps_tm    (:,:) * r1_ndttrc  
     334            sfx   (:,:)          = sfx_tm     (:,:) * r1_ndttrc  
    335335            fr_i  (:,:)          = fr_i_tm    (:,:) * r1_ndttrc 
    336336# if defined key_trabbl 
     
    348348            qsr   (:,:)          = qsr_tm     (:,:) * r1_ndttrcp1  
    349349            emp   (:,:)          = emp_tm     (:,:) * r1_ndttrcp1  
    350             sfx   (:,:)          = emps_tm    (:,:) * r1_ndttrcp1  
     350            sfx   (:,:)          = sfx_tm     (:,:) * r1_ndttrcp1  
    351351            fr_i  (:,:)          = fr_i_tm    (:,:) * r1_ndttrcp1  
    352352# if defined key_trabbl 
     
    598598      fr_i_tm(:,:) = 0._wp 
    599599      emp_tm (:,:) = 0._wp 
    600       emps_tm(:,:) = 0._wp 
     600      sfx_tm(:,:) = 0._wp 
    601601      qsr_tm (:,:) = 0._wp 
    602602      wndm_tm(:,:) = 0._wp 
     
    705705      fr_i  (:,:)     =  fr_i_temp  (:,:) 
    706706      emp   (:,:)     =  emp_temp   (:,:) 
    707       sfx   (:,:)     =  emps_temp  (:,:) 
     707      sfx   (:,:)     =  sfx_temp   (:,:) 
    708708      emp_b (:,:)     =  emp_b_temp (:,:) 
    709709      qsr   (:,:)     =  qsr_temp   (:,:) 
     
    824824      fr_i_tm    (:,:) = fr_i  (:,:) 
    825825      emp_tm     (:,:) = emp   (:,:) 
    826       emps_tm    (:,:) = sfx   (:,:) 
     826      sfx_tm     (:,:) = sfx   (:,:) 
    827827      qsr_tm     (:,:) = qsr   (:,:) 
    828828      wndm_tm    (:,:) = wndm  (:,:) 
     
    10531053         &      rnf_temp(jpi,jpj)           ,  h_rnf_temp(jpi,jpj) ,     & 
    10541054         &      tsn_temp(jpi,jpj,jpk,2)     ,  emp_b_temp(jpi,jpj),      & 
    1055          &      emp_temp(jpi,jpj)           ,  emps_temp(jpi,jpj) ,      & 
     1055         &      emp_temp(jpi,jpj)           ,  sfx_temp(jpi,jpj) ,      & 
    10561056         &      hmld_temp(jpi,jpj)          ,  qsr_temp(jpi,jpj) ,       & 
    10571057         &      fr_i_temp(jpi,jpj)          ,  fr_i_tm(jpi,jpj) ,        & 
     
    11011101         &      sshv_n_tm(jpi,jpj)          ,  sshv_b_hold(jpi,jpj),     & 
    11021102         &      tsn_tm(jpi,jpj,jpk,2)       ,                            & 
    1103          &      emp_tm(jpi,jpj)             ,  emps_tm(jpi,jpj) ,        & 
     1103         &      emp_tm(jpi,jpj)             ,  sfx_tm(jpi,jpj) ,        & 
    11041104         &      emp_b_hold(jpi,jpj)         ,                            & 
    11051105         &      hmld_tm(jpi,jpj)            ,  qsr_tm(jpi,jpj) ,         & 
Note: See TracChangeset for help on using the changeset viewer.