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 10127 for NEMO/trunk/src/TOP/PISCES/P4Z/p4zsbc.F90 – NEMO

Ignore:
Timestamp:
2018-09-13T17:27:54+02:00 (6 years ago)
Author:
cetlod
Message:

Bugfix to allow the use of on-the-fly interpolation for PISCES ancillary data, see ticket #2003

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/TOP/PISCES/P4Z/p4zsbc.F90

    r10111 r10127  
    7575   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   hydrofe          !: Hydrothermal vent supply of iron 
    7676 
    77    REAL(wp), PUBLIC ::   rivalkinput, rivdicinput, nitdepinput, sumdepsi 
    78    REAL(wp), PUBLIC ::   rivdininput, rivdipinput, rivdsiinput 
     77   REAL(wp), PUBLIC :: sedsilfrac, sedcalfrac 
     78   REAL(wp), PUBLIC :: rivalkinput, rivdicinput 
     79   REAL(wp), PUBLIC :: rivdininput, rivdipinput, rivdsiinput 
    7980 
    8081   !! * Substitutions 
     
    110111         IF( kt == nit000 .OR. ( kt /= nit000 .AND. ntimes_dust > 1 ) ) THEN 
    111112            CALL fld_read( kt, 1, sf_dust ) 
    112             IF( nn_ice_tr == -1 .AND. .NOT.ln_ironice ) THEN   ;   dust(:,:) = sf_dust(1)%fnow(:,:,1) 
    113             ELSE                                               ;   dust(:,:) = sf_dust(1)%fnow(:,:,1) * ( 1.-fr_i(:,:) ) 
     113            IF( nn_ice_tr == -1 .AND. .NOT.ln_ironice ) THEN   ;   dust(:,:) = MAX( rtrn, sf_dust(1)%fnow(:,:,1) ) 
     114            ELSE                                               ;   dust(:,:) = MAX( rtrn, sf_dust(1)%fnow(:,:,1) * ( 1.-fr_i(:,:) ) ) 
    114115            ENDIF 
    115116         ENDIF 
     
    174175             zcoef = rno3 * 14E6 * ryyss 
    175176             CALL fld_read( kt, 1, sf_ndepo ) 
    176              nitdep(:,:) = sf_ndepo(1)%fnow(:,:,1) / zcoef / e3t_n(:,:,1)  
     177             nitdep(:,:) = MAX( rtrn, sf_ndepo(1)%fnow(:,:,1) / zcoef / e3t_n(:,:,1) ) 
    177178         ENDIF 
    178179         IF( .NOT.ln_linssh ) THEN 
    179180           zcoef = rno3 * 14E6 * ryyss 
    180            nitdep(:,:) = sf_ndepo(1)%fnow(:,:,1) / zcoef / e3t_n(:,:,1)  
     181           nitdep(:,:) = MAX( rtrn, sf_ndepo(1)%fnow(:,:,1) / zcoef / e3t_n(:,:,1) ) 
    181182         ENDIF 
    182183      ENDIF 
     
    210211      REAL(wp), DIMENSION(nbtimes) :: zsteps                 ! times records 
    211212      REAL(wp), DIMENSION(:), ALLOCATABLE :: rivinput 
    212       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: zdust, zndepo, zriver, zcmask 
     213      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: zriver, zcmask 
    213214      ! 
    214215      CHARACTER(len=100) ::  cn_dir          ! Root directory for location of ssr files 
     
    309310            CALL iom_open (  TRIM( sn_dust%clname ) , numdust ) 
    310311            CALL iom_gettime( numdust, zsteps, kntime=ntimes_dust)  ! get number of record in file 
    311             ALLOCATE( zdust(jpi,jpj,ntimes_dust) ) 
    312             DO jm = 1, ntimes_dust 
    313                CALL iom_get( numdust, jpdom_data, TRIM( sn_dust%clvar ), zdust(:,:,jm), jm ) 
    314             END DO 
    315             CALL iom_close( numdust ) 
    316             ztimes_dust = 1._wp / REAL(ntimes_dust, wp)  
    317             sumdepsi = 0.e0 
    318             DO jm = 1, ntimes_dust 
    319                sumdepsi = sumdepsi + glob_sum( zdust(:,:,jm) * e1e2t(:,:) * tmask(:,:,1) * ztimes_dust ) 
    320             END DO 
    321             sumdepsi = sumdepsi / ( nyear_len(1) * rday ) * 12. * 8.8 * 0.075 * mfrac / 28.1  
    322             DEALLOCATE( zdust) 
    323          ENDIF 
    324       ELSE 
    325          sumdepsi  = 0._wp 
     312         END IF 
    326313      END IF 
    327314 
     
    421408            CALL iom_open ( TRIM( sn_ndepo%clname ), numdepo ) 
    422409            CALL iom_gettime( numdepo, zsteps, kntime=ntimes_ndep) 
    423             ALLOCATE( zndepo(jpi,jpj,ntimes_ndep) ) 
    424             DO jm = 1, ntimes_ndep 
    425                CALL iom_get( numdepo, jpdom_data, TRIM( sn_ndepo%clvar ), zndepo(:,:,jm), jm ) 
    426             END DO 
    427             CALL iom_close( numdepo ) 
    428             ztimes_ndep = 1._wp / REAL(ntimes_ndep, wp)  
    429             nitdepinput = 0._wp 
    430             DO jm = 1, ntimes_ndep 
    431               nitdepinput = nitdepinput + glob_sum( zndepo(:,:,jm) * e1e2t(:,:) * tmask(:,:,1) * ztimes_ndep ) 
    432             ENDDO 
    433             nitdepinput = nitdepinput / rno3 / 14E6  
    434             DEALLOCATE( zndepo) 
    435          ENDIF 
    436       ELSE 
    437          nitdepinput = 0._wp 
     410         ENDIF 
    438411      ENDIF 
    439412 
     
    527500         WRITE(numout,*) '    DIC Supply : ', rivdicinput*1E3*12./1E12     ,' TgC/yr' 
    528501         WRITE(numout,*)  
    529          WRITE(numout,*) '    Total input of elements from atmospheric supply' 
    530          WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
    531          WRITE(numout,*) '    N Supply   : ', nitdepinput*rno3*1E3/1E12*14.,' TgN/yr' 
    532          WRITE(numout,*)  
    533       ENDIF 
     502      ENDIF 
     503      ! 
     504      sedsilfrac = 0.03     ! percentage of silica loss in the sediments 
     505      sedcalfrac = 0.6      ! percentage of calcite loss in the sediments 
    534506      ! 
    535507   END SUBROUTINE p4z_sbc_init 
Note: See TracChangeset for help on using the changeset viewer.