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 5325 for branches – NEMO

Changeset 5325 for branches


Ignore:
Timestamp:
2015-06-01T12:00:26+02:00 (9 years ago)
Author:
aumont
Message:

various bugfixes and code changes

Location:
branches/2015/dev_r5171_CNRS_LIM3_seaicebgc/NEMOGCM/NEMO/TOP_SRC
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5171_CNRS_LIM3_seaicebgc/NEMOGCM/NEMO/TOP_SRC/PISCES/trcice_pisces.F90

    r5195 r5325  
    2020   USE phycst          ! Ocean physics parameters 
    2121   USE sms_pisces      ! PISCES Source Minus Sink variables 
    22    USE p4zsbc 
    2322   USE in_out_manager 
    2423 
     
    5857      !!---------------------------------------------------------------------- 
    5958 
    60       ! --- Variable declarations --- ! 
    61       TYPE TRC_I_NML                    !--- Ice tracer namelist structure 
    62          REAL(wp)         :: trc_ratio  ! ice-ocean trc ratio  
    63          REAL(wp)         :: trc_prescr ! prescribed ice trc cc 
    64          CHARACTER(len=2) :: ctrc_o     ! choice of ocean trc cc 
    65       END TYPE 
    66  
    67                                         !--- Variables extracted from the 
    68                                         !    namelist 
    69       REAL(wp), DIMENSION(24)         :: trc_ice_ratio, & ! ice-ocean tracer ratio 
    70                                          trc_ice_prescr   ! prescribed ice trc cc 
    71       CHARACTER(len=2), DIMENSION(24) :: cn_trc_o ! choice of ocean tracer cc 
    72  
    7359                                        !--- Dummy variables 
    7460      REAL(wp), DIMENSION(jptra,2) & 
     
    8369      !!---------------------------------------------------------------------- 
    8470 
    85       ! --- Namelist declarations --- ! 
    86  
    87       ! Tracer structures for individual tracers 
    88       TYPE(TRC_I_NML) :: sn_tri_dic, sn_tri_doc, sn_tri_tal, sn_tri_oxy, & 
    89                      sn_tri_cal, sn_tri_po4, sn_tri_poc, sn_tri_goc, & 
    90                      sn_tri_bfe, & 
    91                      sn_tri_num, & 
    92                                  sn_tri_sil, sn_tri_dsi, sn_tri_gsi, & 
    93                      sn_tri_phy, sn_tri_dia, sn_tri_zoo, sn_tri_mes, & 
    94                      sn_tri_fer, sn_tri_sfe, sn_tri_dfe, sn_tri_nfe, & 
    95                      sn_tri_nch, sn_tri_dch, sn_tri_no3, sn_tri_nh4 
    96  
    97       
    98       NAMELIST/nampisice/ sn_tri_dic, sn_tri_doc, sn_tri_tal, sn_tri_oxy, & 
    99                           sn_tri_cal, sn_tri_po4, sn_tri_poc, sn_tri_goc, & 
    100                           sn_tri_bfe, & 
    101                           sn_tri_num, & 
    102                                       sn_tri_sil, sn_tri_dsi, sn_tri_gsi, & 
    103                           sn_tri_phy, sn_tri_dia, sn_tri_zoo, sn_tri_mes, & 
    104                           sn_tri_fer, sn_tri_sfe, sn_tri_dfe, sn_tri_nfe, & 
    105                           sn_tri_nch, sn_tri_dch, sn_tri_no3, sn_tri_nh4 
    106  
    107       !!---------------------------------------------------------------------- 
    108  
    10971      IF(lwp) WRITE(numout,*) 
    11072      IF(lwp) WRITE(numout,*) ' trc_ice_ini_pisces: Prescribed sea ice biogeochemistry ' 
    11173      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~' 
    112  
    113       !-------------------------------------------- 
    114       ! Read namelist 
    115       !-------------------------------------------- 
    116  
    117       REWIND( numnatp_ref ) 
    118       READ( numnatp_ref, nampisice ) 
    119  
    120       REWIND( numnatp_cfg ) 
    121       READ( numnatp_cfg, nampisice ) 
    122  
    123       ! Assign namelist stuff 
    124       trc_ice_ratio(jpdic)  = sn_tri_dic%trc_ratio  
    125       trc_ice_prescr(jpdic) = sn_tri_dic%trc_prescr 
    126       cn_trc_o      (jpdic) = sn_tri_dic%ctrc_o 
    127  
    128       trc_ice_ratio(jpdoc)  = sn_tri_doc%trc_ratio  
    129       trc_ice_prescr(jpdoc) = sn_tri_doc%trc_prescr 
    130       cn_trc_o      (jpdoc) = sn_tri_doc%ctrc_o 
    131  
    132       trc_ice_ratio(jptal)  = sn_tri_tal%trc_ratio  
    133       trc_ice_prescr(jptal) = sn_tri_tal%trc_prescr 
    134       cn_trc_o      (jptal) = sn_tri_tal%ctrc_o 
    135  
    136       trc_ice_ratio(jpoxy)  = sn_tri_oxy%trc_ratio  
    137       trc_ice_prescr(jpoxy) = sn_tri_oxy%trc_prescr 
    138       cn_trc_o      (jpoxy) = sn_tri_oxy%ctrc_o 
    139  
    140       trc_ice_ratio(jpcal)  = sn_tri_cal%trc_ratio  
    141       trc_ice_prescr(jpcal) = sn_tri_cal%trc_prescr 
    142       cn_trc_o      (jpcal) = sn_tri_cal%ctrc_o 
    143  
    144       trc_ice_ratio(jppo4)  = sn_tri_po4%trc_ratio  
    145       trc_ice_prescr(jppo4) = sn_tri_po4%trc_prescr 
    146       cn_trc_o      (jppo4) = sn_tri_po4%ctrc_o 
    147  
    148       trc_ice_ratio(jppoc)  = sn_tri_poc%trc_ratio  
    149       trc_ice_prescr(jppoc) = sn_tri_poc%trc_prescr 
    150       cn_trc_o      (jppoc) = sn_tri_poc%ctrc_o 
    151  
    152 #if ! defined key_kriest 
    153       trc_ice_ratio(jpgoc)  = sn_tri_goc%trc_ratio  
    154       trc_ice_prescr(jpgoc) = sn_tri_goc%trc_prescr 
    155       cn_trc_o      (jpgoc) = sn_tri_goc%ctrc_o 
    156  
    157       trc_ice_ratio(jpbfe)  = sn_tri_bfe%trc_ratio  
    158       trc_ice_prescr(jpbfe) = sn_tri_bfe%trc_prescr 
    159       cn_trc_o      (jpbfe) = sn_tri_bfe%ctrc_o 
    160 #else 
    161       trc_ice_ratio(jpnum)  = sn_tri_num%trc_ratio  
    162       trc_ice_prescr(jpnum) = sn_tri_num%trc_prescr 
    163       cn_trc_o      (jpnum) = sn_tri_num%ctrc_o 
    164 #endif 
    165  
    166       trc_ice_ratio(jpsil)  = sn_tri_sil%trc_ratio  
    167       trc_ice_prescr(jpsil) = sn_tri_sil%trc_prescr 
    168       cn_trc_o      (jpsil) = sn_tri_sil%ctrc_o 
    169  
    170       trc_ice_ratio(jpdsi)  = sn_tri_dsi%trc_ratio  
    171       trc_ice_prescr(jpdsi) = sn_tri_dsi%trc_prescr 
    172       cn_trc_o      (jpdsi) = sn_tri_dsi%ctrc_o 
    173  
    174       trc_ice_ratio(jpgsi)  = sn_tri_gsi%trc_ratio  
    175       trc_ice_prescr(jpgsi) = sn_tri_gsi%trc_prescr 
    176       cn_trc_o      (jpgsi) = sn_tri_gsi%ctrc_o 
    177  
    178       trc_ice_ratio(jpphy)  = sn_tri_phy%trc_ratio  
    179       trc_ice_prescr(jpphy) = sn_tri_phy%trc_prescr 
    180       cn_trc_o      (jpphy) = sn_tri_phy%ctrc_o 
    181  
    182       trc_ice_ratio(jpdia)  = sn_tri_dia%trc_ratio  
    183       trc_ice_prescr(jpdia) = sn_tri_dia%trc_prescr 
    184       cn_trc_o      (jpdia) = sn_tri_dia%ctrc_o 
    185  
    186       trc_ice_ratio(jpzoo)  = sn_tri_zoo%trc_ratio  
    187       trc_ice_prescr(jpzoo) = sn_tri_zoo%trc_prescr 
    188       cn_trc_o      (jpzoo) = sn_tri_zoo%ctrc_o 
    189  
    190       trc_ice_ratio(jpmes)  = sn_tri_mes%trc_ratio  
    191       trc_ice_prescr(jpmes) = sn_tri_mes%trc_prescr 
    192       cn_trc_o      (jpmes) = sn_tri_mes%ctrc_o 
    193  
    194       trc_ice_ratio(jpfer)  = sn_tri_fer%trc_ratio  
    195       trc_ice_prescr(jpfer) = sn_tri_fer%trc_prescr 
    196       cn_trc_o      (jpfer) = sn_tri_fer%ctrc_o 
    197  
    198       trc_ice_ratio(jpsfe)  = sn_tri_sfe%trc_ratio  
    199       trc_ice_prescr(jpsfe) = sn_tri_sfe%trc_prescr 
    200       cn_trc_o      (jpsfe) = sn_tri_sfe%ctrc_o 
    201  
    202       trc_ice_ratio(jpdfe)  = sn_tri_dfe%trc_ratio  
    203       trc_ice_prescr(jpdfe) = sn_tri_dfe%trc_prescr 
    204       cn_trc_o      (jpdfe) = sn_tri_dfe%ctrc_o 
    205  
    206       trc_ice_ratio(jpnfe)  = sn_tri_nfe%trc_ratio  
    207       trc_ice_prescr(jpnfe) = sn_tri_nfe%trc_prescr 
    208       cn_trc_o      (jpnfe) = sn_tri_nfe%ctrc_o 
    209  
    210       trc_ice_ratio(jpnch)  = sn_tri_nch%trc_ratio  
    211       trc_ice_prescr(jpnch) = sn_tri_nch%trc_prescr 
    212       cn_trc_o      (jpnch) = sn_tri_nch%ctrc_o 
    213  
    214       trc_ice_ratio(jpdch)  = sn_tri_dch%trc_ratio  
    215       trc_ice_prescr(jpdch) = sn_tri_dch%trc_prescr 
    216       cn_trc_o      (jpdch) = sn_tri_dch%ctrc_o 
    217  
    218       trc_ice_ratio(jpno3)  = sn_tri_no3%trc_ratio  
    219       trc_ice_prescr(jpno3) = sn_tri_no3%trc_prescr 
    220       cn_trc_o      (jpno3) = sn_tri_no3%ctrc_o 
    221  
    222       trc_ice_ratio(jpnh4)  = sn_tri_nh4%trc_ratio  
    223       trc_ice_prescr(jpnh4) = sn_tri_nh4%trc_prescr 
    224       cn_trc_o      (jpnh4) = sn_tri_nh4%ctrc_o 
    22574 
    22675      !-------------------------------------------- 
     
    367216      zrs(2) = zsice_bal / zsoce_bal      !! ice-ocean salinity ratio, Baltic case 
    368217 
    369       DO jn = 1, jptra 
     218      DO jn = jp_pcs0, jp_pcs1 
    370219         IF ( trc_ice_ratio(jn) >= 0._wp )  zratio(jn,:) = trc_ice_ratio(jn) 
    371220         IF ( trc_ice_ratio(jn) == -1._wp ) zratio(jn,:) = zrs(:) 
     
    376225      ! Sea ice tracer concentrations 
    377226      !------------------------------- 
    378       DO jn = 1, jptra 
     227      DO jn = jp_pcs0, jp_pcs1 
    379228         !-- Everywhere but in the Baltic 
    380229         IF ( trc_ice_ratio(jn) >= -1._wp ) THEN !! no prescribed concentration 
     
    391240               WHERE( 14._wp <= glamt(:,:) .AND. glamt(:,:) <= 32._wp .AND.    & 
    392241                      54._wp <= gphit(:,:) .AND. gphit(:,:) <= 66._wp ) 
    393                   trc_i(:,:,jn) = zratio(jn,2) * trc_o(:,:,jn)  
     242                     trc_i(:,:,jn) = zratio(jn,2) * trc_o(:,:,jn)  
    394243               END WHERE 
    395244            ELSE                                 !! prescribed tracer concentration in ice 
    396245               WHERE( 14._wp <= glamt(:,:) .AND. glamt(:,:) <= 32._wp .AND.    & 
    397246                   54._wp <= gphit(:,:) .AND. gphit(:,:) <= 66._wp ) 
    398                   trc_i(:,:,jn) = trc_ice_prescr(jn) 
     247                     trc_i(:,:,jn) = trc_ice_prescr(jn) 
    399248               END WHERE 
    400249            ENDIF ! trc_ice_ratio 
  • branches/2015/dev_r5171_CNRS_LIM3_seaicebgc/NEMOGCM/NEMO/TOP_SRC/TRP/trcsbc.F90

    r5195 r5325  
    2828 
    2929   PUBLIC   trc_sbc   ! routine called by step.F90 
     30 
     31   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:) ::   r2dt  ! vertical profile time-step, = 2 rdttra 
    3032 
    3133   !! * Substitutions 
     
    6365      ! 
    6466      INTEGER  ::   ji, jj, jn                                     ! dummy loop indices 
    65       REAL(wp) ::   zse3t                                          ! temporary scalars 
     67      REAL(wp) ::   zse3t, zrtrn, zratio                           ! temporary scalars 
    6668      REAL(wp) ::   zswitch, zftra, zcd, zdtra, ztfx, ztra         ! temporary scalars 
    6769      CHARACTER (len=22) :: charout 
     
    7678                      CALL wrk_alloc( jpi, jpj,      zsfx   ) 
    7779      IF( l_trdtrc )  CALL wrk_alloc( jpi, jpj, jpk, ztrtrd ) 
     80      ! 
     81      zrtrn = 1.e-15_wp 
    7882 
    7983      SELECT CASE( nn_ice_embd )         ! levitating or embedded sea-ice option 
     
    8286                                         ! (2) embedded sea-ice : salt and volume fluxes and pressure 
    8387      END SELECT 
     88 
     89      IF( ln_top_euler) THEN 
     90         r2dt(:) =  rdttrc(:)              ! = rdttrc (use Euler time stepping) 
     91      ELSE 
     92         IF( neuler == 0 .AND. kt == nittrc000 ) THEN     ! at nittrc000 
     93            r2dt(:) =  rdttrc(:)           ! = rdttrc (restarting with Euler time stepping) 
     94         ELSEIF( kt <= nittrc000 + 1 ) THEN          ! at nittrc000 or nittrc000+1 
     95            r2dt(:) = 2. * rdttrc(:)       ! = 2 rdttrc (leapfrog) 
     96         ENDIF 
     97      ENDIF 
     98 
    8499 
    85100      IF( kt == nittrc000 ) THEN 
     
    99114      ENDIF 
    100115 
    101       WRITE(numout,*) ' trc_sbc initial values', trn(3,2,1,2), trb(3,2,1,2), tra(3,2,1,2) 
    102  
    103116      ! 0. initialization 
    104117      DO jn = 1, jptra 
     
    107120         !                                             ! add the trend to the general tracer trend 
    108121 
    109          IF ( nn_ice_tr == -1 ) THEN  ! identical concentrations in ice and ocean (old code) 
     122         IF ( nn_ice_tr == -1 ) THEN  ! No tracers in sea ice (null concentration in sea ice) 
    110123 
    111124            DO jj = 2, jpj 
    112125               DO ji = fs_2, fs_jpim1   ! vector opt. 
    113126                  zse3t = 1. / fse3t(ji,jj,1) 
    114                   tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + zsfx(ji,jj) * r1_rau0 * trn(ji,jj,1,jn) * zse3t 
     127                  tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + zsfx(ji,jj) * r1_rau0 * trb(ji,jj,1,jn) * zse3t 
    115128               END DO 
    116129            END DO 
     
    131144                  ztfx  = zftra + zswitch * zcd                ! net tracer flux (+C/D if no ice/ocean mass exchange) 
    132145    
    133                   zdtra = r1_rau0 * ( ztfx + zsfx(ji,jj) * trn(ji,jj,1,jn) ) * zse3t 
    134                   tra(ji,jj,1,jn) = MAX( tra(ji,jj,1,jn) + zdtra, 0.) ! avoid integral ocean uptake if freezing (for iron) 
     146                  zdtra = r1_rau0 * ( ztfx + zsfx(ji,jj) * trb(ji,jj,1,jn) ) * zse3t 
     147                  IF ( zdtra < 0. ) THEN 
     148                     zratio = -zdtra * r2dt(1) / ( trb(ji,jj,1,jn) + zrtrn ) 
     149                     zdtra = MIN(1.0, zratio) * zdtra ! avoid negative concentrations to arise 
     150                  ENDIF 
     151                       
     152                  tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + zdtra  
    135153    
    136154               END DO 
  • branches/2015/dev_r5171_CNRS_LIM3_seaicebgc/NEMOGCM/NEMO/TOP_SRC/trc.F90

    r5184 r5325  
    6565   INTEGER             , PUBLIC                                    ::  nittrc000       !: first time step of passive tracers model 
    6666 
     67   !! Information for the ice module for tracers 
     68   !! ------------------------------------------ 
     69   TYPE TRC_I_NML                    !--- Ice tracer namelist structure 
     70         REAL(wp)         :: trc_ratio  ! ice-ocean trc ratio 
     71         REAL(wp)         :: trc_prescr ! prescribed ice trc cc 
     72         CHARACTER(len=2) :: ctrc_o     ! choice of ocean trc cc 
     73   END TYPE 
     74 
     75   REAL(wp), DIMENSION(jptra), PUBLIC         :: trc_ice_ratio, & ! ice-ocean tracer ratio 
     76                                                 trc_ice_prescr   ! prescribed ice trc cc 
     77   CHARACTER(len=2), DIMENSION(jptra), PUBLIC :: cn_trc_o ! choice of ocean tracer cc 
     78 
    6779   !! information for outputs 
    6880   !! -------------------------------------------------- 
  • branches/2015/dev_r5171_CNRS_LIM3_seaicebgc/NEMOGCM/NEMO/TOP_SRC/trcice.F90

    r5193 r5325  
    1616   USE trc             ! passive tracers common variables 
    1717!  USE trcrst          ! passive tracers restart 
    18    USE trcnam          ! Namelist read 
    1918!  USE trcice_cfc      ! CFC      initialisation 
    2019   USE trcice_pisces   ! PISCES   initialisation 
     
    3130   PRIVATE 
    3231    
    33    PUBLIC   trc_ice_ini ! called by trc_init 
     32   PUBLIC   trc_ice_ini ! called by trc_nam 
    3433 
    3534CONTAINS 
     
    3938      !!                     ***  ROUTINE trc_ice_ini *** 
    4039      !! 
    41       !! ** Purpose :   Communication between TOP and sea ice 
     40      !! ** Purpose :   Initialization of the ice module for tracers 
    4241      !! 
    4342      !! ** Method  : -  
    4443      !!             
    4544      !!--------------------------------------------------------------------- 
    46       INTEGER ::   jk, jn, jl    ! dummy loop indices 
    47       INTEGER :: ios                              ! Local integer output status for namelist read 
     45      ! --- Variable declarations --- ! 
    4846 
    49       NAMELIST/namtrc_ice/ nn_ice_tr 
    50       ! 
    5147      IF(lwp) THEN 
    5248         WRITE(numout,*) 
     
    5854 
    5955      ! 
    60       REWIND( numnat_ref )              ! Namelist namtrc_dta in reference namelist : Passive tracer input data 
    61       READ  ( numnat_ref, namtrc_ice, IOSTAT = ios, ERR = 901) 
    62  901  IF( ios /= 0 ) CALL ctl_nam ( ios , ' namtrc_ice in reference namelist ', lwp ) 
    63  
    64       REWIND( numnat_cfg )              ! Namelist nampissbc in configuration namelist : Pisces external sources of nutrients 
    65       READ  ( numnat_cfg, namtrc_ice, IOSTAT = ios, ERR = 902 ) 
    66  902  IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ice in configuration namelist', lwp ) 
    67  
    68       WRITE(numout,*) ' ' 
    69       WRITE(numout,*) ' Sea ice tracers option (nn_ice_tr) : ', nn_ice_tr 
    70       WRITE(numout,*) ' ' 
    71  
    7256      trc_i(:,:,:) = 0.0d0 ! by default 
    7357      trc_o(:,:,:) = 0.0d0 ! by default 
  • branches/2015/dev_r5171_CNRS_LIM3_seaicebgc/NEMOGCM/NEMO/TOP_SRC/trcnam.F90

    r4990 r5325  
    2727   USE trd_oce        
    2828   USE trdtrc_oce 
     29   USE trcnam_ice            ! Ice module for tracers 
    2930   USE iom               ! I/O manager 
    3031 
     
    147148 
    148149 
     150      ! Call the ice module for tracers 
     151      ! ------------------------------- 
     152      CALL trc_nam_ice 
     153 
    149154      ! namelist of SMS 
    150155      ! ---------------       
Note: See TracChangeset for help on using the changeset viewer.