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 7097 for branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/trcnam.F90 – NEMO

Ignore:
Timestamp:
2016-10-25T17:32:50+02:00 (8 years ago)
Author:
lovato
Message:

New top interface : update my_trc and revise structure of TOP component initialisation, see ticket #1782

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/trcnam.F90

    r7068 r7097  
    3535   PUBLIC trc_nam      ! called in trcini 
    3636 
     37   TYPE(PTRACER), DIMENSION(jpmaxtrc), PUBLIC  :: sn_tracer  ! type of tracer for saving if not key_iomput 
     38 
    3739   !!---------------------------------------------------------------------- 
    3840   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
     
    5860      CALL trc_nam_trc     ! passive tracer informations 
    5961      !                                         
    60       ! 
    6162      IF( ln_rsttr                     )   ln_trcdta     = .FALSE.   ! restart : no need of clim data 
    6263      ! 
     
    8283         ENDIF 
    8384      ENDIF 
    84  
    85        
    86       rdttrc = rdt * FLOAT( nn_dttrc )   ! passive tracer time-step 
    87    
    88       IF(lwp) THEN                   ! control print 
     85      ! 
     86      rdttrc = rdt * FLOAT( nn_dttrc )          ! passive tracer time-step 
     87      !  
     88      IF(lwp) THEN                              ! control print 
    8989        WRITE(numout,*)  
    9090        WRITE(numout,*) '    Passive Tracer  time step    rdttrc  = ', rdttrc 
    9191        WRITE(numout,*)  
    9292      ENDIF 
    93  
    94  
     93      ! 
    9594      IF( l_trdtrc )        CALL trc_nam_trd    ! Passive tracer trends 
    96  
    97                               
    98                             CALL trc_nam_ice  ! ice module for tracerd 
    99  
    100       ! namelist of SMS 
    101       ! ---------------       
    102       IF( ln_age     ) THEN   ;   CALL trc_nam_age         ! AGE     tracer 
    103       ELSE                    ;   IF(lwp) WRITE(numout,*) '          AGE not used' 
    104       ENDIF 
    105  
    106       IF( ll_cfc     ) THEN   ;   CALL trc_nam_cfc         ! CFC     tracers 
    107       ELSE                    ;   IF(lwp) WRITE(numout,*) '          CFC not used' 
    108       ENDIF 
    109  
    110       IF( ln_c14     ) THEN   ;   CALL trc_nam_c14         ! C14     tracers 
    111       ELSE                    ;   IF(lwp) WRITE(numout,*) '          C14 not used' 
    112       ENDIF 
    113  
    114       IF( ln_pisces  ) THEN   ;   CALL trc_nam_pisces      ! PISCES  bio-model 
    115       ELSE                    ;   IF(lwp) WRITE(numout,*) '          PISCES not used' 
    116       ENDIF 
    117  
    118  
    119       IF( ln_my_trc  ) THEN   ;   CALL trc_nam_my_trc      ! MY_TRC  tracers 
    120       ELSE                    ;   IF(lwp) WRITE(numout,*) '          MY_TRC not used' 
    121       ENDIF 
    12295      ! 
    12396   END SUBROUTINE trc_nam 
     
    176149      !! 
    177150      !!--------------------------------------------------------------------- 
    178       INTEGER  ::   ios, ierr, ioptio, icfc     ! Local integer output status for namelist read 
    179       INTEGER  ::   jn                    ! dummy loop indice 
    180       ! 
    181       TYPE(PTRACER), DIMENSION(jpmaxtrc) :: sn_tracer  ! type of tracer for saving if not key_iomput 
    182       TYPE(STRACER), DIMENSION(jpmaxtrc) :: bc_tracer  ! type of tracer for saving if not key_iomput 
     151      INTEGER  ::   ios, ierr, icfc       ! Local integer output status for namelist read 
    183152      !! 
    184153      NAMELIST/namtrc/jptra, ln_pisces, ln_my_trc, ln_age, ln_cfc11, ln_cfc12, ln_c14, & 
    185154         &            sn_tracer, ln_trcdta, ln_trcdmp, ln_trcdmp_clo 
    186155      !!--------------------------------------------------------------------- 
     156      ! Dummy settings to fill tracers data structure 
     157      !                  !   name   !   title   !   unit   !   init  !   sbc   !   cbc   !   obc  ! 
     158      sn_tracer = PTRACER( 'NONAME' , 'NOTITLE' , 'NOUNIT' , .false. , .false. , .false. , .false.) 
     159      ! 
    187160      IF(lwp) WRITE(numout,*) 
    188161      IF(lwp) WRITE(numout,*) 'trc_nam_trc : read the passive tracer namelists' 
    189162      IF(lwp) WRITE(numout,*) '~~~~~~~' 
    190  
    191163 
    192164      REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables 
     
    199171      IF(lwm) WRITE ( numont, namtrc ) 
    200172 
    201       ioptio = 0 
    202       IF( ln_pisces )    ioptio = ioptio + 1 
    203       IF( ln_my_trc )    ioptio = ioptio + 1 
    204       ! 
    205       IF( ioptio == 2 )   CALL ctl_stop( 'Choose only ONE BGC model - PISCES or MY_TRC' ) 
    206       IF( ioptio == 0 )   jptra = 0 
    207  
     173      ! Control settings 
     174      IF( ln_pisces .AND. ln_my_trc )   CALL ctl_stop( 'Choose only ONE BGC model - PISCES or MY_TRC' ) 
     175      IF( .NOT. ln_pisces .AND. .NOT. ln_my_trc )   jptra = 0 
    208176      ll_cfc = ln_cfc11 .OR. ln_cfc12 
    209    
    210177      ! 
    211178      jp_pisces   =  0    ;   jp_pcs0  =  0    ;   jp_pcs1  = 0 
     
    213180      jp_cfc      =  0    ;   jp_cfc0  =  0    ;   jp_cfc1  = 0 
    214181      jp_age      =  0    ;   jp_c14   = 0 
     182      ! 
    215183      IF( ln_pisces )  THEN 
    216184         jp_pisces = jptra 
     
    241209           jp_c14    = jptra 
    242210      ENDIF 
    243  
     211      ! 
     212      IF( jptra == 0 )   CALL ctl_stop( 'All TOP tracers disabled: change namtrc setting or check if key_top is active' ) 
     213      ! 
    244214      IF(lwp) THEN                   ! control print 
    245215         WRITE(numout,*) 
     
    247217         WRITE(numout,*) '   Total number of passive tracers              jptra         = ', jptra 
    248218         WRITE(numout,*) '   Simulating PISCES model                      ln_pisces     = ', ln_pisces 
     219         WRITE(numout,*) '   Simulating MY_TRC  model                     ln_my_trc     = ', ln_my_trc 
    249220         WRITE(numout,*) '   Simulating water mass age                    ln_age        = ', ln_age 
    250221         WRITE(numout,*) '   Simulating CFC11 passive tracer              ln_cfc11      = ', ln_cfc11 
    251222         WRITE(numout,*) '   Simulating CFC12 passive tracer              ln_cfc12      = ', ln_cfc12 
    252223         WRITE(numout,*) '   Simulating C14   passive tracer              ln_c14        = ', ln_c14 
    253          WRITE(numout,*) '   Simulating MY_TRC  model                     ln_my_trc     = ', ln_my_trc 
    254224         WRITE(numout,*) '   Read inputs data from file (y/n)             ln_trcdta     = ', ln_trcdta 
    255225         WRITE(numout,*) '   Damping of passive tracer (y/n)              ln_trcdmp     = ', ln_trcdmp 
    256226         WRITE(numout,*) '   Restoring of tracer on closed seas           ln_trcdmp_clo = ', ln_trcdmp_clo 
     227         WRITE(numout,*) '   Total number of BGC-like tracers             jp_bgc        = ', jp_bgc 
    257228         WRITE(numout,*) ' ' 
    258229         WRITE(numout,*) ' ' 
    259230      ENDIF 
    260231      ! 
    261       ALLOCATE( ctrcnm(jptra)      , ctrcln(jptra) , ctrcun(jptra)       , ln_trc_ini(jptra),          & 
    262 #if defined key_bdy 
    263          &      cn_trc_dflt(nb_bdy), cn_trc(nb_bdy), nn_trcdmp_bdy(nb_bdy), trcdta_bdy(jptra,nb_bdy),  & 
    264 #endif 
    265          &      ln_trc_sbc(jptra), ln_trc_cbc(jptra), ln_trc_obc(jptra), STAT = ierr  ) 
    266       ! 
    267232      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'trc_nam_ice: unable to allocate arrays' ) 
    268       ! 
    269       DO jn = 1, jp_bgc 
    270          ctrcnm    (jn) = TRIM( sn_tracer(jn)%clsname ) 
    271          ctrcln    (jn) = TRIM( sn_tracer(jn)%cllname ) 
    272          ctrcun    (jn) = TRIM( sn_tracer(jn)%clunit  ) 
    273          ln_trc_ini(jn) =       sn_tracer(jn)%llinit 
    274       END DO 
    275       ! 
    276       IF( ln_my_trc ) THEN 
    277          DO jn = 1, jp_bgc 
    278            ln_trc_sbc(jn) =  bc_tracer(jn)%llsbc 
    279            ln_trc_cbc(jn) =  bc_tracer(jn)%llcbc 
    280            ln_trc_obc(jn) =  bc_tracer(jn)%llobc 
    281          END DO 
    282       ENDIF 
    283       ! 
    284       IF(lwp) THEN                   ! control print 
    285          DO jn = 1, jp_bgc 
    286             WRITE(numout,*) '  tracer nb : ', jn, '    short name : ', ctrcnm(jn) 
    287          END DO 
    288          WRITE(numout,*) ' ' 
    289       ENDIF 
    290       ! 
    291233      ! 
    292234      IF( ln_age .OR. ll_cfc .OR. ln_c14 ) THEN 
     
    299241 
    300242   END SUBROUTINE trc_nam_trc 
    301  
    302  
    303    SUBROUTINE trc_nam_ice 
    304       !!--------------------------------------------------------------------- 
    305       !!                     ***  ROUTINE trc_nam_ice *** 
    306       !! 
    307       !! ** Purpose :   Read the namelist for the ice effect on tracers 
    308       !! 
    309       !! ** Method  : - 
    310       !! 
    311       !!--------------------------------------------------------------------- 
    312       INTEGER :: jn      ! dummy loop indices 
    313       INTEGER :: ios, ierr     ! Local integer output status for namelist read 
    314       ! 
    315       TYPE(TRC_I_NML), DIMENSION(jpmaxtrc) :: sn_tri_tracer  ! type of tracer for saving if not key_iomput 
    316       !! 
    317       NAMELIST/namtrc_ice/ nn_ice_tr, sn_tri_tracer 
    318       !!--------------------------------------------------------------------- 
    319       ! 
    320       IF(lwp) THEN 
    321          WRITE(numout,*) 
    322          WRITE(numout,*) 'trc_nam_ice : Read the namelist for trc_ice' 
    323          WRITE(numout,*) '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
    324       ENDIF 
    325  
    326       IF( nn_timing == 1 )  CALL timing_start('trc_nam_ice') 
    327  
    328       ! 
    329       REWIND( numnat_ref )              ! Namelist namtrc_ice in reference namelist : Passive tracer input data 
    330       READ  ( numnat_ref, namtrc_ice, IOSTAT = ios, ERR = 901) 
    331  901  IF( ios /= 0 ) CALL ctl_nam ( ios , ' namtrc_ice in reference namelist ', lwp ) 
    332  
    333       REWIND( numnat_cfg )              ! Namelist namtrc_ice in configuration namelist : Pisces external sources of nutrients 
    334       READ  ( numnat_cfg, namtrc_ice, IOSTAT = ios, ERR = 902 ) 
    335  902  IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ice in configuration namelist', lwp ) 
    336  
    337       IF( lwp ) THEN 
    338          WRITE(numout,*) ' ' 
    339          WRITE(numout,*) ' Sea ice tracers option (nn_ice_tr) : ', nn_ice_tr 
    340          WRITE(numout,*) ' ' 
    341       ENDIF 
    342  
    343       ALLOCATE( trc_ice_ratio(jptra), trc_ice_prescr(jptra), cn_trc_o(jptra), STAT = ierr  ) 
    344       IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'trc_nam_ice: unable to allocate arrays' ) 
    345       ! 
    346       ! Assign namelist stuff 
    347       DO jn = 1, jptra 
    348          trc_ice_ratio (jn) = sn_tri_tracer(jn)%trc_ratio 
    349          trc_ice_prescr(jn) = sn_tri_tracer(jn)%trc_prescr 
    350          cn_trc_o      (jn) = sn_tri_tracer(jn)%ctrc_o 
    351       END DO 
    352  
    353       IF( nn_timing == 1 )   CALL timing_stop('trc_nam_ice') 
    354       ! 
    355    END SUBROUTINE trc_nam_ice 
    356  
    357  
    358243 
    359244   SUBROUTINE trc_nam_trd 
Note: See TracChangeset for help on using the changeset viewer.