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 5726 for branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO – NEMO

Ignore:
Timestamp:
2015-09-10T18:48:32+02:00 (9 years ago)
Author:
jpalmier
Message:

JPALM -- 10-09-2015 -- add MEDUSA in the branch ; adapted TOP_SRC to MEDUSA ; remove some svn keywords in the branch

Location:
branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO
Files:
22 added
16 edited

Legend:

Unmodified
Added
Removed
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/OPA_SRC/DIA/diadct.F90

    • Property svn:keywords deleted
    r5505 r5726  
    112112  REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)   ::  transports_2d   
    113113 
    114    !! $Id$ 
    115114CONTAINS 
    116115 
     
    12981297   LOGICAL, PUBLIC, PARAMETER ::   lk_diadct = .FALSE.    !: diamht flag 
    12991298   PUBLIC  
    1300    !! $Id$ 
    13011299CONTAINS 
    13021300 
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zint.F90

    • Property svn:keywords deleted
    r5385 r5726  
    2626   !!---------------------------------------------------------------------- 
    2727   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    28    !! $Id$  
     28   !! $Id$ 
    2929   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    3030   !!---------------------------------------------------------------------- 
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/TRP/trcnam_trp.F90

    • Property svn:keywords deleted
    r5385 r5726  
    5555   !!---------------------------------------------------------------------- 
    5656   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    57    !! $Id$  
     57   !! $Id$ 
    5858   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    5959   !!---------------------------------------------------------------------- 
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/par_trc.F90

    • Property svn:keywords deleted
    r4529 r5726  
    1515   USE par_cfc       ! CFC 11 and 12 tracers 
    1616   USE par_my_trc    ! user defined passive tracers 
     17   USE par_medusa    ! MEDUSA model 
     18   USE par_idtra     ! Idealize tracer 
    1719 
    1820   IMPLICIT NONE 
     
    2426   ! Passive tracers : Total size 
    2527   ! ---------------               ! total number of passive tracers, of 2d and 3d output and trend arrays 
    26    INTEGER, PUBLIC,  PARAMETER ::   jptra    =  jp_pisces     + jp_cfc     + jp_c14b    + jp_my_trc 
    27    INTEGER, PUBLIC,  PARAMETER ::   jpdia2d  =  jp_pisces_2d  + jp_cfc_2d  + jp_c14b_2d + jp_my_trc_2d 
    28    INTEGER, PUBLIC,  PARAMETER ::   jpdia3d  =  jp_pisces_3d  + jp_cfc_3d  + jp_c14b_3d + jp_my_trc_3d 
     28   INTEGER, PUBLIC,  PARAMETER ::   jptra    =  jp_pisces     + jp_cfc     + jp_c14b    + jp_my_trc    + jp_medusa    + jp_idtra 
     29   INTEGER, PUBLIC,  PARAMETER ::   jpdia2d  =  jp_pisces_2d  + jp_cfc_2d  + jp_c14b_2d + jp_my_trc_2d + jp_medusa_2d + jp_idtra_2d 
     30   INTEGER, PUBLIC,  PARAMETER ::   jpdia3d  =  jp_pisces_3d  + jp_cfc_3d  + jp_c14b_3d + jp_my_trc_3d + jp_medusa_3d + jp_idtra_3d 
    2931   !                     ! total number of sms diagnostic arrays 
    30    INTEGER, PUBLIC,  PARAMETER ::   jpdiabio =  jp_pisces_trd + jp_cfc_trd + jp_c14b_trd + jp_my_trc_trd 
     32   INTEGER, PUBLIC,  PARAMETER ::   jpdiabio =  jp_pisces_trd + jp_cfc_trd + jp_c14b_trd + jp_my_trc_trd + jp_medusa_trd + jp_idtra_trd 
    3133    
    3234   !  1D configuration ("key_c1d") 
     
    4244   !!---------------------------------------------------------------------- 
    4345   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    44    !! $Id$  
     46   !! $Id$ 
    4547   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    4648   !!====================================================================== 
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/prtctl_trc.F90

    • Property svn:keywords deleted
    r4520 r5726  
    305305   !!---------------------------------------------------------------------- 
    306306   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    307    !! $Id$  
     307   !! $Id$ 
    308308   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    309309   !!======================================================================    
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/top_substitute.h90

    • Property svn:keywords deleted
    r2528 r5726  
    1313   !!---------------------------------------------------------------------- 
    1414   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    15    !! $Id$  
     15   !! $Id$ 
    1616   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    1717   !!---------------------------------------------------------------------- 
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/trcbc.F90

    • Property svn:keywords deleted
    r5215 r5726  
    4444   !!---------------------------------------------------------------------- 
    4545   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    46    !! $Id$  
     46   !! $Id$ 
    4747   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    4848   !!---------------------------------------------------------------------- 
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/trcdia.F90

    • Property svn:keywords deleted
    r4292 r5726  
    5555   !!---------------------------------------------------------------------- 
    5656   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    57    !! $Id$  
     57   !! $Id$ 
    5858   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    5959   !!---------------------------------------------------------------------- 
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/trcdta.F90

    • Property svn:keywords deleted
    r5385 r5726  
    4040   !!---------------------------------------------------------------------- 
    4141   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    42    !! $Id$  
     42   !! $Id$ 
    4343   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    4444   !!---------------------------------------------------------------------- 
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/trcini.F90

    • Property svn:keywords deleted
    r5407 r5726  
    88   !!            2.0  ! 2005-10 (C. Ethe, G. Madec) revised architecture 
    99   !!            4.0  ! 2011-01 (A. R. Porter, STFC Daresbury) dynamical allocation 
     10   !!             -   ! 2014-06 (A. Yool, J. Palmieri) adding MEDUSA-2 
    1011   !!---------------------------------------------------------------------- 
    1112#if defined key_top 
     
    2425   USE trcini_c14b     ! C14 bomb initialisation 
    2526   USE trcini_my_trc   ! MY_TRC   initialisation 
     27   USE trcini_medusa   ! MEDUSA   initialisation 
     28   USE trcini_idtra    ! idealize tracer initialisation 
    2629   USE trcdta          ! initialisation from files 
    2730   USE daymod          ! calendar manager 
     
    4245   !!---------------------------------------------------------------------- 
    4346   !! NEMO/TOP 4.0 , NEMO Consortium (2011) 
    44    !! $Id$  
     47   !! $Id$ 
    4548   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    4649   !!---------------------------------------------------------------------- 
     
    7780         &   CALL ctl_warn(' Coupling with passive tracers and used of diurnal cycle. & 
    7881         & Computation of a daily mean shortwave for some biogeochemical models) ') 
    79  
     82          !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 
     83          !!!!! CHECK For MEDUSA 
     84          !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 
    8085      IF( nn_cla == 1 )   & 
    8186         &  CALL ctl_stop( ' Cross Land Advection not yet implemented with passive tracer ; nn_cla must be 0' ) 
     
    101106      IF( lk_c14b    )       CALL trc_ini_c14b         ! C14 bomb  tracer 
    102107      IF( lk_my_trc  )       CALL trc_ini_my_trc       ! MY_TRC  tracers 
     108      IF( lk_medusa  )       CALL trc_ini_medusa       ! MEDUSA  tracers 
     109      IF( lk_idtra   )       CALL trc_ini_idtra        ! Idealize tracers 
    103110 
    104111      CALL trc_ice_ini                                 ! Tracers in sea ice 
     112 
     113# if defined key_debug_medusa 
     114         IF (lwp) write (numout,*) '------------------------------' 
     115         IF (lwp) write (numout,*) 'Jpalm - debug' 
     116         IF (lwp) write (numout,*) ' in trc_init' 
     117         IF (lwp) write (numout,*) ' sms init OK' 
     118         IF (lwp) write (numout,*) ' next: open tracer.stat' 
     119         IF (lwp) write (numout,*) ' ' 
     120         CALL flush(numout) 
     121# endif 
    105122 
    106123      IF( lwp ) THEN 
     
    110127      ENDIF 
    111128 
    112       IF( ln_trcdta )      CALL trc_dta_init(jptra) 
    113  
     129# if defined key_debug_medusa 
     130         IF (lwp) write (numout,*) '------------------------------' 
     131         IF (lwp) write (numout,*) 'Jpalm - debug' 
     132         IF (lwp) write (numout,*) ' in trc_init' 
     133         IF (lwp) write (numout,*) 'open tracer.stat -- OK' 
     134         IF (lwp) write (numout,*) ' ' 
     135         CALL flush(numout) 
     136# endif 
     137 
     138 
     139      IF( ln_trcdta ) THEN 
     140#if defined key_medusa 
     141         IF(lwp) WRITE(numout,*) 'AXY: calling trc_dta_init' 
     142         IF(lwp) CALL flush(numout) 
     143#endif 
     144         CALL trc_dta_init(jptra) 
     145      ENDIF 
    114146 
    115147      IF( ln_rsttr ) THEN 
    116148        ! 
     149#if defined key_medusa 
     150        IF(lwp) WRITE(numout,*) 'AXY: calling trc_rst_read' 
     151        IF(lwp) CALL flush(numout) 
     152#endif 
    117153        CALL trc_rst_read              ! restart from a file 
    118154        ! 
     
    121157        IF( ln_trcdta .AND. nb_trcdta > 0 ) THEN  ! Initialisation of tracer from a file that may also be used for damping 
    122158            ! 
     159#if defined key_medusa 
     160            IF(lwp) WRITE(numout,*) 'AXY: calling wrk_alloc' 
     161            IF(lwp) CALL flush(numout) 
     162#endif 
    123163            CALL wrk_alloc( jpi, jpj, jpk, ztrcdta )    ! Memory allocation 
    124164            ! 
     165#if defined key_medusa 
     166            IF(lwp) WRITE(numout,*) 'AXY: calling trc_dta' 
     167            IF(lwp) CALL flush(numout) 
     168#endif 
    125169            DO jn = 1, jptra 
    126170               IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file 
     
    129173                  ztrcdta(:,:,:) = sf_trcdta(jl)%fnow(:,:,:) 
    130174                  trn(:,:,:,jn) = ztrcdta(:,:,:) * tmask(:,:,:)   
    131                   IF( .NOT.ln_trcdmp .AND. .NOT.ln_trcdmp_clo ) THEN      !== deallocate data structure   ==! 
     175                  IF( .NOT.ln_trcdmp .AND. .NOT. ln_trcdmp_clo ) THEN      !== deallocate data structure   ==! 
    132176                     !                                                    (data used only for initialisation) 
    133177                     IF(lwp) WRITE(numout,*) 'trc_dta: deallocate data arrays as they are only used to initialize the run' 
     
    138182               ENDIF 
    139183            ENDDO 
     184#if defined key_medusa 
     185            IF(lwp) WRITE(numout,*) 'AXY: calling wrk_dealloc' 
     186            IF(lwp) CALL flush(numout) 
     187#endif 
    140188            CALL wrk_dealloc( jpi, jpj, jpk, ztrcdta ) 
    141189        ENDIF 
    142190        ! 
     191# if defined key_debug_medusa 
     192         IF (lwp) write (numout,*) '------------------------------' 
     193         IF (lwp) write (numout,*) 'Jpalm - debug' 
     194         IF (lwp) write (numout,*) ' in trc_init' 
     195         IF (lwp) write (numout,*) ' before trb = trn' 
     196         IF (lwp) write (numout,*) ' ' 
     197         CALL flush(numout) 
     198# endif 
     199        ! 
    143200        trb(:,:,:,:) = trn(:,:,:,:) 
     201        !  
     202# if defined key_debug_medusa 
     203         IF (lwp) write (numout,*) '------------------------------' 
     204         IF (lwp) write (numout,*) 'Jpalm - debug' 
     205         IF (lwp) write (numout,*) ' in trc_init' 
     206         IF (lwp) write (numout,*) ' trb = trn -- OK' 
     207         IF (lwp) write (numout,*) ' ' 
     208         CALL flush(numout) 
     209# endif 
    144210        !  
    145211      ENDIF 
     
    150216      IF( ln_zps .AND. .NOT. lk_c1d .AND.       ln_isfcav )   & 
    151217        &    CALL zps_hde_isf( nit000, jptra, trn, pgtu=gtru, pgtv=gtrv, pgtui=gtrui, pgtvi=gtrvi )       ! tracers at the bottom ocean level 
    152  
    153  
     218      ! 
     219# if defined key_debug_medusa 
     220         IF (lwp) write (numout,*) '------------------------------' 
     221         IF (lwp) write (numout,*) 'Jpalm - debug' 
     222         IF (lwp) write (numout,*) ' in trc_init' 
     223         IF (lwp) write (numout,*) ' partial step -- OK' 
     224         IF (lwp) write (numout,*) ' ' 
     225         CALL flush(numout) 
     226# endif 
    154227      ! 
    155228      IF( nn_dttrc /= 1 )        CALL trc_sub_ini      ! Initialize variables for substepping passive tracers 
    156229      ! 
    157  
     230# if defined key_debug_medusa 
     231         IF (lwp) write (numout,*) '------------------------------' 
     232         IF (lwp) write (numout,*) 'Jpalm - debug' 
     233         IF (lwp) write (numout,*) ' in trc_init' 
     234         IF (lwp) write (numout,*) ' before initiate tracer contents' 
     235         IF (lwp) write (numout,*) ' ' 
     236         CALL flush(numout) 
     237# endif 
     238      ! 
    158239      trai(:) = 0._wp                                                   ! initial content of all tracers 
    159240      DO jn = 1, jptra 
     
    168249         WRITE(numout,*) '          *** Total inital content of all tracers ' 
    169250         WRITE(numout,*) 
     251# if defined key_debug_medusa 
     252         CALL flush(numout) 
     253# endif 
     254         ! 
     255# if defined key_debug_medusa 
     256         WRITE(numout,*) ' litle check :  ', ctrcnm(1) 
     257         CALL flush(numout) 
     258# endif 
    170259         DO jn = 1, jptra 
    171260            WRITE(numout,9000) jn, TRIM( ctrcnm(jn) ), trai(jn) 
     
    180269         CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm ) 
    181270      ENDIF 
     271 
     272      IF(lwp) WRITE(numout,*) 
     273      IF(lwp) WRITE(numout,*) 'trc_init : passive tracer set up completed' 
     274      IF(lwp) WRITE(numout,*) '~~~~~~~' 
     275      IF(lwp) CALL flush(numout) 
     276 
    1822779000  FORMAT(' tracer nb : ',i2,'      name :',a10,'      initial content :',e18.10) 
    183278      ! 
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/trcnam.F90

    • Property svn:keywords deleted
    r5411 r5726  
    2525   USE trcnam_c14b       ! C14 SMS namelist 
    2626   USE trcnam_my_trc     ! MY_TRC SMS namelist 
     27   USE trcnam_medusa     ! MEDUSA namelist 
     28   USE trcnam_idtra      ! Idealise tracer namelist 
    2729   USE trd_oce        
    2830   USE trdtrc_oce 
     
    5658      !!                ( (PISCES, CFC, MY_TRC ) 
    5759      !!--------------------------------------------------------------------- 
    58       INTEGER  ::   jn                  ! dummy loop indice 
     60      INTEGER  ::   jn, jk                     ! dummy loop indice 
    5961      !                                        !   Parameters of the run  
    6062      IF( .NOT. lk_offline ) CALL trc_nam_run 
    6163       
    6264      !                                        !  passive tracer informations 
     65# if defined key_debug_medusa 
     66      CALL flush(numout) 
     67      IF (lwp) write (numout,*) '------------------------------' 
     68      IF (lwp) write (numout,*) 'Jpalm - debug' 
     69      IF (lwp) write (numout,*) 'in trc_nam - just before CALL trc_nam_trc' 
     70      IF (lwp) write (numout,*) ' ' 
     71# endif 
     72      ! 
    6373      CALL trc_nam_trc 
    6474       
    6575      !                                        !   Parameters of additional diagnostics 
     76# if defined key_debug_medusa 
     77      CALL flush(numout) 
     78      IF (lwp) write (numout,*) '------------------------------' 
     79      IF (lwp) write (numout,*) 'Jpalm - debug' 
     80      IF (lwp) write (numout,*) 'CALL trc_nam_trc -- OK' 
     81      IF (lwp) write (numout,*) 'in trc_nam - just before CALL trc_nam_dia' 
     82      IF (lwp) write (numout,*) ' ' 
     83# endif 
     84      ! 
     85 
    6686      CALL trc_nam_dia 
    6787 
    6888      !                                        !   namelist of transport 
     89# if defined key_debug_medusa 
     90      CALL flush(numout) 
     91      IF (lwp) write (numout,*) '------------------------------' 
     92      IF (lwp) write (numout,*) 'Jpalm - debug' 
     93      IF (lwp) write (numout,*) 'CALL trc_nam_dia -- OK' 
     94      IF (lwp) write (numout,*) 'in trc_nam - just before CALL trc_nam_trp' 
     95      IF (lwp) write (numout,*) ' ' 
     96# endif 
     97      ! 
    6998      CALL trc_nam_trp 
     99      ! 
     100# if defined key_debug_medusa 
     101      CALL flush(numout) 
     102      IF (lwp) write (numout,*) '------------------------------' 
     103      IF (lwp) write (numout,*) 'Jpalm - debug' 
     104      IF (lwp) write (numout,*) 'CALL trc_nam_trp -- OK' 
     105      IF (lwp) write (numout,*) 'continue trc_nam ' 
     106      IF (lwp) write (numout,*) ' ' 
     107      CALL flush(numout) 
     108# endif 
     109      ! 
    70110 
    71111 
     
    89129         END DO 
    90130         WRITE(numout,*) ' ' 
     131# if defined key_debug_medusa 
     132      CALL flush(numout) 
     133# endif 
    91134      ENDIF 
    92135 
     
    107150            WRITE(numout,*) 
    108151         ENDIF 
    109       ENDIF 
    110  
     152# if defined key_debug_medusa 
     153      CALL flush(numout) 
     154# endif 
     155      ENDIF 
     156 
     157# if defined key_debug_medusa 
     158       DO jk = 1, jpk 
     159          WRITE(numout,*) '  level number: ', jk, 'rdttrc: ',rdttrc(jk),'rdttra: ', rdttra(jk),'nn_dttrc: ', nn_dttrc 
     160       END DO 
     161      CALL flush(numout) 
     162# endif 
    111163       
    112164      rdttrc(:) = rdttra(:) * FLOAT( nn_dttrc )   ! vertical profile of passive tracer time-step 
     
    116168        WRITE(numout,*) '    Passive Tracer  time step    rdttrc  = ', rdttrc(1) 
    117169        WRITE(numout,*)  
     170# if defined key_debug_medusa 
     171      CALL flush(numout) 
     172# endif 
    118173      ENDIF 
    119174 
     
    143198               IF( ln_trdtrc(jn) ) WRITE(numout,*) '    compute ML trends for tracer number :', jn 
    144199            END DO 
     200         WRITE(numout,*) ' ' 
     201         CALL flush(numout) 
    145202         ENDIF 
    146203#endif 
    147204 
     205# if defined key_debug_medusa 
     206      CALL flush(numout) 
     207      IF (lwp) write (numout,*) '------------------------------' 
     208      IF (lwp) write (numout,*) 'Jpalm - debug' 
     209      IF (lwp) write (numout,*) 'just before ice module for tracers call : ' 
     210      IF (lwp) write (numout,*) ' ' 
     211# endif 
     212      ! 
    148213 
    149214      ! Call the ice module for tracers 
    150215      ! ------------------------------- 
    151216      CALL trc_nam_ice 
     217 
     218# if defined key_debug_medusa 
     219      CALL flush(numout) 
     220      IF (lwp) write (numout,*) '------------------------------' 
     221      IF (lwp) write (numout,*) 'Jpalm - debug' 
     222      IF (lwp) write (numout,*) 'Will now read SMS namelists : ' 
     223      IF (lwp) write (numout,*) ' ' 
     224# endif 
     225      ! 
    152226 
    153227      ! namelist of SMS 
     
    156230      ELSE                    ;   IF(lwp) WRITE(numout,*) '          PISCES not used' 
    157231      ENDIF 
    158  
     232      ! 
     233# if defined key_debug_medusa 
     234      CALL flush(numout) 
     235      IF (lwp) write (numout,*) '------------------------------' 
     236      IF (lwp) write (numout,*) 'Jpalm - debug' 
     237      IF (lwp) write (numout,*) 'CALL trc_nam_pisces -- OK' 
     238      IF (lwp) write (numout,*) 'in trc_nam - just before CALL trc_nam_medusa' 
     239      IF (lwp) write (numout,*) ' ' 
     240# endif 
     241      ! 
     242      IF( lk_medusa  ) THEN   ;   CALL trc_nam_medusa      ! MEDUSA  tracers 
     243      ELSE                    ;   IF(lwp) WRITE(numout,*) '          MEDUSA not used' 
     244      ENDIF 
     245      ! 
     246# if defined key_debug_medusa 
     247      CALL flush(numout) 
     248      IF (lwp) write (numout,*) '------------------------------' 
     249      IF (lwp) write (numout,*) 'Jpalm - debug' 
     250      IF (lwp) write (numout,*) 'CALL trc_nam_medusa -- OK' 
     251      IF (lwp) write (numout,*) 'in trc_nam - just before CALL trc_nam_idtra' 
     252      IF (lwp) write (numout,*) ' ' 
     253# endif 
     254      ! 
     255      IF( lk_idtra   ) THEN   ;   CALL trc_nam_idtra       ! Idealize tracers 
     256      ELSE                    ;   IF(lwp) WRITE(numout,*) '          Idealize tracers not used' 
     257      ENDIF 
     258      ! 
     259# if defined key_debug_medusa 
     260      CALL flush(numout) 
     261      IF (lwp) write (numout,*) '------------------------------' 
     262      IF (lwp) write (numout,*) 'Jpalm - debug' 
     263      IF (lwp) write (numout,*) 'CALL trc_nam_idtra -- OK' 
     264      IF (lwp) write (numout,*) 'in trc_nam - just before CALL trc_nam_cfc' 
     265      IF (lwp) write (numout,*) ' ' 
     266# endif 
     267      ! 
    159268      IF( lk_cfc     ) THEN   ;   CALL trc_nam_cfc         ! CFC     tracers 
    160269      ELSE                    ;   IF(lwp) WRITE(numout,*) '          CFC not used' 
     
    169278      ENDIF 
    170279      ! 
     280      IF(lwp)   CALL flush(numout) 
    171281   END SUBROUTINE trc_nam 
    172282 
     
    216326         WRITE(numout,*) '   Use euler integration for TRC (y/n)          ln_top_euler  = ', ln_top_euler 
    217327         WRITE(numout,*) ' ' 
     328        CALL flush(numout) 
    218329      ENDIF 
    219330      ! 
     
    306417         ln_trc_wri(jn) =       sn_tracer(jn)%llsave 
    307418      END DO 
    308        
     419      IF(lwp)  CALL flush(numout)       
     420 
    309421    END SUBROUTINE trc_nam_trc 
    310422 
     
    357469         WRITE(numout,*) '    frequency of outputs for biological trends  nn_writebio = ', nn_writebio 
    358470         WRITE(numout,*) ' ' 
    359       ENDIF 
    360  
    361       IF( ln_diatrc .AND. .NOT. lk_iomput ) THEN  
     471         CALL flush(numout) 
     472      ENDIF 
     473!! 
     474!! JPALM -- 17-07-2015 -- 
     475!! MEDUSA is not yet up-to-date with the iom server. 
     476!! we use it for the main tracer, but not fully with diagnostics. 
     477!! will have to adapt it properly when visiting Christian Ethee 
     478!! for now, we change  
     479!! IF( ln_diatrc .AND. .NOT. lk_iomput ) THEN 
     480!! to : 
     481!! 
     482      IF( ( ln_diatrc .AND. .NOT. lk_iomput ) .OR. ( ln_diatrc .AND. lk_medusa ) ) THEN  
    362483         ALLOCATE( trc2d(jpi,jpj,jpdia2d), trc3d(jpi,jpj,jpk,jpdia3d),  & 
    363484           &       ctrc2d(jpdia2d), ctrc2l(jpdia2d), ctrc2u(jpdia2d) ,  &  
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/trcrst.F90

    • Property svn:keywords deleted
    r5513 r5726  
    2828   USE iom 
    2929   USE daymod 
     30   !! AXY (05/11/13): need these for MEDUSA to input/output benthic reservoirs 
     31   USE sms_medusa 
     32   USE trcsms_medusa 
     33   !! 
    3034   IMPLICIT NONE 
    3135   PRIVATE 
     
    102106      !!---------------------------------------------------------------------- 
    103107      INTEGER  ::  jn      
     108      !! AXY (05/11/13): temporary variables 
     109      REAL(wp) ::    fq0,fq1,fq2 
    104110 
    105111      !!---------------------------------------------------------------------- 
     
    117123         CALL iom_get( numrtr, jpdom_autoglo, 'TRB'//ctrcnm(jn), trb(:,:,:,jn) ) 
    118124      END DO 
     125 
     126      !! AXY (09/06/14): the ARCHER version of MEDUSA-2 does not include an equivalent 
     127      !!                 call to MEDUSA-2 at this point; this suggests that the FCM 
     128      !!                 version of NEMO date significantly earlier than the current 
     129      !!                 version 
     130 
     131#if defined key_medusa 
     132      !! AXY (13/01/12): check if the restart contains sediment fields; 
     133      !!                 this is only relevant for simulations that include 
     134      !!                 biogeochemistry and are restarted from earlier runs 
     135      !!                 in which there was no sediment component 
     136      !! 
     137      IF( iom_varid( numrtr, 'B_SED_N', ldstop = .FALSE. ) > 0 ) THEN 
     138         !! YES; in which case read them 
     139         !! 
     140         IF(lwp) WRITE(numout,*) ' MEDUSA sediment fields present - reading in ...' 
     141         CALL iom_get( numrtr, jpdom_autoglo, 'B_SED_N',  zb_sed_n(:,:)  ) 
     142         CALL iom_get( numrtr, jpdom_autoglo, 'N_SED_N',  zn_sed_n(:,:)  ) 
     143         CALL iom_get( numrtr, jpdom_autoglo, 'B_SED_FE', zb_sed_fe(:,:) ) 
     144         CALL iom_get( numrtr, jpdom_autoglo, 'N_SED_FE', zn_sed_fe(:,:) ) 
     145         CALL iom_get( numrtr, jpdom_autoglo, 'B_SED_SI', zb_sed_si(:,:) ) 
     146         CALL iom_get( numrtr, jpdom_autoglo, 'N_SED_SI', zn_sed_si(:,:) ) 
     147         CALL iom_get( numrtr, jpdom_autoglo, 'B_SED_C',  zb_sed_c(:,:)  ) 
     148         CALL iom_get( numrtr, jpdom_autoglo, 'N_SED_C',  zn_sed_c(:,:)  ) 
     149         CALL iom_get( numrtr, jpdom_autoglo, 'B_SED_CA', zb_sed_ca(:,:) ) 
     150         CALL iom_get( numrtr, jpdom_autoglo, 'N_SED_CA', zn_sed_ca(:,:) ) 
     151      ELSE 
     152         !! NO; in which case set them to zero 
     153         !! 
     154         IF(lwp) WRITE(numout,*) ' MEDUSA sediment fields absent - setting to zero ...' 
     155         zb_sed_n(:,:)  = 0.0   !! organic N 
     156         zn_sed_n(:,:)  = 0.0 
     157         zb_sed_fe(:,:) = 0.0   !! organic Fe 
     158         zn_sed_fe(:,:) = 0.0 
     159         zb_sed_si(:,:) = 0.0   !! inorganic Si 
     160         zn_sed_si(:,:) = 0.0 
     161         zb_sed_c(:,:)  = 0.0   !! organic C 
     162         zn_sed_c(:,:)  = 0.0 
     163         zb_sed_ca(:,:) = 0.0   !! inorganic C 
     164         zn_sed_ca(:,:) = 0.0 
     165      ENDIF 
     166      !! 
     167      !! calculate stats on these fields 
     168      IF(lwp) WRITE(numout,*) ' MEDUSA sediment field stats (min, max, sum) ...' 
     169      fq0 = MINVAL(zn_sed_n(:,:)) 
     170      fq1 = MAXVAL(zn_sed_n(:,:)) 
     171      fq2 = SUM(zn_sed_n(:,:)) 
     172      if (lwp) write (numout,'(a,3f15.5)') 'Sediment  N ', & 
     173         &        fq0, fq1, fq2 
     174      fq0 = MINVAL(zn_sed_fe(:,:)) 
     175      fq1 = MAXVAL(zn_sed_fe(:,:)) 
     176      fq2 = SUM(zn_sed_fe(:,:)) 
     177      if (lwp) write (numout,'(a,3f15.5)') 'Sediment Fe ', & 
     178         &        fq0, fq1, fq2 
     179      fq0 = MINVAL(zn_sed_si(:,:)) 
     180      fq1 = MAXVAL(zn_sed_si(:,:)) 
     181      fq2 = SUM(zn_sed_si(:,:)) 
     182      if (lwp) write (numout,'(a,3f15.5)') 'Sediment Si ', & 
     183         &        fq0, fq1, fq2 
     184      fq0 = MINVAL(zn_sed_c(:,:)) 
     185      fq1 = MAXVAL(zn_sed_c(:,:)) 
     186      fq2 = SUM(zn_sed_c(:,:)) 
     187      if (lwp) write (numout,'(a,3f15.5)') 'Sediment  C ', & 
     188         &        fq0, fq1, fq2 
     189      fq0 = MINVAL(zn_sed_ca(:,:)) 
     190      fq1 = MAXVAL(zn_sed_ca(:,:)) 
     191      fq2 = SUM(zn_sed_ca(:,:)) 
     192      if (lwp) write (numout,'(a,3f15.5)') 'Sediment Ca ', & 
     193         &        fq0, fq1, fq2 
     194#endif 
     195  
    119196      ! 
    120197   END SUBROUTINE trc_rst_read 
     
    130207      INTEGER  :: jn 
    131208      REAL(wp) :: zarak0 
     209      !! AXY (05/11/13): temporary variables 
     210      REAL(wp) ::    fq0,fq1,fq2 
    132211      !!---------------------------------------------------------------------- 
    133212      ! 
     
    142221         CALL iom_rstput( kt, nitrst, numrtw, 'TRB'//ctrcnm(jn), trb(:,:,:,jn) ) 
    143222      END DO 
     223 
     224      !! AXY (09/06/14): the ARCHER version of MEDUSA-2 does not include an equivalent 
     225      !!                 call to MEDUSA-2 at this point; this suggests that the FCM 
     226      !!                 version of NEMO date significantly earlier than the current 
     227      !!                 version 
     228 
     229#if defined key_medusa 
     230      !! AXY (13/01/12): write out "before" and "now" state of seafloor 
     231      !!                 sediment pools into restart; this happens 
     232      !!                 whether or not the pools are to be used by 
     233      !!                 MEDUSA (which is controlled by a switch in the 
     234      !!                 namelist_top file) 
     235      !! 
     236      IF(lwp) WRITE(numout,*) ' MEDUSA sediment fields - writing out ...' 
     237      CALL iom_rstput( kt, nitrst, numrtw, 'B_SED_N',  zb_sed_n(:,:)  ) 
     238      CALL iom_rstput( kt, nitrst, numrtw, 'N_SED_N',  zn_sed_n(:,:)  ) 
     239      CALL iom_rstput( kt, nitrst, numrtw, 'B_SED_FE', zb_sed_fe(:,:) ) 
     240      CALL iom_rstput( kt, nitrst, numrtw, 'N_SED_FE', zn_sed_fe(:,:) ) 
     241      CALL iom_rstput( kt, nitrst, numrtw, 'B_SED_SI', zb_sed_si(:,:) ) 
     242      CALL iom_rstput( kt, nitrst, numrtw, 'N_SED_SI', zn_sed_si(:,:) ) 
     243      CALL iom_rstput( kt, nitrst, numrtw, 'B_SED_C',  zb_sed_c(:,:)  ) 
     244      CALL iom_rstput( kt, nitrst, numrtw, 'N_SED_C',  zn_sed_c(:,:)  ) 
     245      CALL iom_rstput( kt, nitrst, numrtw, 'B_SED_CA', zb_sed_ca(:,:) ) 
     246      CALL iom_rstput( kt, nitrst, numrtw, 'N_SED_CA', zn_sed_ca(:,:) ) 
     247      !! 
     248      !! calculate stats on these fields 
     249      IF(lwp) WRITE(numout,*) ' MEDUSA sediment field stats (min, max, sum) ...' 
     250      fq0 = MINVAL(zn_sed_n(:,:)) 
     251      fq1 = MAXVAL(zn_sed_n(:,:)) 
     252      fq2 = SUM(zn_sed_n(:,:)) 
     253      if (lwp) write (numout,'(a,3f15.5)') 'Sediment  N ', & 
     254         &        fq0, fq1, fq2 
     255      fq0 = MINVAL(zn_sed_fe(:,:)) 
     256      fq1 = MAXVAL(zn_sed_fe(:,:)) 
     257      fq2 = SUM(zn_sed_fe(:,:)) 
     258      if (lwp) write (numout,'(a,3f15.5)') 'Sediment Fe ', & 
     259         &        fq0, fq1, fq2 
     260      fq0 = MINVAL(zn_sed_si(:,:)) 
     261      fq1 = MAXVAL(zn_sed_si(:,:)) 
     262      fq2 = SUM(zn_sed_si(:,:)) 
     263      if (lwp) write (numout,'(a,3f15.5)') 'Sediment Si ', & 
     264         &        fq0, fq1, fq2 
     265      fq0 = MINVAL(zn_sed_c(:,:)) 
     266      fq1 = MAXVAL(zn_sed_c(:,:)) 
     267      fq2 = SUM(zn_sed_c(:,:)) 
     268      if (lwp) write (numout,'(a,3f15.5)') 'Sediment  C ', & 
     269         &        fq0, fq1, fq2 
     270      fq0 = MINVAL(zn_sed_ca(:,:)) 
     271      fq1 = MAXVAL(zn_sed_ca(:,:)) 
     272      fq2 = SUM(zn_sed_ca(:,:)) 
     273      if (lwp) write (numout,'(a,3f15.5)') 'Sediment Ca ', & 
     274         &        fq0, fq1, fq2 
     275#endif 
     276 
    144277      ! 
    145278      IF( kt == nitrst ) THEN 
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/trcsms.F90

    • Property svn:keywords deleted
    r3680 r5726  
    1616   USE trc                ! 
    1717   USE trcsms_pisces      ! PISCES biogeo-model 
     18   USE trcsms_medusa      ! MEDUSA tracers 
     19   USE trcsms_idtra       ! Idealize Tracer 
    1820   USE trcsms_cfc         ! CFC 11 & 12 
    1921   USE trcsms_c14b        ! C14b tracer  
     
    2830   !!---------------------------------------------------------------------- 
    2931   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    30    !! $Id$  
     32   !! $Id$ 
    3133   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    3234   !!---------------------------------------------------------------------- 
     
    4951      ! 
    5052      IF( lk_pisces  )   CALL trc_sms_pisces ( kt )    ! main program of PISCES  
     53      IF( lk_medusa  )   CALL trc_sms_medusa ( kt )    ! MEDUSA  tracers 
     54      IF( lk_idtra   )   CALL trc_sms_idtra  ( kt )    ! radioactive decay of Id. tracer 
    5155      IF( lk_cfc     )   CALL trc_sms_cfc    ( kt )    ! surface fluxes of CFC 
    5256      IF( lk_c14b    )   CALL trc_sms_c14b   ( kt )    ! surface fluxes of C14 
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/trcstp.F90

    • Property svn:keywords deleted
    r5407 r5726  
    4040   !!---------------------------------------------------------------------- 
    4141   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    42    !! $Id$  
     42   !! $Id$ 
    4343   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    4444   !!---------------------------------------------------------------------- 
     
    8787         tra(:,:,:,:) = 0.e0 
    8888         ! 
     89# if defined key_debug_medusa 
     90         IF(lwp) WRITE(numout,*) ' MEDUSA trc_stp begins at kt =', kt 
     91         CALL flush(numout) 
     92# endif 
    8993                                   CALL trc_rst_opn  ( kt )       ! Open tracer restart file  
    9094         IF( lrst_trc )            CALL trc_rst_cal  ( kt, 'WRITE' )   ! calendar 
     
    9397         ENDIF 
    9498                                   CALL trc_sms      ( kt )       ! tracers: sinks and sources 
     99# if defined key_debug_medusa 
     100         IF(lwp) WRITE(numout,*) ' MEDUSA trc_stp SMS complete at kt =', kt 
     101         CALL flush(numout) 
     102# endif 
    95103                                   CALL trc_trp      ( kt )       ! transport of passive tracers 
     104# if defined key_debug_medusa 
     105         IF(lwp) WRITE(numout,*) ' MEDUSA trc_stp transport complete at kt =', kt 
     106         CALL flush(numout) 
     107# endif 
    96108         IF( kt == nittrc000 ) THEN 
    97109            CALL iom_close( numrtr )       ! close input tracer restart file 
     
    102114         ! 
    103115         IF( nn_dttrc /= 1   )     CALL trc_sub_reset( kt )       ! resetting physical variables when sub-stepping 
     116# if defined key_debug_medusa 
     117         IF(lwp) WRITE(numout,*) ' MEDUSA trc_stp ends at kt =', kt 
     118         CALL flush(numout) 
     119# endif 
    104120         ! 
    105121      ENDIF 
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/trcsub.F90

    • Property svn:keywords deleted
    r5215 r5726  
    4848   !!---------------------------------------------------------------------- 
    4949   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    50    !! $Id$  
     50   !! $Id$ 
    5151   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    5252   !!---------------------------------------------------------------------- 
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/trcwri.F90

    • Property svn:keywords deleted
    r3750 r5726  
    2121   USE trcwri_c14b 
    2222   USE trcwri_my_trc 
     23   USE trcwri_medusa 
    2324 
    2425   IMPLICIT NONE 
     
    5758      ! --------------------------------------- 
    5859      IF( lk_pisces  )   CALL trc_wri_pisces     ! PISCES  
     60      ! 
     61# if defined key_debug_medusa 
     62      CALL flush(numout) 
     63      IF (lwp) write (numout,*) '------------------------------' 
     64      IF (lwp) write (numout,*) 'Jpalm - debug' 
     65      IF (lwp) write (numout,*) 'Just before call trc_wri_medusa' 
     66      IF (lwp) write (numout,*) ' ' 
     67      CALL flush(numout) 
     68# endif 
     69      ! 
     70      IF( lk_medusa  )   CALL trc_wri_medusa     ! MESDUSA 
     71      ! 
     72# if defined key_debug_medusa 
     73      CALL flush(numout) 
     74      IF (lwp) write (numout,*) '------------------------------' 
     75      IF (lwp) write (numout,*) 'Jpalm - debug' 
     76      IF (lwp) write (numout,*) 'CALL trc_wri_medusa -- OK' 
     77      IF (lwp) write (numout,*) ' ' 
     78      CALL flush(numout) 
     79# endif 
     80      ! 
     81      !!! JPALM 
     82      !!! don't forget to add idtra  
    5983      IF( lk_cfc     )   CALL trc_wri_cfc        ! surface fluxes of CFC 
    6084      IF( lk_c14b    )   CALL trc_wri_c14b       ! surface fluxes of C14 
     
    78102   !!---------------------------------------------------------------------- 
    79103   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    80    !! $Id$  
     104   !! $Id$ 
    81105   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    82106   !!====================================================================== 
Note: See TracChangeset for help on using the changeset viewer.