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 14789 for NEMO/branches/2021/dev_r13747_HPC-11_mcastril_HPDAonline_DiagGPU/src/OCE/SBC/sbcrnf.F90 – NEMO

Ignore:
Timestamp:
2021-05-05T13:18:04+02:00 (3 years ago)
Author:
mcastril
Message:

[2021/HPC-11_mcastril_HPDAonline_DiagGPU] Update externals

Location:
NEMO/branches/2021/dev_r13747_HPC-11_mcastril_HPDAonline_DiagGPU
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r13747_HPC-11_mcastril_HPDAonline_DiagGPU

    • Property svn:externals
      •  

        old new  
        33^/utils/build/mk@HEAD         mk 
        44^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev_r12970_AGRIF_CMEMS      ext/AGRIF 
         5^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         8^/vendors/PPR@HEAD            ext/PPR 
        89 
        910# SETTE 
        10 ^/utils/CI/sette@13559        sette 
         11^/utils/CI/sette@14244        sette 
  • NEMO/branches/2021/dev_r13747_HPC-11_mcastril_HPDAonline_DiagGPU/src/OCE/SBC/sbcrnf.F90

    r13497 r14789  
    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 
     
    4242   REAL(wp)                   ::      rn_dep_max        !: depth over which runoffs is spread       (ln_rnf_depth_ini =T) 
    4343   INTEGER                    ::      nn_rnf_depth_file !: create (=1) a runoff depth file or not (=0) 
    44    LOGICAL                   ::   ln_rnf_icb        !: iceberg flux is specified in a file 
     44   LOGICAL           , PUBLIC ::   ln_rnf_icb        !: iceberg flux is specified in a file 
    4545   LOGICAL                    ::   ln_rnf_tem        !: temperature river runoffs attribute specified in a file 
    4646   LOGICAL           , PUBLIC ::   ln_rnf_sal        !: salinity    river runoffs attribute specified in a file 
     
    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" 
     
    131131             IF( ln_rnf_icb ) THEN 
    132132                fwficb(:,:) = rn_rfact * ( sf_i_rnf(1)%fnow(:,:,1) ) * tmask(:,:,1)  ! updated runoff value at time step kt 
    133                 CALL iom_put( 'iceberg_cea'  , fwficb(:,:)  )         ! output iceberg flux 
    134                 CALL iom_put( 'hflx_icb_cea' , fwficb(:,:) * rLfus )   ! output Heat Flux into Sea Water due to Iceberg Thermodynamics --> 
     133                rnf(:,:) = rnf(:,:) + fwficb(:,:) 
     134                qns(:,:) = qns(:,:) - fwficb(:,:) * rLfus 
     135                !!qns_tot(:,:) = qns_tot(:,:) - fwficb(:,:) * rLfus                 
     136                !!qns_oce(:,:) = qns_oce(:,:) - fwficb(:,:) * rLfus                 
     137                CALL iom_put( 'iceberg_cea'  ,  fwficb(:,:)  )          ! output iceberg flux 
     138                CALL iom_put( 'hflx_icb_cea' , -fwficb(:,:) * rLfus )   ! output Heat Flux into Sea Water due to Iceberg Thermodynamics --> 
    135139             ENDIF 
    136140         ENDIF 
     
    152156                                         CALL iom_put( 'runoffs'     , rnf(:,:)                         )   ! output runoff mass flux 
    153157         IF( iom_use('hflx_rnf_cea') )   CALL iom_put( 'hflx_rnf_cea', rnf_tsc(:,:,jp_tem) * rho0 * rcp )   ! output runoff sensible heat (W/m2) 
     158         IF( iom_use('sflx_rnf_cea') )   CALL iom_put( 'sflx_rnf_cea', rnf_tsc(:,:,jp_sal) * rho0       )   ! output runoff salt flux (g/m2/s) 
    154159      ENDIF 
    155160      ! 
     
    157162      IF( kt == nit000 ) THEN                          !   set the forcing field at nit000 - 1    ! 
    158163         !                                             ! ---------------------------------------- ! 
    159          IF( ln_rstart .AND.    &                               !* Restart: read in restart file 
    160             & iom_varid( numror, 'rnf_b', ldstop = .FALSE. ) > 0 ) THEN 
     164         IF( ln_rstart .AND. .NOT.l_1st_euler ) THEN         !* Restart: read in restart file 
    161165            IF(lwp) WRITE(numout,*) '          nit000-1 runoff forcing fields red in the restart file', lrxios 
    162             CALL iom_get( numror, jpdom_auto, 'rnf_b', rnf_b, ldxios = lrxios )     ! before runoff 
    163             CALL iom_get( numror, jpdom_auto, 'rnf_hc_b', rnf_tsc_b(:,:,jp_tem), ldxios = lrxios )   ! before heat content of runoff 
    164             CALL iom_get( numror, jpdom_auto, 'rnf_sc_b', rnf_tsc_b(:,:,jp_sal), ldxios = lrxios )   ! before salinity content of runoff 
    165          ELSE                                                   !* no restart: set from nit000 values 
     166            CALL iom_get( numror, jpdom_auto, 'rnf_b'   , rnf_b                 )   ! before runoff 
     167            CALL iom_get( numror, jpdom_auto, 'rnf_hc_b', rnf_tsc_b(:,:,jp_tem) )   ! before heat content of runoff 
     168            CALL iom_get( numror, jpdom_auto, 'rnf_sc_b', rnf_tsc_b(:,:,jp_sal) )   ! before salinity content of runoff 
     169         ELSE                                                !* no restart: set from nit000 values 
    166170            IF(lwp) WRITE(numout,*) '          nit000-1 runoff forcing fields set to nit000' 
    167171            rnf_b    (:,:  ) = rnf    (:,:  ) 
     
    176180            &                    'at it= ', kt,' date= ', ndastp 
    177181         IF(lwp) WRITE(numout,*) '~~~~' 
    178          IF( lwxios ) CALL iom_swap(      cwxios_context          ) 
    179          CALL iom_rstput( kt, nitrst, numrow, 'rnf_b' , rnf, ldxios = lwxios ) 
    180          CALL iom_rstput( kt, nitrst, numrow, 'rnf_hc_b', rnf_tsc(:,:,jp_tem), ldxios = lwxios ) 
    181          CALL iom_rstput( kt, nitrst, numrow, 'rnf_sc_b', rnf_tsc(:,:,jp_sal), ldxios = lwxios ) 
    182          IF( lwxios ) CALL iom_swap(      cxios_context          ) 
     182         CALL iom_rstput( kt, nitrst, numrow, 'rnf_b'   , rnf                 ) 
     183         CALL iom_rstput( kt, nitrst, numrow, 'rnf_hc_b', rnf_tsc(:,:,jp_tem) ) 
     184         CALL iom_rstput( kt, nitrst, numrow, 'rnf_sc_b', rnf_tsc(:,:,jp_sal) ) 
    183185      ENDIF 
    184186      ! 
     
    250252      INTEGER           ::   ios           ! Local integer output status for namelist read 
    251253      INTEGER           ::   nbrec         ! temporary integer 
    252       REAL(wp)          ::   zacoef   
    253       REAL(wp), DIMENSION(jpi,jpj,2) :: zrnfcl     
     254      REAL(wp)          ::   zacoef 
     255      REAL(wp), DIMENSION(jpi,jpj,2) :: zrnfcl 
    254256      !! 
    255257      NAMELIST/namsbc_rnf/ cn_dir            , ln_rnf_depth, ln_rnf_tem, ln_rnf_sal, ln_rnf_icb,   & 
     
    262264      IF( sbc_rnf_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_rnf_alloc : unable to allocate arrays' ) 
    263265      ! 
    264       IF( .NOT. ln_rnf ) THEN                      ! no specific treatment in vicinity of river mouths  
     266      IF( .NOT. ln_rnf ) THEN                      ! no specific treatment in vicinity of river mouths 
    265267         ln_rnf_mouth  = .FALSE.                   ! default definition needed for example by sbc_ssr or by tra_adv_muscl 
    266268         nkrnf         = 0 
     
    298300      !                                   ! ================== 
    299301      ! 
    300       IF( .NOT. l_rnfcpl ) THEN                     
     302      IF( .NOT. l_rnfcpl ) THEN 
    301303         ALLOCATE( sf_rnf(1), STAT=ierror )         ! Create sf_rnf structure (runoff inflow) 
    302304         IF(lwp) WRITE(numout,*) 
     
    353355         IF(lwp) WRITE(numout,*) '   ==>>>   runoffs depth read in a file' 
    354356         rn_dep_file = TRIM( cn_dir )//TRIM( sn_dep_rnf%clname ) 
    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%clftyp == 'monthly' )   WRITE(rn_dep_file, '(a,"m",i2)'  ) TRIM( rn_dep_file ), nmonth   ! add month  
     357         IF( .NOT. sn_dep_rnf%ln_clim ) THEN   ;   WRITE(rn_dep_file, '(a,"_y",i4)' ) TRIM( rn_dep_file ), nyear    ! add year 
     358            IF( sn_dep_rnf%clftyp == 'monthly' )   WRITE(rn_dep_file, '(a,"m",i2)'  ) TRIM( rn_dep_file ), nmonth   ! add month 
    357359         ENDIF 
    358360         CALL iom_open ( rn_dep_file, inum )                             ! open file 
     
    480482      ENDIF 
    481483      ! 
    482       IF( lwxios ) THEN 
    483          CALL iom_set_rstw_var_active('rnf_b') 
    484          CALL iom_set_rstw_var_active('rnf_hc_b') 
    485          CALL iom_set_rstw_var_active('rnf_sc_b') 
    486       ENDIF 
    487  
    488484   END SUBROUTINE sbc_rnf_init 
    489485 
Note: See TracChangeset for help on using the changeset viewer.