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 2000 for branches/DEV_r1784_mid_year_merge_2010/NEMO/OPA_SRC/SBC/sbcrnf.F90 – NEMO

Ignore:
Timestamp:
2010-07-09T13:27:11+02:00 (14 years ago)
Author:
acc
Message:

ticket #684 step 7: Add in changes between the head of the DEV_r1821_Rivers branch and the trunk@1821. Note untested changes were made to the Rivers branch before this merge see wiki ticket page for details

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/DEV_r1784_mid_year_merge_2010/NEMO/OPA_SRC/SBC/sbcrnf.F90

    r1951 r2000  
    3232   TYPE(FLD_N)       , PUBLIC ::   sn_rnf                 !: information about the runoff file to be read 
    3333   TYPE(FLD_N)       , PUBLIC ::   sn_cnf                 !: information about the runoff mouth file to be read 
     34   TYPE(FLD_N)                ::   sn_sal_rnf             !: information about the salinities of runoff file to be read   
     35   TYPE(FLD_N)                ::   sn_tmp_rnf             !: information about the temperatures of runoff file to be read   
     36   TYPE(FLD_N)                ::   sn_dep_rnf             !: information about the depth which river inflow affects 
    3437   LOGICAL           , PUBLIC ::   ln_rnf_mouth = .false. !: specific treatment in mouths vicinity 
    3538   REAL(wp)          , PUBLIC ::   rn_hrnf      = 0.e0    !: runoffs, depth over which enhanced vertical mixing is used 
    3639   REAL(wp)          , PUBLIC ::   rn_avt_rnf   = 0.e0    !: runoffs, value of the additional vertical mixing coef. [m2/s] 
     40   LOGICAL           , PUBLIC ::   ln_rnf_att   = .false. !: river runoffs attributes (temp, sal & depth) are specified in a file  
    3741   REAL(wp)          , PUBLIC ::   rn_rfact     = 1.e0    !: multiplicative factor for runoff 
    3842 
     
    4145   REAL(wp), PUBLIC, DIMENSION(jpk)     ::   rnfmsk_z    !: river mouth mask (vert.) 
    4246 
    43    TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_rnf   ! structure of input SST (file information, fields read) 
     47   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_rnf        !: structure of input river runoff (file information, fields read) 
     48 
     49   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_sal_rnf    !: structure of input river runoff salinity (file information, fields read)   
     50   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_tmp_rnf    !: structure of input river runoff temperature (file information, fields read)   
     51  
     52   REAL,    PUBLIC, DIMENSION(jpi,jpj) ::  rnf_dep         !: depth of runoff in m   
     53   INTEGER, PUBLIC, DIMENSION(jpi,jpj) ::  rnf_mod_dep     !: depth of runoff in model levels   
     54   REAL,    PUBLIC, DIMENSION(jpi,jpj) ::  rnf_sal         !: salinity of river runoff   
     55   REAL,    PUBLIC, DIMENSION(jpi,jpj) ::  rnf_tmp         !: temperature of river runoff   
     56   
     57   INTEGER  ::  ji, jj ,jk    ! dummy loop indices   
     58   INTEGER  ::  inum          ! temporary logical unit   
     59   
     60   !! * Substitutions   
     61#  include "domzgr_substitute.h90"   
    4462 
    4563   !!---------------------------------------------------------------------- 
     
    7088      !                                    
    7189      IF( kt == nit000 ) THEN   
    72          IF( .NOT. ln_rnf_emp ) THEN 
    73             ALLOCATE( sf_rnf(1), STAT=ierror ) 
    74             IF( ierror > 0 ) THEN 
    75                CALL ctl_stop( 'sbc_rnf: unable to allocate sf_rnf structure' )   ;   RETURN 
    76             ENDIF 
    77             ALLOCATE( sf_rnf(1)%fnow(jpi,jpj,1  ) ) 
    78             ALLOCATE( sf_rnf(1)%fdta(jpi,jpj,1,2) ) 
    79          ENDIF 
    80          CALL sbc_rnf_init(sf_rnf) 
     90         CALL sbc_rnf_init                      ! Read namelist and allocate structures 
    8191      ENDIF 
    8292 
     
    8797         CALL fld_read( kt, nn_fsbc, sf_rnf )   ! Read Runoffs data and provides it 
    8898         !                                      ! at the current time-step 
     99         IF ( ln_rnf_att ) THEN   
     100            CALL fld_read ( kt, nn_fsbc, sf_sal_rnf )   
     101            CALL fld_read ( kt, nn_fsbc, sf_tmp_rnf )   
     102         ENDIF   
    89103 
    90104         ! Runoff reduction only associated to the ORCA2_LIM configuration 
     
    101115 
    102116         IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN 
    103             emp (:,:) = emp (:,:) - rn_rfact * ABS( sf_rnf(1)%fnow(:,:,1) ) 
    104             emps(:,:) = emps(:,:) - rn_rfact * ABS( sf_rnf(1)%fnow(:,:,1) ) 
    105             CALL iom_put( "runoffs", sf_rnf(1)%fnow )         ! runoffs 
     117            rnf(:,:)  = rn_rfact * ( sf_rnf(1)%fnow(:,:) )   
     118            IF ( ln_rnf_att ) THEN   
     119               rnf_sal(:,:) = ( sf_sal_rnf(1)%fnow(:,:) )   
     120               rnf_tmp(:,:) = ( sf_tmp_rnf(1)%fnow(:,:) )   
     121            ELSE   
     122               rnf_sal(:,:) = 0   
     123               rnf_tmp(:,:) = -999   
     124            ENDIF   
     125            CALL iom_put( "runoffs", rnf )         ! runoffs 
    106126         ENDIF 
    107127         ! 
     
    111131 
    112132 
    113    SUBROUTINE sbc_rnf_init( sf_rnf ) 
     133   SUBROUTINE sbc_rnf_init 
    114134      !!---------------------------------------------------------------------- 
    115135      !!                  ***  ROUTINE sbc_rnf_init  *** 
     
    121141      !! ** Action  : - read parameters 
    122142      !!---------------------------------------------------------------------- 
    123       TYPE(FLD), INTENT(inout), DIMENSION(:) :: sf_rnf   ! input data 
    124       !! 
    125       NAMELIST/namsbc_rnf/ cn_dir, ln_rnf_emp, sn_rnf, sn_cnf, ln_rnf_mouth,   & 
    126          &                 rn_hrnf, rn_avt_rnf, rn_rfact 
     143      CHARACTER(len=32) ::   rn_dep_file   ! runoff file name   
     144      !!  
     145      NAMELIST/namsbc_rnf/ cn_dir, ln_rnf_emp, sn_rnf, sn_cnf, sn_sal_rnf, sn_tmp_rnf, sn_dep_rnf,   &   
     146         &                 ln_rnf_mouth, ln_rnf_att, rn_hrnf, rn_avt_rnf, rn_rfact   
    127147      !!---------------------------------------------------------------------- 
    128148 
     
    136156      sn_cnf = FLD_N( 'runoffs',     0     , 'sorunoff' ,  .FALSE.   , .true. ,   'yearly'  , ''       , ''         ) 
    137157 
     158      sn_sal_rnf = FLD_N( 'runoffs',  24.  , 'rosaline' ,  .TRUE.    , .true. ,   'yearly'  , ''    , ''  )   
     159      sn_tmp_rnf = FLD_N( 'runoffs',  24.  , 'rotemper' ,  .TRUE.    , .true. ,   'yearly'  , ''    , ''  )   
     160      sn_dep_rnf = FLD_N( 'runoffs',   0.  , 'rodepth'  ,  .FALSE.   , .true. ,   'yearly'  , ''    , ''  )   
    138161      ! 
    139162      REWIND ( numnam )                         ! Read Namelist namsbc_rnf 
     
    160183         IF(lwp) WRITE(numout,*) 
    161184         IF(lwp) WRITE(numout,*) '          runoffs directly provided in the precipitations' 
     185         IF ( ln_rnf_att ) THEN 
     186           CALL ctl_warn( 'runoffs already included in precipitations & so runoff attributes will not be used' )  
     187           ln_rnf_att = .FALSE. 
     188         ENDIF 
    162189         ! 
    163190      ELSE                                      ! runoffs read in a file : set sf_rnf structure  
    164191         ! 
    165          ! sf_rnf already allocated in main routine 
     192         ! Allocate sf_rnf structure and (if required) sf_sal_rnf and sf_tmp_rnf structures 
     193         ALLOCATE( sf_rnf(1), STAT=ierror ) 
     194         IF( ierror > 0 ) THEN 
     195            CALL ctl_stop( 'sbc_rnf: unable to allocate sf_rnf structure' )   ;   RETURN 
     196         ENDIF 
     197         ALLOCATE( sf_rnf(1)%fnow(jpi,jpj) ) 
     198         ALLOCATE( sf_rnf(1)%fdta(jpi,jpj,2) ) 
     199 
     200         IF( ln_rnf_att ) THEN 
     201            ALLOCATE( sf_sal_rnf(1), STAT=ierror ) 
     202            IF( ierror > 0 ) THEN 
     203               CALL ctl_stop( 'sbc_sal_rnf: unable to allocate sf_sal_rnf structure' )   ;   RETURN 
     204            ENDIF 
     205            ALLOCATE( sf_sal_rnf(1)%fnow(jpi,jpj) ) 
     206            ALLOCATE( sf_sal_rnf(1)%fdta(jpi,jpj,2) ) 
     207 
     208            ALLOCATE( sf_tmp_rnf(1), STAT=ierror ) 
     209            IF( ierror > 0 ) THEN 
     210                CALL ctl_stop( 'sbc_tmp_rnf: unable to allocate sf_tmp_rnf structure' )   ;   RETURN 
     211            ENDIF 
     212            ALLOCATE( sf_tmp_rnf(1)%fnow(jpi,jpj) ) 
     213            ALLOCATE( sf_tmp_rnf(1)%fdta(jpi,jpj,2) ) 
     214         ENDIF 
    166215         ! fill sf_rnf with sn_rnf and control print 
    167216         CALL fld_fill( sf_rnf, (/ sn_rnf /), cn_dir, 'sbc_rnf_init', 'read runoffs data', 'namsbc_rnf' ) 
    168          ! 
     217  
     218         IF ( ln_rnf_att ) THEN   
     219            CALL fld_fill (sf_sal_rnf, (/ sn_sal_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff salinity data', 'namsbc_rnf' )   
     220            CALL fld_fill (sf_tmp_rnf, (/ sn_tmp_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff temperature data', 'namsbc_rnf' )   
     221   
     222            rn_dep_file = TRIM( cn_dir )//TRIM( sn_dep_rnf%clname )   
     223            CALL iom_open ( rn_dep_file, inum )                           ! open file   
     224            CALL iom_get  ( inum, jpdom_data, sn_dep_rnf%clvar, rnf_dep )    ! read the river mouth array   
     225            CALL iom_close( inum )                                      ! close file   
     226   
     227            rnf_mod_dep(:,:)=0   
     228            DO jj=1,jpj   
     229              DO ji=1,jpi   
     230                IF ( rnf_dep(ji,jj) > 0.e0 ) THEN   
     231                  jk=2   
     232                  DO WHILE ( jk/=jpkm1 .AND. fsdept(ji,jj,jk) < rnf_dep(ji,jj) );  jk=jk+1;   ENDDO   
     233                  rnf_mod_dep(ji,jj)=jk   
     234                ELSE IF ( rnf_dep(ji,jj) .eq. -1 ) THEN   
     235                  rnf_mod_dep(ji,jj)=1   
     236                ELSE IF ( rnf_dep(ji,jj) .eq. -999 ) THEN   
     237                  rnf_mod_dep(ji,jj)=jpkm1   
     238                ELSE IF ( rnf_dep(ji,jj) /= 0 ) THEN   
     239                  CALL ctl_stop( 'runoff depth not positive, and not -999 or -1, rnf value in file fort.999'  )   
     240                  WRITE(999,*) 'ji, jj, rnf(ji,jj) :', ji, jj, rnf(ji,jj)   
     241                ENDIF   
     242              ENDDO   
     243            ENDDO   
     244         ELSE   
     245            rnf_mod_dep(:,:)=1   
     246         ENDIF   
     247      !  
    169248      ENDIF 
    170249 
     
    179258         ! 
    180259         !                                          ! Number of level over which Kz increase 
     260         IF ( ln_rnf_att )  &   
     261              &  CALL ctl_warn( 'increased mixing turned on but effects may already be spread through depth by ln_rnf_att' )  
    181262         nkrnf = 0 
    182263         IF( rn_hrnf > 0.e0 ) THEN 
Note: See TracChangeset for help on using the changeset viewer.