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 15574 for NEMO/branches/2021/dev_r14318_RK3_stage1/src/TOP/PISCES/P4Z/p4zbc.F90 – NEMO

Ignore:
Timestamp:
2021-12-03T20:32:50+01:00 (3 years ago)
Author:
techene
Message:

#2605 #2715 trunk merged into dev_r14318_RK3_stage1

Location:
NEMO/branches/2021/dev_r14318_RK3_stage1
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r14318_RK3_stage1

    • Property svn:externals
      •  

        old new  
        99 
        1010# SETTE 
        11 ^/utils/CI/sette@14244        sette 
         11^/utils/CI/sette@HEAD        sette 
         12 
  • NEMO/branches/2021/dev_r14318_RK3_stage1/src/TOP/PISCES/P4Z/p4zbc.F90

    r13295 r15574  
    7171      ! 
    7272      INTEGER  ::  ji, jj, jk, jl  
    73       REAL(wp) ::  zcoef, zyyss 
    74       REAL(wp) ::  zdep, ztrfer, zwdust, zwflux, zrivdin 
     73      REAL(wp) ::  zdep, zwflux, zironice 
     74      REAL(wp) ::  zcoef, zwdust, zrivdin, zdustdep, zndep 
    7575      ! 
    7676      CHARACTER (len=25) :: charout 
    77       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: zirondep 
    78       REAL(wp), ALLOCATABLE, DIMENSION(:,:  ) :: zironice, zndep 
    7977      !!--------------------------------------------------------------------- 
    8078      ! 
    8179      IF( ln_timing )   CALL timing_start('p4z_bc') 
    82       ! 
     80       
     81      ! Add the external input of nutrients from dust deposition in the water column 
     82      ! The inputs at surface have already been added 
     83      ! ---------------------------------------------------------- 
    8384      IF( ll_dust )  THEN 
    84          ALLOCATE(  zirondep(jpi,jpj,jpk) ) 
    8585         ! 
    8686         CALL fld_read( kt, 1, sf_dust ) 
    8787         dust(:,:) = MAX( rtrn, sf_dust(1)%fnow(:,:,1) ) 
    8888         ! 
    89          jl = n_trc_indsbc(jpfer) 
    90          zirondep(:,:,1) = rf_trsfac(jl) * sf_trcsbc(jl)%fnow(:,:,1) / e3t(:,:,1,Kmm) / rn_sbc_time 
    91          !                                              ! Iron solubilization of particles in the water column 
    92          !                                              ! dust in kg/m2/s ---> 1/55.85 to put in mol/Fe ;  wdust in m/j 
    93          zwdust = 0.03 / ( wdust / rday ) / ( 270. * rday ) 
    94          DO jk = 2, jpkm1 
    95             zirondep(:,:,jk) = ( mfrac * dust(:,:) * zwdust / mMass_Fe ) * rfact * EXP( -gdept(:,:,jk,Kmm) / 540. ) 
    96             tr(:,:,jk,jpfer,Krhs) = tr(:,:,jk,jpfer,Krhs) + zirondep(:,:,jk) 
    97             tr(:,:,jk,jppo4,Krhs) = tr(:,:,jk,jppo4,Krhs) + zirondep(:,:,jk) * 0.023 
    98          ENDDO 
     89         ! Iron solubilization of particles in the water column 
     90         ! dust in kg/m2/s ---> 1/55.85 to put in mol/Fe ;  wdust in m/d 
     91         ! Dust are supposed to sink at wdust sinking speed. 3% of the iron  
     92         ! in dust is hypothesized to be soluble at a dissolution rate set to  
     93         ! 1/(250 days). The vertical distribution of iron in dust is computed  
     94         ! from a steady state assumption. Parameters are very uncertain and  
     95         ! are estimated from the literature quoted in Raiswell et al. (2011)  
     96         ! -------------------------------------------------------------------  
     97 
     98         zwdust = 0.03 / ( wdust / rday ) / ( 250. * rday ) 
     99 
     100         ! Atmospheric input of Iron dissolves in the water column 
     101         IF ( ln_trc_sbc(jpfer) ) THEN 
     102            DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 2, jpkm1 ) 
     103               zdustdep = dust(ji,jj) * zwdust * rfact * EXP( -gdept(ji,jj,jk,Kmm) /( 250. * wdust ) ) 
     104               ! 
     105               tr(ji,jj,jk,jpfer,Krhs) = tr(ji,jj,jk,jpfer,Krhs) + zdustdep * mfrac / mMass_Fe  
     106            END_3D 
     107 
     108            IF( lk_iomput ) THEN 
     109                ! surface downward dust depo of iron 
     110                jl = n_trc_indsbc(jpfer) 
     111                CALL iom_put( "Irondep", ( rf_trsfac(jl) * sf_trcsbc(jl)%fnow(:,:,1) / rn_sbc_time ) * 1.e+3 * tmask(:,:,1) ) 
     112 
     113            ENDIF 
     114 
     115         ENDIF 
     116 
     117         ! Atmospheric input of PO4 dissolves in the water column 
     118         IF ( ln_trc_sbc(jppo4) ) THEN 
     119            DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 2, jpkm1 ) 
     120               zdustdep = dust(ji,jj) * zwdust * rfact * EXP( -gdept(ji,jj,jk,Kmm) /( 250. * wdust ) ) 
     121               ! 
     122               tr(ji,jj,jk,jppo4,Krhs) = tr(ji,jj,jk,jppo4,Krhs) + zdustdep * 1.e-3 / mMass_P 
     123            END_3D 
     124         ENDIF 
     125 
     126         ! Atmospheric input of Si dissolves in the water column 
     127         IF ( ln_trc_sbc(jpsil) ) THEN 
     128            DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 2, jpkm1 ) 
     129               zdustdep = dust(ji,jj) * zwdust * rfact * EXP( -gdept(ji,jj,jk,Kmm) /( 250. * wdust ) ) 
     130               ! 
     131               tr(ji,jj,jk,jpsil,Krhs) = tr(ji,jj,jk,jpsil,Krhs) + zdustdep * 0.269 / mMass_Si 
     132            END_3D 
     133         ENDIF 
     134 
    99135         ! 
    100136         IF( lk_iomput ) THEN 
    101              CALL iom_put( "Irondep", zirondep(:,:,1) * 1.e+3 * rfactr * e3t(:,:,1,Kmm) * tmask(:,:,1) ) ! surface downward dust depo of iron 
    102              CALL iom_put( "pdust"  , dust(:,:) / ( wdust * rday ) * tmask(:,:,1) ) ! dust concentration at surface 
    103          ENDIF 
    104          DEALLOCATE( zirondep ) 
    105       ENDIF 
    106  
    107       ! N/P and Si releases due to coastal rivers 
    108       ! Compute river at nit000 or only if there is more than 1 time record in river file 
     137             ! dust concentration at surface 
     138             CALL iom_put( "pdust"  , dust(:,:) / ( wdust / rday ) * tmask(:,:,1) ) ! dust concentration at surface 
     139         ENDIF 
     140      ENDIF 
     141 
    109142      ! ----------------------------------------- 
    110             ! Add the external input of nutrients from river 
     143      ! Add the external input of nutrients from river 
    111144      ! ---------------------------------------------------------- 
    112145      IF( ll_river ) THEN 
    113146          jl = n_trc_indcbc(jpno3) 
    114           DO_2D( 1, 1, 1, 1 ) 
     147          DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    115148             DO jk = 1, nk_rnf(ji,jj) 
    116149                zcoef = rn_rfact / ( e1e2t(ji,jj) * h_rnf(ji,jj) * rn_cbc_time ) * tmask(ji,jj,1) 
     
    124157      ! ---------------------------------------------------------- 
    125158      IF( ll_ndepo ) THEN 
    126          ALLOCATE( zndep(jpi,jpj) ) 
    127159         IF( ln_trc_sbc(jpno3) ) THEN 
    128160            jl = n_trc_indsbc(jpno3) 
    129             zndep(:,:) = rf_trsfac(jl) * sf_trcsbc(jl)%fnow(:,:,1) / e3t(:,:,1,Kmm) / rn_sbc_time 
    130             tr(:,:,1,jptal,Krhs) = tr(:,:,1,jptal,Krhs) - rno3 * zndep(:,:) * rfact 
     161            DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
     162               zndep = rf_trsfac(jl) * sf_trcsbc(jl)%fnow(ji,jj,1) / e3t(ji,jj,1,Kmm) / rn_sbc_time 
     163               tr(ji,jj,1,jptal,Krhs) = tr(ji,jj,1,jptal,Krhs) - rno3 * zndep * rfact 
     164            END_2D 
    131165         ENDIF 
    132166         IF( ln_trc_sbc(jpnh4) ) THEN 
    133167            jl = n_trc_indsbc(jpnh4) 
    134             zndep(:,:) = rf_trsfac(jl) * sf_trcsbc(jl)%fnow(:,:,1) / e3t(:,:,1,Kmm) / rn_sbc_time 
    135             tr(:,:,1,jptal,Krhs) = tr(:,:,1,jptal,Krhs) - rno3 * zndep(:,:) * rfact 
    136          ENDIF 
    137          DEALLOCATE( zndep ) 
    138       ENDIF 
    139       ! 
    140       ! Iron input/uptake due to sea ice : Crude parameterization based on 
    141       ! Lancelot et al. 
     168            DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
     169               zndep = rf_trsfac(jl) * sf_trcsbc(jl)%fnow(ji,jj,1) / e3t(ji,jj,1,Kmm) / rn_sbc_time 
     170               tr(ji,jj,1,jptal,Krhs) = tr(ji,jj,1,jptal,Krhs) + rno3 * zndep * rfact 
     171            END_2D 
     172         ENDIF 
     173      ENDIF 
     174      ! 
     175      ! Iron input/uptake due to sea ice : Crude parameterization based on  
     176      ! Lancelot et al. Iron concentration in sea-ice is constant and set  
     177      ! in the namelist_pisces (icefeinput). ln_ironice is forced to false 
     178      ! when nn_ice_tr = 1 
    142179      ! ---------------------------------------------------- 
    143180      IF( ln_ironice ) THEN 
    144181         ! 
    145          ALLOCATE( zironice(jpi,jpj) ) 
    146          ! 
    147          DO_2D( 1, 1, 1, 1 ) 
    148             zdep    = rfact / e3t(ji,jj,1,Kmm) 
    149             zwflux  = fmmflx(ji,jj) / 1000._wp 
    150             zironice(ji,jj) =  MAX( -0.99 * tr(ji,jj,1,jpfer,Kbb), -zwflux * icefeinput * zdep ) 
     182         ! Compute the iron flux between sea ice and sea water 
     183         ! Simple parameterization assuming a fixed constant concentration in 
     184         ! sea-ice (icefeinput) 
     185         ! ------------------------------------------------------------------          
     186         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
     187            zdep     = rfact / e3t(ji,jj,1,Kmm) 
     188            zwflux   = fmmflx(ji,jj) / 1000._wp 
     189            zironice =  MAX( -0.99 * tr(ji,jj,1,jpfer,Kbb), -zwflux * icefeinput * zdep ) 
     190            tr(ji,jj,1,jpfer,Krhs) = tr(ji,jj,1,jpfer,Krhs) + zironice 
    151191         END_2D 
    152192         ! 
    153          tr(:,:,1,jpfer,Krhs) = tr(:,:,1,jpfer,Krhs) + zironice(:,:) 
    154          ! 
    155          IF( lk_iomput )  CALL iom_put( "Ironice", zironice(:,:) * 1.e+3 * rfactr * e3t(:,:,1,Kmm) * tmask(:,:,1) ) ! iron flux from ice 
    156          ! 
    157          DEALLOCATE( zironice ) 
     193         ! iron flux from ice 
     194         IF( lk_iomput ) & 
     195         & CALL iom_put( "Ironice", MAX( -0.99 * tr(:,:,1,jpfer,Kbb), (-1.*fmmflx(:,:)/1000._wp )*icefeinput*1.e+3*tmask(:,:,1)) ) 
    158196         ! 
    159197      ENDIF 
     
    212250      !! 
    213251      NAMELIST/nampisbc/cn_dir, sn_dust, sn_ironsed, sn_hydrofe, & 
    214         &                ln_ironsed, ln_ironice, ln_hydrofe,    & 
    215         &                sedfeinput, distcoast, icefeinput, wdust, mfrac,  & 
     252        &                ln_ironsed, ln_ironice, ln_hydrofe,     & 
     253        &                sedfeinput, distcoast, icefeinput, wdust, mfrac,   & 
    216254        &                hratio, lgw_rath 
    217255      !!---------------------------------------------------------------------- 
     
    254292      END IF 
    255293 
    256       ll_bc    = ( ln_trcbc .AND. lltrcbc )  .OR. ln_hydrofe .OR. ln_ironsed .OR. ln_ironice 
    257       ll_dust  =  ln_trc_sbc(jpfer)    
     294      ll_bc    = ( ln_trcbc .AND. lltrcbc )  .OR. ln_hydrofe .OR. ln_ironsed .OR. ln_ironice  
     295      ll_dust  =  ln_trc_sbc(jpfer) .OR. ln_trc_sbc(jppo4) .OR. ln_trc_sbc(jpsil) .OR. ln_sediment 
    258296      ll_ndepo =  ln_trc_sbc(jpno3) .OR. ln_trc_sbc(jpnh4)    
    259297      ll_river =  ln_trc_cbc(jpno3)   
     
    269307         ! 
    270308         ALLOCATE( sf_dust(1), STAT=ierr )           !* allocate and fill sf_sst (forcing structure) with sn_sst 
    271          IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'p4z_sed_init: unable to allocate sf_dust structure' ) 
    272          ! 
    273          CALL fld_fill( sf_dust, (/ sn_dust /), cn_dir, 'p4z_sed_init', 'Atmospheric dust deposition', 'nampissed' ) 
     309         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'p4z_bc_init: unable to allocate sf_dust structure' ) 
     310         ! 
     311         CALL fld_fill( sf_dust, (/ sn_dust /), cn_dir, 'p4z_bc_init', 'Atmospheric dust deposition', 'nampisbc' ) 
    274312                                   ALLOCATE( sf_dust(1)%fnow(jpi,jpj,1)   ) 
    275313         IF( sn_dust%ln_tint )     ALLOCATE( sf_dust(1)%fdta(jpi,jpj,1,2) ) 
     
    313351         CALL lbc_lnk( 'p4zbc', zcmask , 'T', 1.0_wp )      ! lateral boundary conditions on cmask   (sign unchanged) 
    314352         ! 
    315          DO_3D( 1, 1, 1, 1, 1, jpk ) 
     353         DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, jpk ) 
    316354            zexpide   = MIN( 8.,( gdept(ji,jj,jk,Kmm) / 500. )**(-1.5) ) 
    317355            zdenitide = -0.9543 + 0.7662 * LOG( zexpide ) - 0.235 * LOG( zexpide )**2 
     
    337375         ! 
    338376         ALLOCATE( sf_hydrofe(1), STAT=ierr )           !* allocate and fill sf_sst (forcing structure) with sn_sst 
    339          IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'p4z_sed_init: unable to allocate sf_hydro structure' ) 
    340          ! 
    341          CALL fld_fill( sf_hydrofe, (/ sn_hydrofe /), cn_dir, 'p4z_sed_init', 'Input of iron from hydrothermal vents', 'nampisbc' ) 
     377         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'p4z_bc_init: unable to allocate sf_hydro structure' ) 
     378         ! 
     379         CALL fld_fill( sf_hydrofe, (/ sn_hydrofe /), cn_dir, 'p4z_bc_init', 'Input of iron from hydrothermal vents', 'nampisbc' ) 
    342380                                   ALLOCATE( sf_hydrofe(1)%fnow(jpi,jpj,jpk)   ) 
    343381         IF( sn_hydrofe%ln_tint )    ALLOCATE( sf_hydrofe(1)%fdta(jpi,jpj,jpk,2) ) 
Note: See TracChangeset for help on using the changeset viewer.