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 3294 for trunk/NEMOGCM/NEMO/TOP_SRC/trcdia.F90 – NEMO

Ignore:
Timestamp:
2012-01-28T17:44:18+01:00 (12 years ago)
Author:
rblod
Message:

Merge of 3.4beta into the trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/TOP_SRC/trcdia.F90

    r2715 r3294  
    1111   !!                  !  2008-05 (C. Ethe re-organization) 
    1212   !!---------------------------------------------------------------------- 
    13 #if defined key_top && ! defined key_iomput 
     13#if defined key_top  
    1414   !!---------------------------------------------------------------------- 
    1515   !!   'key_top'                                                TOP models 
     
    2525   USE par_trc 
    2626   USE dianam    ! build name of file (routine) 
    27    USE ioipsl 
     27   USE ioipsl    ! I/O manager 
     28   USE iom       ! I/O manager 
     29   USE lib_mpp   ! MPP library 
    2830 
    2931   IMPLICIT NONE 
     
    3133 
    3234   PUBLIC   trc_dia        ! called by XXX module  
    33    PUBLIC   trc_dia_alloc  ! called by nemogcm.F90 
    3435 
    3536   INTEGER  ::   nit5      !: id for tracer output file 
     
    4142   INTEGER , ALLOCATABLE, SAVE, DIMENSION (:) ::   ndext50   !: integer arrays for ocean 3D index 
    4243   INTEGER , ALLOCATABLE, SAVE, DIMENSION (:) ::   ndext51   !: integer arrays for ocean surface index 
    43 # if defined key_diatrc 
     44 
    4445   INTEGER  ::   nitd      !: id for additional array output file 
    4546   INTEGER  ::   ndepitd   !: id for depth mesh 
    4647   INTEGER  ::   nhoritd   !: id for horizontal mesh 
    47 # endif 
    48 # if defined key_diabio 
     48 
    4949   INTEGER  ::   nitb        !:         id.         for additional array output file 
    5050   INTEGER  ::   ndepitb   !:  id for depth mesh 
    5151   INTEGER  ::   nhoritb   !:  id for horizontal mesh 
    52 # endif 
    5352 
    5453   !! * Substitutions 
     
    6766      !! ** Purpose :   output passive tracers fields  
    6867      !!--------------------------------------------------------------------- 
    69       INTEGER, INTENT(in) ::   kt   ! ocean time-step 
    70       ! 
    71       INTEGER ::   kindic   ! local integer 
     68      INTEGER, INTENT(in) ::   kt    ! ocean time-step 
     69      ! 
     70      INTEGER             ::  ierr   ! local integer 
    7271      !!--------------------------------------------------------------------- 
    7372      ! 
    74       CALL trcdit_wr( kt, kindic )      ! outputs for tracer concentration 
    75       CALL trcdii_wr( kt, kindic )      ! outputs for additional arrays 
    76       CALL trcdib_wr( kt, kindic )      ! outputs for biological trends 
     73      IF( kt == nittrc000 )  THEN 
     74         ALLOCATE( ndext50(jpij*jpk), ndext51(jpij), STAT=ierr ) 
     75         IF( ierr > 0 ) THEN 
     76            CALL ctl_stop( 'STOP', 'trc_diat: unable to allocate arrays' )  ;   RETURN 
     77         ENDIF 
     78      ENDIF 
     79      ! 
     80      IF( .NOT.lk_iomput ) THEN 
     81                          CALL trcdit_wr( kt )      ! outputs for tracer concentration 
     82         IF( ln_diatrc )  CALL trcdii_wr( kt )      ! outputs for additional arrays 
     83         IF( ln_diabio )  CALL trcdib_wr( kt )      ! outputs for biological trends 
     84      ENDIF 
    7785      ! 
    7886   END SUBROUTINE trc_dia 
    7987 
    8088 
    81    SUBROUTINE trcdit_wr( kt, kindic ) 
     89   SUBROUTINE trcdit_wr( kt ) 
    8290      !!---------------------------------------------------------------------- 
    8391      !!                     ***  ROUTINE trcdit_wr  *** 
     
    8593      !! ** Purpose :   Standard output of passive tracer : concentration fields 
    8694      !! 
    87       !! ** Method  :   At the beginning of the first time step (nit000), define all 
     95      !! ** Method  :   At the beginning of the first time step (nittrc000), define all 
    8896      !!             the NETCDF files and fields for concentration of passive tracer 
    8997      !! 
     
    9199      !!        Each nwritetrc time step, output the instantaneous or mean fields 
    92100      !! 
    93       !!        IF kindic <0, output of fields before the model interruption. 
    94       !!        IF kindic =0, time step loop 
    95       !!        IF kindic >0, output of fields before the time step loop 
    96101      !!---------------------------------------------------------------------- 
    97102      INTEGER, INTENT(in) ::   kt       ! ocean time-step 
    98       INTEGER, INTENT(in) ::   kindic   ! indicator of abnormal termination 
    99103      ! 
    100104      INTEGER ::   jn 
     
    135139 
    136140      ! define time axis 
    137       itmod = kt - nit000 + 1 
     141      itmod = kt - nittrc000 + 1 
    138142      it    = kt 
    139       iiter = ( nit000 - 1 ) / nn_dttrc 
     143      iiter = ( nittrc000 - 1 ) / nn_dttrc 
    140144 
    141145      ! Define NETCDF files and fields at beginning of first time step 
    142146      ! -------------------------------------------------------------- 
    143147 
    144       IF(ll_print)WRITE(numout,*)'trcdit_wr kt=',kt,' kindic ',kindic 
     148      IF(ll_print)WRITE(numout,*)'trcdit_wr kt=',kt 
    145149       
    146       IF( kt == nit000 ) THEN 
     150      IF( kt == nittrc000 ) THEN 
     151 
     152         IF(lwp) THEN                   ! control print 
     153            WRITE(numout,*) 
     154            WRITE(numout,*) '    frequency of outputs for passive tracers nn_writetrc = ', nn_writetrc 
     155            DO jn = 1, jptra 
     156               IF( ln_trc_wri(jn) )  WRITE(numout,*) ' ouput tracer nb : ', jn, '    short name : ', ctrcnm(jn)  
     157            END DO 
     158            WRITE(numout,*) ' ' 
     159         ENDIF 
    147160 
    148161         ! Compute julian date from starting date of the run 
     
    150163         zjulian = zjulian - adatrj   !   set calendar origin to the beginning of the experiment 
    151164         IF(lwp)WRITE(numout,*)' '   
    152          IF(lwp)WRITE(numout,*)' Date 0 used :', nit000                         & 
     165         IF(lwp)WRITE(numout,*)' Date 0 used :', nittrc000                         & 
    153166            &                 ,' YEAR ', nyear, ' MONTH ', nmonth, ' DAY ', nday   & 
    154167            &                 ,'Julian day : ', zjulian   
     
    182195         ! Declare all the output fields as NETCDF variables 
    183196         DO jn = 1, jptra 
    184             IF( lutsav(jn) ) THEN 
     197            IF( ln_trc_wri(jn) ) THEN 
    185198               cltra  = TRIM( ctrcnm(jn) )   ! short title for tracer 
    186                cltral = TRIM( ctrcnl(jn) )   ! long title for tracer 
     199               cltral = TRIM( ctrcln(jn) )   ! long title for tracer 
    187200               cltrau = TRIM( ctrcun(jn) )   ! UNIT for tracer 
    188201               CALL histdef( nit5, cltra, cltral, cltrau, jpi, jpj, nhorit5,  & 
     
    209222      DO jn = 1, jptra 
    210223         cltra  = TRIM( ctrcnm(jn) )   ! short title for tracer 
    211          IF( lutsav(jn) ) CALL histwrite( nit5, cltra, it, trn(:,:,:,jn), ndimt50, ndext50 ) 
     224         IF( ln_trc_wri(jn) ) CALL histwrite( nit5, cltra, it, trn(:,:,:,jn), ndimt50, ndext50 ) 
    212225      END DO 
    213226 
    214227      ! close the file  
    215228      ! -------------- 
    216       IF( kt == nitend .OR. kindic < 0 )   CALL histclo( nit5 ) 
     229      IF( kt == nitend )   CALL histclo( nit5 ) 
    217230      ! 
    218231   END SUBROUTINE trcdit_wr 
    219232 
    220 #if defined key_diatrc 
    221  
    222    SUBROUTINE trcdii_wr( kt, kindic ) 
     233   SUBROUTINE trcdii_wr( kt ) 
    223234      !!---------------------------------------------------------------------- 
    224235      !!                     ***  ROUTINE trcdii_wr  *** 
     
    226237      !! ** Purpose :   output of passive tracer : additional 2D and 3D arrays 
    227238      !! 
    228       !! ** Method  :   At the beginning of the first time step (nit000), define all 
     239      !! ** Method  :   At the beginning of the first time step (nittrc000), define all 
    229240      !!             the NETCDF files and fields for concentration of passive tracer 
    230241      !! 
     
    232243      !!        Each nn_writedia time step, output the instantaneous or mean fields 
    233244      !! 
    234       !!        IF kindic <0, output of fields before the model interruption. 
    235       !!        IF kindic =0, time step loop 
    236       !!        IF kindic >0, output of fields before the time step loop 
    237245      !!---------------------------------------------------------------------- 
    238246      INTEGER, INTENT(in) ::   kt       ! ocean time-step 
    239       INTEGER, INTENT(in) ::   kindic   ! indicator of abnormal termination 
    240247      !! 
    241248      LOGICAL ::   ll_print = .FALSE. 
     
    275282 
    276283      ! define time axis 
    277       itmod = kt - nit000 + 1 
     284      itmod = kt - nittrc000 + 1 
    278285      it    = kt 
    279       iiter = ( nit000 - 1 ) / nn_dttrc 
     286      iiter = ( nittrc000 - 1 ) / nn_dttrc 
    280287 
    281288      ! 1. Define NETCDF files and fields at beginning of first time step 
    282289      ! ----------------------------------------------------------------- 
    283290 
    284       IF( ll_print ) WRITE(numout,*) 'trcdii_wr kt=', kt, ' kindic ', kindic 
    285  
    286       IF( kt == nit000 ) THEN 
     291      IF( ll_print ) WRITE(numout,*) 'trcdii_wr kt=', kt 
     292 
     293      IF( kt == nittrc000 ) THEN 
    287294 
    288295         ! Define the NETCDF files for additional arrays : 2D or 3D 
     
    356363      ! Closing all files 
    357364      ! ----------------- 
    358       IF( kt == nitend .OR. kindic < 0 )   CALL histclo(nitd) 
     365      IF( kt == nitend )   CALL histclo(nitd) 
    359366      ! 
    360367 
    361368   END SUBROUTINE trcdii_wr 
    362369 
    363 # else 
    364    SUBROUTINE trcdii_wr( kt, kindic )                      ! Dummy routine 
    365       INTEGER, INTENT (in) :: kt, kindic 
    366    END SUBROUTINE trcdii_wr 
    367 # endif 
    368  
    369 # if defined key_diabio 
    370  
    371    SUBROUTINE trcdib_wr( kt, kindic ) 
     370   SUBROUTINE trcdib_wr( kt ) 
    372371      !!---------------------------------------------------------------------- 
    373372      !!                     ***  ROUTINE trcdib_wr  *** 
     
    375374      !! ** Purpose :   output of passive tracer : biological fields 
    376375      !! 
    377       !! ** Method  :   At the beginning of the first time step (nit000), define all 
     376      !! ** Method  :   At the beginning of the first time step (nittrc000), define all 
    378377      !!             the NETCDF files and fields for concentration of passive tracer 
    379378      !! 
     
    381380      !!        Each nn_writebio time step, output the instantaneous or mean fields 
    382381      !! 
    383       !!        IF kindic <0, output of fields before the model interruption. 
    384       !!        IF kindic =0, time step loop 
    385       !!        IF kindic >0, output of fields before the time step loop 
    386382      !!---------------------------------------------------------------------- 
    387383      INTEGER, INTENT( in ) ::   kt          ! ocean time-step 
    388       INTEGER, INTENT( in ) ::   kindic      ! indicator of abnormal termination 
    389384      !! 
    390385      LOGICAL ::   ll_print = .FALSE. 
     
    424419 
    425420      ! define time axis 
    426       itmod = kt - nit000 + 1 
     421      itmod = kt - nittrc000 + 1 
    427422      it    = kt 
    428       iiter = ( nit000 - 1 ) / nn_dttrc 
     423      iiter = ( nittrc000 - 1 ) / nn_dttrc 
    429424 
    430425      ! Define NETCDF files and fields at beginning of first time step 
    431426      ! -------------------------------------------------------------- 
    432427 
    433       IF(ll_print) WRITE(numout,*)'trcdib_wr kt=',kt,' kindic ',kindic 
    434  
    435       IF( kt == nit000 ) THEN 
     428      IF(ll_print) WRITE(numout,*)'trcdib_wr kt=',kt 
     429 
     430      IF( kt == nittrc000 ) THEN 
    436431 
    437432         ! Define the NETCDF files for biological trends 
     
    481476      ! Closing all files 
    482477      ! ----------------- 
    483       IF( kt == nitend .OR. kindic < 0 )   CALL histclo( nitb ) 
     478      IF( kt == nitend )   CALL histclo( nitb ) 
    484479      ! 
    485480   END SUBROUTINE trcdib_wr 
    486481 
    487 # else 
    488  
    489    SUBROUTINE trcdib_wr( kt, kindic )                      ! Dummy routine 
    490       INTEGER, INTENT ( in ) ::   kt, kindic 
    491    END SUBROUTINE trcdib_wr 
    492  
    493 # endif  
    494  
    495    INTEGER FUNCTION trc_dia_alloc() 
    496       !!--------------------------------------------------------------------- 
    497       !!                     ***  ROUTINE trc_dia_alloc  *** 
    498       !!--------------------------------------------------------------------- 
    499       ALLOCATE( ndext50(jpij*jpk), ndext51(jpij), STAT=trc_dia_alloc ) 
    500       ! 
    501       IF( trc_dia_alloc /= 0 )   CALL ctl_warn('trc_dia_alloc : failed to allocate arrays') 
    502       ! 
    503    END FUNCTION trc_dia_alloc 
    504482#else 
    505483   !!---------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.