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 12590 for NEMO/branches/2020/dev_r12377_KERNEL-06_techene_e3/src/OCE/SBC/sbcrnf.F90 – NEMO

Ignore:
Timestamp:
2020-03-23T22:16:19+01:00 (4 years ago)
Author:
techene
Message:

all: add e3 substitute, OCE/DOM/domzgr_substitute.h90: correct a bug for e3f

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r12377_KERNEL-06_techene_e3/src/OCE/SBC/sbcrnf.F90

    r12377 r12590  
    3434   PUBLIC   sbc_rnf_alloc ! called in sbcmod module 
    3535   PUBLIC   sbc_rnf_init  ! called in sbcmod module 
    36     
     36 
    3737   !                                                !!* namsbc_rnf namelist * 
    3838   CHARACTER(len=100)         ::   cn_dir            !: Root directory for location of rnf files 
     
    5858   LOGICAL , PUBLIC ::   l_rnfcpl = .false.   !: runoffs recieved from oasis 
    5959   INTEGER , PUBLIC ::   nkrnf = 0            !: nb of levels over which Kz is increased at river mouths 
    60     
     60 
    6161   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rnfmsk              !: river mouth mask (hori.) 
    6262   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)     ::   rnfmsk_z            !: river mouth mask (vert.) 
    6363   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   h_rnf               !: depth of runoff in m 
    6464   INTEGER,  PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   nk_rnf              !: depth of runoff in model levels 
    65    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   rnf_tsc_b, rnf_tsc  !: before and now T & S runoff contents   [K.m/s & PSU.m/s]    
     65   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   rnf_tsc_b, rnf_tsc  !: before and now T & S runoff contents   [K.m/s & PSU.m/s] 
    6666 
    6767   TYPE(FLD),        ALLOCATABLE, DIMENSION(:) ::   sf_rnf       ! structure: river runoff (file information, fields read) 
    6868   TYPE(FLD),        ALLOCATABLE, DIMENSION(:) ::   sf_i_rnf     ! structure: iceberg flux (file information, fields read) 
    69    TYPE(FLD),        ALLOCATABLE, DIMENSION(:) ::   sf_s_rnf     ! structure: river runoff salinity (file information, fields read)   
    70    TYPE(FLD),        ALLOCATABLE, DIMENSION(:) ::   sf_t_rnf     ! structure: river runoff temperature (file information, fields read)   
    71   
     69   TYPE(FLD),        ALLOCATABLE, DIMENSION(:) ::   sf_s_rnf     ! structure: river runoff salinity (file information, fields read) 
     70   TYPE(FLD),        ALLOCATABLE, DIMENSION(:) ::   sf_t_rnf     ! structure: river runoff temperature (file information, fields read) 
     71 
    7272   !! * Substitutions 
    7373#  include "do_loop_substitute.h90" 
     74#  include "domzgr_substitute.h90" 
    7475   !!---------------------------------------------------------------------- 
    7576   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    227228      ELSE                       !==   runoff put only at the surface   ==! 
    228229         h_rnf (:,:)   = e3t (:,:,1,Kmm)        ! update h_rnf to be depth of top box 
    229          phdivn(:,:,1) = phdivn(:,:,1) - ( rnf(:,:) + rnf_b(:,:) ) * zfact * r1_rau0 / e3t(:,:,1,Kmm) 
     230         phdivn(:,:,1) = phdivn(:,:,1) - ( rnf(:,:)+rnf_b(:,:) ) * zfact * r1_rau0 / e3t(:,:,1,Kmm) 
    230231      ENDIF 
    231232      ! 
     
    249250      INTEGER           ::   ios           ! Local integer output status for namelist read 
    250251      INTEGER           ::   nbrec         ! temporary integer 
    251       REAL(wp)          ::   zacoef   
    252       REAL(wp), DIMENSION(jpi,jpj,2) :: zrnfcl     
     252      REAL(wp)          ::   zacoef 
     253      REAL(wp), DIMENSION(jpi,jpj,2) :: zrnfcl 
    253254      !! 
    254255      NAMELIST/namsbc_rnf/ cn_dir            , ln_rnf_depth, ln_rnf_tem, ln_rnf_sal, ln_rnf_icb,   & 
     
    261262      IF( sbc_rnf_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_rnf_alloc : unable to allocate arrays' ) 
    262263      ! 
    263       IF( .NOT. ln_rnf ) THEN                      ! no specific treatment in vicinity of river mouths  
     264      IF( .NOT. ln_rnf ) THEN                      ! no specific treatment in vicinity of river mouths 
    264265         ln_rnf_mouth  = .FALSE.                   ! default definition needed for example by sbc_ssr or by tra_adv_muscl 
    265266         nkrnf         = 0 
     
    297298      !                                   ! ================== 
    298299      ! 
    299       IF( .NOT. l_rnfcpl ) THEN                     
     300      IF( .NOT. l_rnfcpl ) THEN 
    300301         ALLOCATE( sf_rnf(1), STAT=ierror )         ! Create sf_rnf structure (runoff inflow) 
    301302         IF(lwp) WRITE(numout,*) 
     
    352353         IF(lwp) WRITE(numout,*) '   ==>>>   runoffs depth read in a file' 
    353354         rn_dep_file = TRIM( cn_dir )//TRIM( sn_dep_rnf%clname ) 
    354          IF( .NOT. sn_dep_rnf%ln_clim ) THEN   ;   WRITE(rn_dep_file, '(a,"_y",i4)' ) TRIM( rn_dep_file ), nyear    ! add year  
    355             IF( sn_dep_rnf%cltype == 'monthly' )   WRITE(rn_dep_file, '(a,"m",i2)'  ) TRIM( rn_dep_file ), nmonth   ! add month  
     355         IF( .NOT. sn_dep_rnf%ln_clim ) THEN   ;   WRITE(rn_dep_file, '(a,"_y",i4)' ) TRIM( rn_dep_file ), nyear    ! add year 
     356            IF( sn_dep_rnf%cltype == 'monthly' )   WRITE(rn_dep_file, '(a,"m",i2)'  ) TRIM( rn_dep_file ), nmonth   ! add month 
    356357         ENDIF 
    357358         CALL iom_open ( rn_dep_file, inum )                           ! open file 
Note: See TracChangeset for help on using the changeset viewer.