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 14072 for NEMO/trunk/src/OCE/SBC/sbcrnf.F90 – NEMO

Ignore:
Timestamp:
2020-12-04T08:48:38+01:00 (3 years ago)
Author:
laurent
Message:

Merging branch "2020/dev_r13648_ASINTER-04_laurent_bulk_ice", ticket #2369

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/OCE/SBC/sbcrnf.F90

    r14053 r14072  
    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" 
     
    247247      INTEGER           ::   ios           ! Local integer output status for namelist read 
    248248      INTEGER           ::   nbrec         ! temporary integer 
    249       REAL(wp)          ::   zacoef   
    250       REAL(wp), DIMENSION(jpi,jpj,2) :: zrnfcl     
     249      REAL(wp)          ::   zacoef 
     250      REAL(wp), DIMENSION(jpi,jpj,2) :: zrnfcl 
    251251      !! 
    252252      NAMELIST/namsbc_rnf/ cn_dir            , ln_rnf_depth, ln_rnf_tem, ln_rnf_sal, ln_rnf_icb,   & 
     
    259259      IF( sbc_rnf_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_rnf_alloc : unable to allocate arrays' ) 
    260260      ! 
    261       IF( .NOT. ln_rnf ) THEN                      ! no specific treatment in vicinity of river mouths  
     261      IF( .NOT. ln_rnf ) THEN                      ! no specific treatment in vicinity of river mouths 
    262262         ln_rnf_mouth  = .FALSE.                   ! default definition needed for example by sbc_ssr or by tra_adv_muscl 
    263263         nkrnf         = 0 
     
    295295      !                                   ! ================== 
    296296      ! 
    297       IF( .NOT. l_rnfcpl ) THEN                     
     297      IF( .NOT. l_rnfcpl ) THEN 
    298298         ALLOCATE( sf_rnf(1), STAT=ierror )         ! Create sf_rnf structure (runoff inflow) 
    299299         IF(lwp) WRITE(numout,*) 
     
    350350         IF(lwp) WRITE(numout,*) '   ==>>>   runoffs depth read in a file' 
    351351         rn_dep_file = TRIM( cn_dir )//TRIM( sn_dep_rnf%clname ) 
    352          IF( .NOT. sn_dep_rnf%ln_clim ) THEN   ;   WRITE(rn_dep_file, '(a,"_y",i4)' ) TRIM( rn_dep_file ), nyear    ! add year  
    353             IF( sn_dep_rnf%clftyp == 'monthly' )   WRITE(rn_dep_file, '(a,"m",i2)'  ) TRIM( rn_dep_file ), nmonth   ! add month  
     352         IF( .NOT. sn_dep_rnf%ln_clim ) THEN   ;   WRITE(rn_dep_file, '(a,"_y",i4)' ) TRIM( rn_dep_file ), nyear    ! add year 
     353            IF( sn_dep_rnf%clftyp == 'monthly' )   WRITE(rn_dep_file, '(a,"m",i2)'  ) TRIM( rn_dep_file ), nmonth   ! add month 
    354354         ENDIF 
    355355         CALL iom_open ( rn_dep_file, inum )                             ! open file 
Note: See TracChangeset for help on using the changeset viewer.