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 9169 for branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsbc.F90 – NEMO

Ignore:
Timestamp:
2017-12-26T17:32:56+01:00 (6 years ago)
Author:
gm
Message:

dev_merge_2017: all SRC: finalize the removal of useless warning when reading namelist_cfg + remove all nn_closea + nn_msh replaced by a logical

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsbc.F90

    r9124 r9169  
    2121   PUBLIC   p4z_sbc_init    
    2222 
    23    LOGICAL , PUBLIC  :: ln_dust     !: boolean for dust input from the atmosphere 
    24    LOGICAL , PUBLIC  :: ln_solub    !: boolean for variable solubility of atmospheric iron 
    25    LOGICAL , PUBLIC  :: ln_river    !: boolean for river input of nutrients 
    26    LOGICAL , PUBLIC  :: ln_ndepo    !: boolean for atmospheric deposition of N 
    27    LOGICAL , PUBLIC  :: ln_ironsed  !: boolean for Fe input from sediments 
    28    LOGICAL , PUBLIC  :: ln_hydrofe  !: boolean for Fe input from hydrothermal vents 
    29    LOGICAL , PUBLIC  :: ln_ironice  !: boolean for Fe input from sea ice 
    30    REAL(wp), PUBLIC  :: sedfeinput  !: Coastal release of Iron 
    31    REAL(wp), PUBLIC  :: dustsolub   !: Solubility of the dust 
    32    REAL(wp), PUBLIC  :: mfrac       !: Mineral Content of the dust 
    33    REAL(wp), PUBLIC  :: icefeinput  !: Iron concentration in sea ice 
    34    REAL(wp), PUBLIC  :: wdust       !: Sinking speed of the dust  
    35    REAL(wp), PUBLIC  :: nitrfix     !: Nitrogen fixation rate    
    36    REAL(wp), PUBLIC  :: diazolight  !: Nitrogen fixation sensitivty to light  
    37    REAL(wp), PUBLIC  :: concfediaz  !: Fe half-saturation Cste for diazotrophs  
    38    REAL(wp)          :: hratio      !: Fe:3He ratio assumed for vent iron supply 
    39    REAL(wp), PUBLIC  :: fep_rats    !: Fep/Fer ratio from sed  sources 
    40    REAL(wp), PUBLIC  :: fep_rath    !: Fep/Fer ratio from hydro sources 
    41    REAL(wp), PUBLIC  :: lgw_rath    !: Weak ligand ratio from hydro sources 
    42  
    43  
    44    LOGICAL , PUBLIC  :: ll_sbc 
    45  
    46    LOGICAL  ::  ll_solub 
     23   LOGICAL , PUBLIC ::   ln_dust      !: boolean for dust input from the atmosphere 
     24   LOGICAL , PUBLIC ::   ln_solub     !: boolean for variable solubility of atmospheric iron 
     25   LOGICAL , PUBLIC ::   ln_river     !: boolean for river input of nutrients 
     26   LOGICAL , PUBLIC ::   ln_ndepo     !: boolean for atmospheric deposition of N 
     27   LOGICAL , PUBLIC ::   ln_ironsed   !: boolean for Fe input from sediments 
     28   LOGICAL , PUBLIC ::   ln_hydrofe   !: boolean for Fe input from hydrothermal vents 
     29   LOGICAL , PUBLIC ::   ln_ironice   !: boolean for Fe input from sea ice 
     30   REAL(wp), PUBLIC ::   sedfeinput   !: Coastal release of Iron 
     31   REAL(wp), PUBLIC ::   dustsolub    !: Solubility of the dust 
     32   REAL(wp), PUBLIC ::   mfrac        !: Mineral Content of the dust 
     33   REAL(wp), PUBLIC ::   icefeinput   !: Iron concentration in sea ice 
     34   REAL(wp), PUBLIC ::   wdust        !: Sinking speed of the dust  
     35   REAL(wp), PUBLIC ::   nitrfix      !: Nitrogen fixation rate    
     36   REAL(wp), PUBLIC ::   diazolight   !: Nitrogen fixation sensitivty to light  
     37   REAL(wp), PUBLIC ::   concfediaz   !: Fe half-saturation Cste for diazotrophs  
     38   REAL(wp)         ::   hratio       !: Fe:3He ratio assumed for vent iron supply 
     39   REAL(wp), PUBLIC ::   fep_rats     !: Fep/Fer ratio from sed  sources 
     40   REAL(wp), PUBLIC ::   fep_rath     !: Fep/Fer ratio from hydro sources 
     41   REAL(wp), PUBLIC ::   lgw_rath     !: Weak ligand ratio from hydro sources 
     42 
     43   LOGICAL , PUBLIC ::   ll_sbc 
     44   LOGICAL          ::   ll_solub 
    4745 
    4846   INTEGER , PARAMETER  :: jpriv  = 7   !: Maximum number of river input fields 
     
    5553   INTEGER , PARAMETER  :: jr_dsi = 7   !: index of dissolved silicate 
    5654 
    57  
    5855   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_dust      ! structure of input dust 
    59    TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_solub      ! structure of input dust 
    60    TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_river  ! structure of input riverdic 
     56   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_solub     ! structure of input dust 
     57   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_river     ! structure of input riverdic 
    6158   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_ndepo     ! structure of input nitrogen deposition 
    6259   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_ironsed   ! structure of input iron from sediment 
    6360   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_hydrofe   ! structure of input iron from hydrothermal vents 
    6461 
    65    INTEGER , PARAMETER :: nbtimes = 365  !: maximum number of times record in a file 
    66    INTEGER  :: ntimes_dust, ntimes_riv, ntimes_ndep       ! number of time steps in a file 
    67    INTEGER  :: ntimes_solub, ntimes_hydro                 ! number of time steps in a file 
    68  
    69    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: dust, solub       !: dust fields 
    70    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdic, rivalk    !: river input fields 
    71    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdin, rivdip    !: river input fields 
    72    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdon, rivdop    !: river input fields 
    73    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdoc    !: river input fields 
    74    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: rivdsi    !: river input fields 
    75    REAL(wp), PUBLIC, ALLOCATABLE, SAVE,   DIMENSION(:,:) :: nitdep    !: atmospheric N deposition  
    76    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: ironsed   !: Coastal supply of iron 
    77    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: hydrofe   !: Hydrothermal vent supply of iron 
    78  
    79    REAL(wp), PUBLIC :: sumdepsi, rivalkinput, rivdicinput, nitdepinput 
    80    REAL(wp), PUBLIC :: rivdininput, rivdipinput, rivdsiinput 
     62   INTEGER , PARAMETER ::   nbtimes = 365                          ! maximum number of times record in a file 
     63   INTEGER             ::   ntimes_dust, ntimes_riv, ntimes_ndep   ! number of time steps in a file 
     64   INTEGER             ::   ntimes_solub, ntimes_hydro             ! number of time steps in a file 
     65 
     66   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   dust  , solub    !: dust fields 
     67   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rivdic, rivalk   !: river input fields 
     68   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rivdin, rivdip   !: river input fields 
     69   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rivdon, rivdop   !: river input fields 
     70   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rivdoc           !: river input fields 
     71   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rivdsi           !: river input fields 
     72   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   nitdep           !: atmospheric N deposition  
     73   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ironsed          !: Coastal supply of iron 
     74   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   hydrofe          !: Hydrothermal vent supply of iron 
     75 
     76   REAL(wp), PUBLIC ::   rivalkinput, rivdicinput, nitdepinput, sumdepsi 
     77   REAL(wp), PUBLIC ::   rivdininput, rivdipinput, rivdsiinput 
    8178 
    8279   !! * Substitutions 
     
    10097      !! 
    10198      !!---------------------------------------------------------------------- 
    102       !! * arguments 
    103       INTEGER, INTENT( in  ) ::   kt   ! ocean time step 
    104  
    105       !! * local declarations 
    106       INTEGER  :: ji,jj  
    107       REAL(wp) :: zcoef, zyyss 
     99      INTEGER, INTENT(in) ::   kt   ! ocean time step 
     100      ! 
     101      INTEGER  ::   ji, jj  
     102      REAL(wp) ::   zcoef, zyyss 
    108103      !!--------------------------------------------------------------------- 
    109104      ! 
    110       IF( ln_timing )  CALL timing_start('p4z_sbc') 
     105      IF( ln_timing )   CALL timing_start('p4z_sbc') 
    111106      ! 
    112107      ! Compute dust at nit000 or only if there is more than 1 time record in dust file 
     
    114109         IF( kt == nit000 .OR. ( kt /= nit000 .AND. ntimes_dust > 1 ) ) THEN 
    115110            CALL fld_read( kt, 1, sf_dust ) 
    116             IF( nn_ice_tr == -1 .AND. .NOT. ln_ironice ) THEN 
    117                dust(:,:) = sf_dust(1)%fnow(:,:,1) 
    118             ELSE 
    119                dust(:,:) = sf_dust(1)%fnow(:,:,1) * ( 1.0 - fr_i(:,:) ) 
     111            IF( nn_ice_tr == -1 .AND. .NOT.ln_ironice ) THEN   ;   dust(:,:) = sf_dust(1)%fnow(:,:,1) 
     112            ELSE                                               ;   dust(:,:) = sf_dust(1)%fnow(:,:,1) * ( 1.-fr_i(:,:) ) 
    120113            ENDIF 
    121114         ENDIF 
    122115      ENDIF 
    123  
     116      ! 
    124117      IF( ll_solub ) THEN 
    125118         IF( kt == nit000 .OR. ( kt /= nit000 .AND. ntimes_solub > 1 ) ) THEN 
     
    205198      !! 
    206199      !!---------------------------------------------------------------------- 
    207       ! 
    208200      INTEGER  :: ji, jj, jk, jm, ifpr 
    209201      INTEGER  :: ii0, ii1, ij0, ij1 
     
    224216      TYPE(FLD_N) ::   sn_riverdoc, sn_riverdic, sn_riverdsi   ! informations about the fields to be read 
    225217      TYPE(FLD_N) ::   sn_riverdin, sn_riverdon, sn_riverdip, sn_riverdop 
    226       ! 
     218      !! 
    227219      NAMELIST/nampissbc/cn_dir, sn_dust, sn_solub, sn_riverdic, sn_riverdoc, sn_riverdin, sn_riverdon,     & 
    228220        &                sn_riverdip, sn_riverdop, sn_riverdsi, sn_ndepo, sn_ironsed, sn_hydrofe, & 
     
    232224      !!---------------------------------------------------------------------- 
    233225      ! 
     226      IF(lwp) THEN 
     227         WRITE(numout,*) 
     228         WRITE(numout,*) 'p4z_sbc_init : initialization of the external sources of nutrients ' 
     229         WRITE(numout,*) '~~~~~~~~~~~~ ' 
     230      ENDIF 
    234231      !                            !* set file information 
    235232      REWIND( numnatp_ref )              ! Namelist nampissbc in reference namelist : Pisces external sources of nutrients 
    236233      READ  ( numnatp_ref, nampissbc, IOSTAT = ios, ERR = 901) 
    237 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampissbc in reference namelist', lwp ) 
    238  
     234901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampissbc in reference namelist', lwp ) 
    239235      REWIND( numnatp_cfg )              ! Namelist nampissbc in configuration namelist : Pisces external sources of nutrients 
    240236      READ  ( numnatp_cfg, nampissbc, IOSTAT = ios, ERR = 902 ) 
    241 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampissbc in configuration namelist', lwp ) 
     237902   IF( ios >  0 )  CALL ctl_nam ( ios , 'nampissbc in configuration namelist', lwp ) 
    242238      IF(lwm) WRITE ( numonp, nampissbc ) 
    243239 
    244       IF ( ( nn_ice_tr >= 0 ) .AND. ln_ironice ) THEN 
     240      IF(lwp) THEN 
     241         WRITE(numout,*) '   Namelist : nampissbc ' 
     242         WRITE(numout,*) '      dust input from the atmosphere           ln_dust     = ', ln_dust 
     243         WRITE(numout,*) '      Variable solubility of iron input        ln_solub    = ', ln_solub 
     244         WRITE(numout,*) '      river input of nutrients                 ln_river    = ', ln_river 
     245         WRITE(numout,*) '      atmospheric deposition of n              ln_ndepo    = ', ln_ndepo 
     246         WRITE(numout,*) '      Fe input from sediments                  ln_ironsed  = ', ln_ironsed 
     247         WRITE(numout,*) '      Fe input from seaice                     ln_ironice  = ', ln_ironice 
     248         WRITE(numout,*) '      fe input from hydrothermal vents         ln_hydrofe  = ', ln_hydrofe 
     249         WRITE(numout,*) '      coastal release of iron                  sedfeinput  = ', sedfeinput 
     250         WRITE(numout,*) '      solubility of the dust                   dustsolub   = ', dustsolub 
     251         WRITE(numout,*) '      Mineral Fe content of the dust           mfrac       = ', mfrac 
     252         WRITE(numout,*) '      Iron concentration in sea ice            icefeinput  = ', icefeinput 
     253         WRITE(numout,*) '      sinking speed of the dust                wdust       = ', wdust 
     254         WRITE(numout,*) '      nitrogen fixation rate                   nitrfix     = ', nitrfix 
     255         WRITE(numout,*) '      nitrogen fixation sensitivty to light    diazolight  = ', diazolight 
     256         WRITE(numout,*) '      Fe half-saturation cste for diazotrophs  concfediaz  = ', concfediaz 
     257         WRITE(numout,*) '      Fe to 3He ratio assumed for vent iron supply hratio  = ', hratio 
     258         IF( ln_ligand ) THEN 
     259            WRITE(numout,*) '      Fep/Fer ratio from sed sources            fep_rats   = ', fep_rats 
     260            WRITE(numout,*) '      Fep/Fer ratio from sed hydro sources      fep_rath   = ', fep_rath 
     261            WRITE(numout,*) '      Weak ligand ratio from sed hydro sources  lgw_rath   = ', lgw_rath 
     262         ENDIF 
     263      END IF 
     264 
     265      IF( nn_ice_tr >= 0 .AND. ln_ironice ) THEN 
    245266         IF(lwp) THEN 
    246             WRITE(numout,*) ' ln_ironice incompatible with nn_ice_tr = ', nn_ice_tr 
    247             WRITE(numout,*) ' Specify your sea ice iron concentration in nampisice instead ' 
    248             WRITE(numout,*) ' ln_ironice is forced to .FALSE. ' 
    249             ln_ironice = .FALSE. 
    250          ENDIF 
    251       ENDIF 
    252  
    253       IF(lwp) THEN 
    254          WRITE(numout,*) ' ' 
    255          WRITE(numout,*) ' namelist : nampissbc ' 
    256          WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~ ' 
    257          WRITE(numout,*) '    dust input from the atmosphere           ln_dust     = ', ln_dust 
    258          WRITE(numout,*) '    Variable solubility of iron input        ln_solub    = ', ln_solub 
    259          WRITE(numout,*) '    river input of nutrients                 ln_river    = ', ln_river 
    260          WRITE(numout,*) '    atmospheric deposition of n              ln_ndepo    = ', ln_ndepo 
    261          WRITE(numout,*) '    Fe input from sediments                  ln_ironsed  = ', ln_ironsed 
    262          WRITE(numout,*) '    Fe input from seaice                     ln_ironice  = ', ln_ironice 
    263          WRITE(numout,*) '    fe input from hydrothermal vents         ln_hydrofe  = ', ln_hydrofe 
    264          WRITE(numout,*) '    coastal release of iron                  sedfeinput  = ', sedfeinput 
    265          WRITE(numout,*) '    solubility of the dust                   dustsolub   = ', dustsolub 
    266          WRITE(numout,*) '    Mineral Fe content of the dust           mfrac       = ', mfrac 
    267          WRITE(numout,*) '    Iron concentration in sea ice            icefeinput  = ', icefeinput 
    268          WRITE(numout,*) '    sinking speed of the dust                wdust       = ', wdust 
    269          WRITE(numout,*) '    nitrogen fixation rate                   nitrfix     = ', nitrfix 
    270          WRITE(numout,*) '    nitrogen fixation sensitivty to light    diazolight  = ', diazolight 
    271          WRITE(numout,*) '    fe half-saturation cste for diazotrophs  concfediaz  = ', concfediaz 
    272          WRITE(numout,*) '    Fe to 3He ratio assumed for vent iron supply hratio  = ', hratio 
    273          IF( ln_ligand ) THEN 
    274             WRITE(numout,*) '    Fep/Fer ratio from sed sources            fep_rats   = ', fep_rats 
    275             WRITE(numout,*) '    Fep/Fer ratio from sed hydro sources      fep_rath   = ', fep_rath 
    276             WRITE(numout,*) '    Weak ligand ratio from sed hydro sources  lgw_rath   = ', lgw_rath 
    277          ENDIF 
    278       END IF 
    279  
    280       IF( ln_dust .OR. ln_river .OR. ln_ndepo ) THEN  ;  ll_sbc = .TRUE. 
    281       ELSE                                            ;  ll_sbc = .FALSE. 
    282       ENDIF 
    283  
    284       IF( ln_dust .AND. ln_solub ) THEN               ;  ll_solub = .TRUE. 
    285       ELSE                                            ;  ll_solub = .FALSE. 
     267            WRITE(numout,*) '   ==>>>   ln_ironice incompatible with nn_ice_tr = ', nn_ice_tr 
     268            WRITE(numout,*) '           Specify your sea ice iron concentration in nampisice instead ' 
     269            WRITE(numout,*) '           ln_ironice is forced to .FALSE. ' 
     270         ENDIF 
     271         ln_ironice = .FALSE. 
     272      ENDIF 
     273 
     274      IF( ln_dust .OR. ln_river .OR. ln_ndepo ) THEN   ;   ll_sbc = .TRUE. 
     275      ELSE                                             ;   ll_sbc = .FALSE. 
     276      ENDIF 
     277 
     278      IF( ln_dust .AND. ln_solub ) THEN                ;   ll_solub = .TRUE. 
     279      ELSE                                             ;   ll_solub = .FALSE. 
    286280      ENDIF 
    287281 
     
    322316            DO jm = 1, ntimes_dust 
    323317               sumdepsi = sumdepsi + glob_sum( zdust(:,:,jm) * e1e2t(:,:) * tmask(:,:,1) * ztimes_dust ) 
    324             ENDDO 
     318            END DO 
    325319            sumdepsi = sumdepsi / ( nyear_len(1) * rday ) * 12. * 8.8 * 0.075 * mfrac / 28.1  
    326320            DEALLOCATE( zdust) 
     
    335329      IF( ll_solub ) THEN 
    336330         ! 
    337          IF(lwp) WRITE(numout,*) '    initialize variable solubility of Fe ' 
    338          IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' 
     331         IF(lwp) WRITE(numout,*) 
     332         IF(lwp) WRITE(numout,*) '   ==>>>   ll_solub=T , initialize variable solubility of Fe ' 
    339333         ! 
    340334         ALLOCATE( solub(jpi,jpj) )    ! allocation 
     
    356350      IF( ln_river ) THEN 
    357351         ! 
    358          slf_river(jr_dic) = sn_riverdic  ;  slf_river(jr_doc) = sn_riverdoc  ;  slf_river(jr_din) = sn_riverdin  
    359          slf_river(jr_don) = sn_riverdon  ;  slf_river(jr_dip) = sn_riverdip  ;  slf_river(jr_dop) = sn_riverdop 
     352         slf_river(jr_dic) = sn_riverdic   ;   slf_river(jr_doc) = sn_riverdoc   ;   slf_river(jr_din) = sn_riverdin  
     353         slf_river(jr_don) = sn_riverdon   ;   slf_river(jr_dip) = sn_riverdip   ;   slf_river(jr_dop) = sn_riverdop 
    360354         slf_river(jr_dsi) = sn_riverdsi   
    361355         ! 
     
    363357         IF( ln_p5z )  ALLOCATE( rivdon(jpi,jpj), rivdop(jpi,jpj), rivdoc(jpi,jpj) ) 
    364358         ! 
    365          ALLOCATE( sf_river(jpriv), rivinput(jpriv), STAT=ierr1 )           !* allocate and fill sf_river (forcing structure) with sn_river_ 
    366          rivinput(:) = 0.0 
     359         ALLOCATE( sf_river(jpriv), rivinput(jpriv), STAT=ierr1 )    !* allocate and fill sf_river (forcing structure) with sn_river_ 
     360         rivinput(:) = 0._wp 
    367361 
    368362         IF( ierr1 > 0 )   CALL ctl_stop( 'STOP', 'p4z_sed_init: unable to allocate sf_irver structure' ) 
     
    409403      IF( ln_ndepo ) THEN 
    410404         ! 
    411          IF(lwp) WRITE(numout,*) '    initialize the nutrient input by dust from ndeposition.orca.nc' 
    412          IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
     405         IF(lwp) WRITE(numout,*) 
     406         IF(lwp) WRITE(numout,*) '   ==>>>   ln_ndepo=T , initialize the nutrient input by dust from NetCDF file' 
    413407         ! 
    414408         ALLOCATE( nitdep(jpi,jpj) )    ! allocation 
     
    446440      IF( ln_ironsed ) THEN      
    447441         ! 
    448          IF(lwp) WRITE(numout,*) '    computation of an island mask to enhance coastal supply of iron' 
    449          IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
     442         IF(lwp) WRITE(numout,*) 
     443         IF(lwp) WRITE(numout,*) '   ==>>>   ln_ironsed=T , computation of an island mask to enhance coastal supply of iron' 
    450444         ! 
    451445         ALLOCATE( ironsed(jpi,jpj,jpk) )    ! allocation 
     
    458452         ik50 = 5        !  last level where depth less than 50 m 
    459453         DO jk = jpkm1, 1, -1 
    460             IF( gdept_1d(jk) > 50. )  ik50 = jk - 1 
     454            IF( gdept_1d(jk) > 50. )   ik50 = jk - 1 
    461455         END DO 
    462          IF (lwp) WRITE(numout,*) 
    463          IF (lwp) WRITE(numout,*) ' Level corresponding to 50m depth ',  ik50,' ', gdept_1d(ik50+1) 
    464          IF (lwp) WRITE(numout,*) 
     456         IF(lwp) WRITE(numout,*) 
     457         IF(lwp) WRITE(numout,*) ' Level corresponding to 50m depth ',  ik50,' ', gdept_1d(ik50+1) 
    465458         DO jk = 1, ik50 
    466459            DO jj = 2, jpjm1 
     
    499492      IF( ln_hydrofe ) THEN 
    500493         ! 
    501          IF(lwp) WRITE(numout,*) '    Input of iron from hydrothermal vents ' 
    502          IF(lwp) WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
     494         IF(lwp) WRITE(numout,*) 
     495         IF(lwp) WRITE(numout,*) '   ==>>>   ln_hydrofe=T , Input of iron from hydrothermal vents' 
    503496         ! 
    504497         ALLOCATE( hydrofe(jpi,jpj,jpk) )    ! allocation 
     
    521514         WRITE(numout,*) '    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
    522515         WRITE(numout,*) '    N Supply   : ', rivdininput*rno3*1E3/1E12*14.,' TgN/yr' 
    523          WRITE(numout,*) '    Si Supply  : ', rivdsiinput*1E3/1E12*28.1,' TgSi/yr' 
     516         WRITE(numout,*) '    Si Supply  : ', rivdsiinput*1E3/1E12*28.1    ,' TgSi/yr' 
    524517         WRITE(numout,*) '    P Supply   : ', rivdipinput*1E3*po4r/1E12*31.,' TgP/yr' 
    525          WRITE(numout,*) '    Alk Supply : ', rivalkinput*1E3/1E12,' Teq/yr' 
    526          WRITE(numout,*) '    DIC Supply : ', rivdicinput*1E3*12./1E12,'TgC/yr' 
     518         WRITE(numout,*) '    Alk Supply : ', rivalkinput*1E3/1E12         ,' Teq/yr' 
     519         WRITE(numout,*) '    DIC Supply : ', rivdicinput*1E3*12./1E12     ,' TgC/yr' 
    527520         WRITE(numout,*)  
    528521         WRITE(numout,*) '    Total input of elements from atmospheric supply' 
Note: See TracChangeset for help on using the changeset viewer.