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 4152 for branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/TOP_SRC/trcnam.F90 – NEMO

Ignore:
Timestamp:
2013-11-05T12:59:53+01:00 (10 years ago)
Author:
cetlod
Message:

merge in dev_LOCEAN_2013 the 2nd development branch dev_r3940_CNRS4_IOCRS, see ticket #1169

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/TOP_SRC/trcnam.F90

    r4148 r4152  
    3232   PRIVATE  
    3333 
     34   PUBLIC trc_nam_run  ! called in trcini 
    3435   PUBLIC trc_nam      ! called in trcini 
    3536 
     
    4445CONTAINS 
    4546 
     47 
    4648   SUBROUTINE trc_nam 
    4749      !!--------------------------------------------------------------------- 
     
    5456      !!                ( (PISCES, CFC, MY_TRC ) 
    5557      !!--------------------------------------------------------------------- 
    56       INTEGER ::  jn, ierr 
    57       INTEGER ::  ios                 ! Local integer output status for namelist read 
    58       ! Definition of a tracer as a structure 
    59       TYPE(PTRACER), DIMENSION(jptra) :: sn_tracer  ! type of tracer for saving if not key_iomput 
    60       !! 
    61       NAMELIST/namtrc/ nn_dttrc, nn_writetrc, ln_rsttr, nn_rsttr, & 
    62          &             cn_trcrst_in, cn_trcrst_out, sn_tracer, ln_trcdta, & 
    63          &             ln_trcdmp, ln_trcdmp_clo, ln_top_euler 
    64 #if defined key_trdmld_trc  || defined key_trdtrc 
    65       NAMELIST/namtrc_trd/ nn_trd_trc, nn_ctls_trc, rn_ucf_trc, & 
    66          &                ln_trdmld_trc_restart, ln_trdmld_trc_instant, & 
    67          &                cn_trdrst_trc_in, cn_trdrst_trc_out, ln_trdtrc 
    68 #endif 
    69       NAMELIST/namtrc_dia/ ln_diatrc, ln_diabio, nn_writedia, nn_writebio 
    70  
    71       !!--------------------------------------------------------------------- 
    72  
    73       IF(lwp) WRITE(numout,*) 'trc_nam : read the passive tracer namelists' 
    74       IF(lwp) WRITE(numout,*) '~~~~~~~' 
    75  
    76       CALL ctl_opn( numnat_ref, 'namelist_top_ref'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', 1, numout, .FALSE. ) 
    77       CALL ctl_opn( numnat_cfg, 'namelist_top_cfg'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', 1, numout, .FALSE. ) 
    78       CALL ctl_opn( numont    , 'output.namelist.top', 'REPLACE', 'FORMATTED', 'SEQUENTIAL',-1, numout, .FALSE. ) 
    79  
    80       REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables 
    81       READ  ( numnat_ref, namtrc, IOSTAT = ios, ERR = 901) 
    82 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp ) 
    83  
    84       REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables 
    85       READ  ( numnat_cfg, namtrc, IOSTAT = ios, ERR = 902 ) 
    86 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp ) 
    87       WRITE ( numont, namtrc ) 
    88  
    89       DO jn = 1, jptra 
    90          ctrcnm    (jn) = TRIM( sn_tracer(jn)%clsname ) 
    91          ctrcln    (jn) = TRIM( sn_tracer(jn)%cllname ) 
    92          ctrcun    (jn) = TRIM( sn_tracer(jn)%clunit  ) 
    93          ln_trc_ini(jn) =       sn_tracer(jn)%llinit 
    94          ln_trc_wri(jn) =       sn_tracer(jn)%llsave 
    95       END DO 
    96  
    97       !!KPE  computes the first time step of tracer model 
    98       nittrc000 = nit000 + nn_dttrc - 1 
    99   
    100  
    101       IF(lwp) THEN                   ! control print 
     58      !                                        !   Parameters of the run  
     59      IF( .NOT. lk_offline ) CALL trc_nam_run 
     60       
     61      !                                        !  passive tracer informations 
     62      CALL trc_nam_trc 
     63       
     64      !                                        !   Parameters of additional diagnostics 
     65      CALL trc_nam_dia 
     66 
     67      !                                        !   namelist of transport 
     68      CALL trc_nam_trp 
     69 
     70 
     71      IF( ln_rsttr )                      ln_trcdta = .FALSE.   ! restart : no need of clim data 
     72      ! 
     73      IF( ln_trcdmp .OR. ln_trcdmp_clo )  ln_trcdta = .TRUE.   ! damping : need to have clim data 
     74      ! 
     75      IF( .NOT.ln_trcdta ) THEN 
     76         ln_trc_ini(:) = .FALSE. 
     77      ENDIF 
     78 
     79     IF(lwp) THEN                   ! control print 
    10280         WRITE(numout,*) 
    10381         WRITE(numout,*) ' Namelist : namtrc' 
    104          WRITE(numout,*) '   time step freq. for passive tracer           nn_dttrc      = ', nn_dttrc 
    105          WRITE(numout,*) '   restart  for passive tracer                  ln_rsttr      = ', ln_rsttr 
    106          WRITE(numout,*) '   control of time step for passive tracer      nn_rsttr      = ', nn_rsttr 
    107          WRITE(numout,*) '   first time step for pass. trac.              nittrc000     = ', nittrc000 
    108          WRITE(numout,*) '   frequency of outputs for passive tracers     nn_writetrc   = ', nn_writetrc   
    10982         WRITE(numout,*) '   Read inputs data from file (y/n)             ln_trcdta     = ', ln_trcdta 
    11083         WRITE(numout,*) '   Damping of passive tracer (y/n)              ln_trcdmp     = ', ln_trcdmp 
    11184         WRITE(numout,*) '   Restoring of tracer on closed seas           ln_trcdmp_clo = ', ln_trcdmp_clo 
    112          WRITE(numout,*) '   Use euler integration for TRC (y/n)          ln_top_euler  = ', ln_top_euler 
    11385         WRITE(numout,*) ' ' 
    11486         DO jn = 1, jptra 
     
    11890      ENDIF 
    11991 
     92      IF(lwp) THEN                   ! control print 
     93         IF( ln_rsttr ) THEN 
     94            WRITE(numout,*) 
     95            WRITE(numout,*) '  Read a restart file for passive tracer : ', TRIM( cn_trcrst_in ) 
     96            WRITE(numout,*) 
     97         ENDIF 
     98         IF( ln_trcdta .AND. .NOT.ln_rsttr ) THEN 
     99            WRITE(numout,*) 
     100            WRITE(numout,*) '  Some of the passive tracers are initialised from climatologies ' 
     101            WRITE(numout,*) 
     102         ENDIF 
     103         IF( .NOT.ln_trcdta ) THEN 
     104            WRITE(numout,*) 
     105            WRITE(numout,*) '  All the passive tracers are initialised with constant values ' 
     106            WRITE(numout,*) 
     107         ENDIF 
     108      ENDIF 
     109 
     110       
    120111      rdttrc(:) = rdttra(:) * FLOAT( nn_dttrc )   ! vertical profile of passive tracer time-step 
    121112   
     
    124115        WRITE(numout,*) '    Passive Tracer  time step    rdttrc  = ', rdttrc(1) 
    125116        WRITE(numout,*)  
    126       ENDIF 
    127  
    128       REWIND( numnat_ref )              ! Namelist namtrc_dia in reference namelist : Passive tracer diagnostics 
    129       READ  ( numnat_ref, namtrc_dia, IOSTAT = ios, ERR = 903) 
    130 903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in reference namelist', lwp ) 
    131  
    132       REWIND( numnat_cfg )              ! Namelist namtrc_dia in configuration namelist : Passive tracer diagnostics 
    133       READ  ( numnat_cfg, namtrc_dia, IOSTAT = ios, ERR = 904 ) 
    134 904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in configuration namelist', lwp ) 
    135       WRITE ( numont, namtrc_dia ) 
    136  
    137       IF(lwp) THEN 
    138          WRITE(numout,*) 
    139          WRITE(numout,*) 
    140          WRITE(numout,*) ' Namelist : namtrc_dia' 
    141          WRITE(numout,*) '    save additionnal diagnostics arrays         ln_diatrc   = ', ln_diatrc 
    142          WRITE(numout,*) '    save additionnal biology diagnostics arrays ln_diabio   = ', ln_diabio 
    143          WRITE(numout,*) '    frequency of outputs for additional arrays  nn_writedia = ', nn_writedia 
    144          WRITE(numout,*) '    frequency of outputs for biological trends  nn_writebio = ', nn_writebio 
    145          WRITE(numout,*) ' ' 
    146       ENDIF 
    147  
    148       IF( ln_diatrc .AND. .NOT. lk_iomput ) THEN  
    149          ALLOCATE( trc2d(jpi,jpj,jpdia2d), trc3d(jpi,jpj,jpk,jpdia3d),  & 
    150            &       ctrc2d(jpdia2d), ctrc2l(jpdia2d), ctrc2u(jpdia2d) ,  &  
    151            &       ctrc3d(jpdia3d), ctrc3l(jpdia3d), ctrc3u(jpdia3d) ,  STAT = ierr )  
    152          IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate add. diag. array' ) 
    153          ! 
    154          trc2d(:,:,:  ) = 0._wp  ;   ctrc2d(:) = ' '   ;   ctrc2l(:) = ' '    ;    ctrc2u(:) = ' '  
    155          trc3d(:,:,:,:) = 0._wp  ;   ctrc3d(:) = ' '   ;   ctrc3l(:) = ' '    ;    ctrc3u(:) = ' '  
    156          ! 
    157       ENDIF 
    158  
    159       IF( ( ln_diabio .AND. .NOT. lk_iomput ) .OR. l_trdtrc ) THEN 
    160          ALLOCATE( trbio (jpi,jpj,jpk,jpdiabio) , & 
    161            &       ctrbio(jpdiabio), ctrbil(jpdiabio), ctrbiu(jpdiabio), STAT = ierr )  
    162          IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate bio. diag. array' ) 
    163          ! 
    164          trbio(:,:,:,:) = 0._wp  ;   ctrbio(:) = ' '   ;   ctrbil(:) = ' '    ;    ctrbiu(:) = ' '  
    165          ! 
    166       ENDIF 
    167  
    168       ! namelist of transport 
    169       ! --------------------- 
    170       CALL trc_nam_trp 
    171  
    172  
    173       IF( ln_rsttr )                      ln_trcdta = .FALSE.   ! restart : no need of clim data 
    174       ! 
    175       IF( ln_trcdmp .OR. ln_trcdmp_clo )  ln_trcdta = .TRUE.   ! damping : need to have clim data 
    176       ! 
    177       IF( .NOT.ln_trcdta ) THEN 
    178          ln_trc_ini(:) = .FALSE. 
    179       ENDIF 
    180  
    181       IF(lwp) THEN                   ! control print 
    182          IF( ln_rsttr ) THEN 
    183             WRITE(numout,*) 
    184             WRITE(numout,*) '  Read a restart file for passive tracer : ', TRIM( cn_trcrst_in ) 
    185             WRITE(numout,*) 
    186          ENDIF 
    187          IF( ln_trcdta .AND. .NOT.ln_rsttr ) THEN 
    188             WRITE(numout,*) 
    189             WRITE(numout,*) '  Some of the passive tracers are initialised from climatologies ' 
    190             WRITE(numout,*) 
    191          ENDIF 
    192          IF( .NOT.ln_trcdta ) THEN 
    193             WRITE(numout,*) 
    194             WRITE(numout,*) '  All the passive tracers are initialised with constant values ' 
    195             WRITE(numout,*) 
    196          ENDIF 
    197117      ENDIF 
    198118 
     
    246166   END SUBROUTINE trc_nam 
    247167 
     168   SUBROUTINE trc_nam_run 
     169      !!--------------------------------------------------------------------- 
     170      !!                     ***  ROUTINE trc_nam  *** 
     171      !! 
     172      !! ** Purpose :   read options for the passive tracer run (namelist)  
     173      !! 
     174      !!--------------------------------------------------------------------- 
     175      NAMELIST/namtrc_run/ nn_dttrc, nn_writetrc, ln_rsttr, nn_rsttr, ln_top_euler, & 
     176        &                  cn_trcrst_in, cn_trcrst_out 
     177 
     178      !!--------------------------------------------------------------------- 
     179 
     180 
     181      IF(lwp) WRITE(numout,*) 'trc_nam : read the passive tracer namelists' 
     182      IF(lwp) WRITE(numout,*) '~~~~~~~' 
     183 
     184      CALL ctl_opn( numnat_ref, 'namelist_top_ref'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', 1, numout, .FALSE. ) 
     185      CALL ctl_opn( numnat_cfg, 'namelist_top_cfg'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', 1, numout, .FALSE. ) 
     186      CALL ctl_opn( numont    , 'output.namelist.top', 'REPLACE', 'FORMATTED', 'SEQUENTIAL',-1, numout, .FALSE. ) 
     187 
     188      REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables 
     189      READ  ( numnat_ref, namtrc_run, IOSTAT = ios, ERR = 901) 
     190901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp ) 
     191 
     192      REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables 
     193      READ  ( numnat_cfg, namtrc_run, IOSTAT = ios, ERR = 902 ) 
     194902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp ) 
     195      WRITE ( numont, namtrc ) 
     196 
     197      !  computes the first time step of tracer model 
     198      nittrc000 = nit000 + nn_dttrc - 1 
     199 
     200      IF(lwp) THEN                   ! control print 
     201         WRITE(numout,*) 
     202         WRITE(numout,*) ' Namelist : namtrc' 
     203         WRITE(numout,*) '   time step freq. for passive tracer           nn_dttrc      = ', nn_dttrc 
     204         WRITE(numout,*) '   restart  for passive tracer                  ln_rsttr      = ', ln_rsttr 
     205         WRITE(numout,*) '   control of time step for passive tracer      nn_rsttr      = ', nn_rsttr 
     206         WRITE(numout,*) '   first time step for pass. trac.              nittrc000     = ', nittrc000 
     207         WRITE(numout,*) '   frequency of outputs for passive tracers     nn_writetrc   = ', nn_writetrc   
     208         WRITE(numout,*) ' ' 
     209      ENDIF 
     210      ! 
     211    END SUBROUTINE trc_nam_run 
     212 
     213 
     214   SUBROUTINE trc_nam_trc 
     215      !!--------------------------------------------------------------------- 
     216      !!                     ***  ROUTINE trc_nam  *** 
     217      !! 
     218      !! ** Purpose :   read options for the passive tracer run (namelist)  
     219      !! 
     220      !!--------------------------------------------------------------------- 
     221      INTEGER ::  jn 
     222      ! Definition of a tracer as a structure 
     223      TYPE(PTRACER), DIMENSION(jptra) :: sn_tracer  ! type of tracer for saving if not key_iomput 
     224      !! 
     225      NAMELIST/namtrc/ sn_tracer, ln_trcdta,ln_trcdmp, ln_trcdmp_clo 
     226 
     227      !!--------------------------------------------------------------------- 
     228      IF(lwp) WRITE(numout,*) 
     229      IF(lwp) WRITE(numout,*) 'trc_nam : read the passive tracer namelists' 
     230      IF(lwp) WRITE(numout,*) '~~~~~~~' 
     231 
     232 
     233      REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables 
     234      READ  ( numnat_ref, namtrc, IOSTAT = ios, ERR = 901) 
     235901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp ) 
     236 
     237      REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables 
     238      READ  ( numnat_cfg, namtrc, IOSTAT = ios, ERR = 902 ) 
     239902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp ) 
     240      WRITE ( numont, namtrc ) 
     241 
     242      DO jn = 1, jptra 
     243         ctrcnm    (jn) = TRIM( sn_tracer(jn)%clsname ) 
     244         ctrcln    (jn) = TRIM( sn_tracer(jn)%cllname ) 
     245         ctrcun    (jn) = TRIM( sn_tracer(jn)%clunit  ) 
     246         ln_trc_ini(jn) =       sn_tracer(jn)%llinit 
     247         ln_trc_wri(jn) =       sn_tracer(jn)%llsave 
     248      END DO 
     249       
     250    END SUBROUTINE trc_nam_trc 
     251 
     252 
     253   SUBROUTINE trc_nam_dia 
     254      !!--------------------------------------------------------------------- 
     255      !!                     ***  ROUTINE trc_nam_dia  *** 
     256      !! 
     257      !! ** Purpose :   read options for the passive tracer diagnostics 
     258      !! 
     259      !! ** Method  : - read passive tracer namelist  
     260      !!              - read namelist of each defined SMS model 
     261      !!                ( (PISCES, CFC, MY_TRC ) 
     262      !!--------------------------------------------------------------------- 
     263      INTEGER ::  ierr 
     264#if defined key_trdmld_trc  || defined key_trdtrc 
     265      NAMELIST/namtrc_trd/ nn_trd_trc, nn_ctls_trc, rn_ucf_trc, & 
     266         &                ln_trdmld_trc_restart, ln_trdmld_trc_instant, & 
     267         &                cn_trdrst_trc_in, cn_trdrst_trc_out, ln_trdtrc 
     268#endif 
     269      NAMELIST/namtrc_dia/ ln_diatrc, ln_diabio, nn_writedia, nn_writebio 
     270 
     271      !!--------------------------------------------------------------------- 
     272 
     273      IF(lwp) WRITE(numout,*)  
     274      IF(lwp) WRITE(numout,*) 'trc_nam_dia : read the passive tracer diagnostics options' 
     275      IF(lwp) WRITE(numout,*) '~~~~~~~' 
     276 
     277      IF(lwp) WRITE(numout,*) 
     278      IF(lwp) WRITE(numout,*) 'trc_nam_dia : read the passive tracer diagnostics options' 
     279      IF(lwp) WRITE(numout,*) '~~~~~~~' 
     280 
     281      REWIND( numnat_ref )              ! Namelist namtrc_dia in reference namelist : Passive tracer diagnostics 
     282      READ  ( numnat_ref, namtrc_dia, IOSTAT = ios, ERR = 903) 
     283903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in reference namelist', lwp ) 
     284 
     285      REWIND( numnat_cfg )              ! Namelist namtrc_dia in configuration namelist : Passive tracer diagnostics 
     286      READ  ( numnat_cfg, namtrc_dia, IOSTAT = ios, ERR = 904 ) 
     287904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in configuration namelist', lwp ) 
     288      WRITE ( numont, namtrc_dia ) 
     289 
     290      IF(lwp) THEN 
     291         WRITE(numout,*) 
     292         WRITE(numout,*) 
     293         WRITE(numout,*) ' Namelist : namtrc_dia' 
     294         WRITE(numout,*) '    save additionnal diagnostics arrays         ln_diatrc   = ', ln_diatrc 
     295         WRITE(numout,*) '    save additionnal biology diagnostics arrays ln_diabio   = ', ln_diabio 
     296         WRITE(numout,*) '    frequency of outputs for additional arrays  nn_writedia = ', nn_writedia 
     297         WRITE(numout,*) '    frequency of outputs for biological trends  nn_writebio = ', nn_writebio 
     298         WRITE(numout,*) ' ' 
     299      ENDIF 
     300 
     301      IF( ln_diatrc .AND. .NOT. lk_iomput ) THEN  
     302         ALLOCATE( trc2d(jpi,jpj,jpdia2d), trc3d(jpi,jpj,jpk,jpdia3d),  & 
     303           &       ctrc2d(jpdia2d), ctrc2l(jpdia2d), ctrc2u(jpdia2d) ,  &  
     304           &       ctrc3d(jpdia3d), ctrc3l(jpdia3d), ctrc3u(jpdia3d) ,  STAT = ierr )  
     305         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate add. diag. array' ) 
     306         ! 
     307         trc2d(:,:,:  ) = 0._wp  ;   ctrc2d(:) = ' '   ;   ctrc2l(:) = ' '    ;    ctrc2u(:) = ' '  
     308         trc3d(:,:,:,:) = 0._wp  ;   ctrc3d(:) = ' '   ;   ctrc3l(:) = ' '    ;    ctrc3u(:) = ' '  
     309         ! 
     310      ENDIF 
     311 
     312      IF( ( ln_diabio .AND. .NOT. lk_iomput ) .OR. l_trdtrc ) THEN 
     313         ALLOCATE( trbio (jpi,jpj,jpk,jpdiabio) , & 
     314           &       ctrbio(jpdiabio), ctrbil(jpdiabio), ctrbiu(jpdiabio), STAT = ierr )  
     315         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate bio. diag. array' ) 
     316         ! 
     317         trbio(:,:,:,:) = 0._wp  ;   ctrbio(:) = ' '   ;   ctrbil(:) = ' '    ;    ctrbiu(:) = ' '  
     318         ! 
     319      ENDIF 
     320      ! 
     321   END SUBROUTINE trc_nam_dia 
     322 
    248323#else 
    249324   !!---------------------------------------------------------------------- 
     
    253328   SUBROUTINE trc_nam                      ! Empty routine    
    254329   END SUBROUTINE trc_nam 
     330   SUBROUTINE trc_nam_run                      ! Empty routine    
     331   END SUBROUTINE trc_nam_run 
    255332#endif 
    256333 
Note: See TracChangeset for help on using the changeset viewer.