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 765 – NEMO

Changeset 765


Ignore:
Timestamp:
2007-12-14T08:29:53+01:00 (16 years ago)
Author:
gm
Message:

dev_001_GM - create 1 parameter module by tracers (CFC, LOBSTER, PISCES..) - never compiled

Location:
branches/dev_001_GM/NEMO/TOP_SRC
Files:
1 added
6 deleted
7 edited
1 moved

Legend:

Unmodified
Added
Removed
  • branches/dev_001_GM/NEMO/TOP_SRC/CFC/trccfc.F90

    r764 r765  
    1 MODULE trcfreons 
     1MODULE trccfc 
    22   !!====================================================================== 
    3    !!                      ***  MODULE trcfreons  *** 
     3   !!                      ***  MODULE trccfc  *** 
    44   !! TOP : CFC main model 
    55   !!====================================================================== 
    66   !! History :    -   !  1999-10  (JC. Dutay)  original code 
    77   !!             1.0  !  2004-03 (C. Ethe) free form + modularity 
     8   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  reorganisation 
    89   !!---------------------------------------------------------------------- 
    910#if defined key_cfc 
    1011   !!---------------------------------------------------------------------- 
    11    !!   'key_cfc'                                        CFC chemical model 
    12    !!---------------------------------------------------------------------- 
    13    !!   trc_freons     :  compute and add CFC suface forcing to CFC trends 
    14    !!   trc_freons_cst :  sets constants for CFC surface forcing computation 
    15    !!---------------------------------------------------------------------- 
    16    USE daymod 
    17    USE sms 
    18    USE oce_trc 
    19    USE trc 
     12   !!   'key_cfc'                                               CFC tracers 
     13   !!---------------------------------------------------------------------- 
     14   !!   trc_cfc     :  compute and add CFC suface forcing to CFC trends 
     15   !!   trc_cfc_cst :  sets constants for CFC surface forcing computation 
     16   !!---------------------------------------------------------------------- 
     17   USE daymod       ! calendar 
     18   USE oce_trc      ! Ocean variables 
     19   USE par_trc      ! TOP parameters 
     20   USE trc          ! TOP variables 
    2021 
    2122   IMPLICIT NONE 
    2223   PRIVATE 
    2324 
    24    PUBLIC   trc_freons       ! called in ???     
     25   PUBLIC   trc_cfc       ! called in ???     
     26 
     27   INTEGER , PARAMETER ::   jpyear = 100   ! temporal parameter  
     28   INTEGER , PARAMETER ::   jphem  =   2   ! parameter for the 2 hemispheres 
     29   INTEGER , PUBLIC    ::   ndate_beg      ! initial calendar date (aammjj) for CFC 
     30   INTEGER , PUBLIC    ::   nyear_res      ! restoring time constant (year) 
     31   INTEGER , PUBLIC    ::   nyear_beg      ! initial year (aa)  
     32    
     33   REAL(wp), PUBLIC, DIMENSION(jpyear,jphem, jpf_cfc:jpl_cfc) ::   p_cfc   ! partial hemispheric pressure for CFC           
     34   REAL(wp), PUBLIC, DIMENSION(jpi,jpj)                       ::   xphem    ! spatial interpolation factor for patm 
     35   REAL(wp), PUBLIC, DIMENSION(jpi,jpj      ,jpf_cfc:jpl_cfc) ::   qtr      ! input function 
     36   REAL(wp), PUBLIC, DIMENSION(jpi,jpj      ,jpf_cfc:jpl_cfc) ::   qint     ! flux function 
    2537 
    2638   REAL(wp), DIMENSION(jptra) ::   soa1, soa2, soa3, soa4   ! coefficient for solubility of CFC [mol/l/atm] 
     
    3749#  include "passivetrc_substitute.h90" 
    3850   !!---------------------------------------------------------------------- 
    39    !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)  
    40    !! $Id$  
     51   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)  
     52   !! $Id:$  
    4153   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    4254   !!---------------------------------------------------------------------- 
     
    4456CONTAINS 
    4557 
    46    SUBROUTINE trc_freons( kt ) 
     58   SUBROUTINE trc_cfc( kt ) 
    4759      !!---------------------------------------------------------------------- 
    48       !!                  ***  ROUTINE trc_freons  *** 
    49       !! 
    50       !! ** Purpose :   Compute the surface boundary contition on freon 11  
    51       !!      passive tracer associated with air-mer fluxes and add it to  
    52       !!      the general trend of tracers equations. 
    53       !! 
    54       !! ** Method : 
    55       !!          - get the atmospheric partial pressure - given in pico - 
    56       !!          - computation of solubility ( in 1.e-12 mol/l then in 1.e-9 mol/m3) 
    57       !!          - computation of transfert speed ( given in cm/hour ----> cm/s ) 
    58       !!          - the input function is given by :  
    59       !!            speed * ( concentration at equilibrium - concemtration at surface ) 
    60       !!          - the input function is in pico-mol/m3/s and the 
    61       !!            freons concentration in pico-mol/m3 
     60      !!                     ***  ROUTINE trc_cfc  *** 
     61      !! 
     62      !! ** Purpose :   Compute the surface boundary contition on CFC 11  
     63      !!             passive tracer associated with air-mer fluxes and add it  
     64      !!             to the general trend of tracers equations. 
     65      !! 
     66      !! ** Method  : - get the atmospheric partial pressure - given in pico - 
     67      !!              - computation of solubility ( in 1.e-12 mol/l then in 1.e-9 mol/m3) 
     68      !!              - computation of transfert speed ( given in cm/hour ----> cm/s ) 
     69      !!              - the input function is given by :  
     70      !!                speed * ( concentration at equilibrium - concentration at surface ) 
     71      !!              - the input function is in pico-mol/m3/s and the 
     72      !!                CFC concentration in pico-mol/m3 
    6273      !!---------------------------------------------------------------------- 
    6374      INTEGER, INTENT( in ) ::   kt    ! ocean time-step index 
     
    6576      INTEGER ::   ji, jj, jn, jm 
    6677      INTEGER ::   iyear_beg, iyear_end 
    67       INTEGER ::   imonth, im1, im2 
     78      INTEGER ::   im1, im2 
    6879 
    6980      REAL(wp) ::   ztap, zdtap         
    7081      REAL(wp) ::   zt1, zt2, zt3, zv2 
    71       REAL(wp) ::   zsol   ! solubility 
    72       REAL(wp) ::   zsch   ! schmidt number  
     82      REAL(wp) ::   zsol      ! solubility 
     83      REAL(wp) ::   zsch      ! schmidt number  
     84      REAL(wp) ::   zpp_cfc   ! atmospheric partial pressure of CFC 
     85      REAL(wp) ::   zca_cfc   ! concentration at equilibrium 
     86      REAL(wp) ::   zak_cfc   ! transfert coefficients 
    7387       
    74       REAL(wp), DIMENSION(jphem,jptra) ::   zpatm       ! atmospheric function 
    75       REAL(wp), DIMENSION(jpi,jpj,jptra) ::   zca_cfc   ! concentration 
    76       REAL(wp), DIMENSION(jpi,jpj,jptra) ::   zak_cfc   ! transfert coefficients 
     88      REAL(wp), DIMENSION(jphem,jptra)   ::   zpatm       ! atmospheric function 
    7789      !!---------------------------------------------------------------------- 
    7890 
    79       IF( kt == nittrc000 )   CALL trc_freons_cst 
     91      IF( kt == nittrc000 )   CALL trc_cfc_cst 
    8092 
    8193      ! Temporal interpolation 
    8294      ! ---------------------- 
    8395      iyear_beg = nyear + ( nyear_res - 1900 - nyear_beg  ) 
    84       imonth    = nmonth 
    85  
    86       IF ( imonth .LE. 6 ) THEN 
     96      IF ( nmonth <= 6 ) THEN 
    8797         iyear_beg = iyear_beg - 2 + nyear_beg 
    88          im1       = 6 - imonth + 1 
    89          im2       = 6 + imonth - 1 
     98         im1       =  6 - nmonth + 1 
     99         im2       =  6 + nmonth - 1 
    90100      ELSE 
    91101         iyear_beg = iyear_beg - 1 + nyear_beg 
    92          im1       = 12 - imonth + 7 
    93          im2       =      imonth - 7 
     102         im1       = 12 - nmonth + 7 
     103         im2       =      nmonth - 7 
    94104      ENDIF 
    95  
    96105      iyear_end = iyear_beg + 1 
    97106 
    98107 
    99       !  Temporal and spatial interpolation at time k 
    100       ! -------------------------------------------------- 
    101       DO jn = 1, jptra 
    102          DO  jm = 1, jphem 
     108      !                                                         !------------! 
     109      DO jn = jpf_cfc, jpl_cfc                                  !  CFC loop  ! 
     110         !                                                      !------------! 
     111         ! time interpolation at time kt 
     112         DO jm = 1, jphem 
    103113            zpatm(jm,jn) = (  p_cfc(iyear_beg, jm, jn) * FLOAT (im1)  & 
    104114               &           +  p_cfc(iyear_end, jm, jn) * FLOAT (im2) ) / 12. 
    105115         END DO 
    106       END DO 
    107  
    108       DO jn = 1, jptra 
    109          pp_cfc(:,:,jn) =       xphem(:,:)   * zpatm(1,jn)   & 
    110             &           + ( 1.- xphem(:,:) ) * zpatm(2,jn) 
    111       END DO 
    112  
    113  
    114       !------------------------------------------------------------ 
    115       ! Computation of concentration at equilibrium : in picomol/l 
    116       ! ----------------------------------------------------------- 
    117  
    118       DO jn = 1, jptra 
    119          DO jj = 1 , jpj 
    120             DO ji = 1 , jpi 
     116          
     117         !                                                         !------------! 
     118         DO jj = 1, jpj                                            !  i-j loop  ! 
     119            DO ji = 1, jpi                                         !------------! 
     120  
     121               ! space interpolation 
     122               zpp_cfc  =       xphem(ji,jj)   * zpatm(1,jn)   & 
     123                  &     + ( 1.- xphem(ji,jj) ) * zpatm(2,jn) 
     124 
     125               ! Computation of concentration at equilibrium : in picomol/l 
    121126               ! coefficient for solubility for CFC-11/12 in  mol/l/atm 
    122127               IF( tmask(ji,jj,1) .GE. 0.5 ) THEN 
    123                   ztap  = ( tn(ji,jj,1) + 273.16 )* 0.01 
    124                   zdtap = ( sob3(jn) * ztap + sob2(jn))* ztap + sob1(jn)  
    125                   zsol  =  EXP ( soa1(jn) + soa2(jn) / ztap + soa3(jn) * LOG ( ztap )   & 
     128                  ztap  = ( tn(ji,jj,1) + 273.16 ) * 0.01 
     129                  zdtap = ( sob3(jn) * ztap + sob2(jn) ) * ztap + sob1(jn)  
     130                  zsol  =  EXP( soa1(jn) + soa2(jn) / ztap + soa3(jn) * LOG( ztap )   & 
    126131                     &                   + soa4(jn) * ztap * ztap + sn(ji,jj,1) * zdtap )  
    127132               ELSE 
    128                   zsol  = 0. 
     133                  zsol  = 0.e0 
    129134               ENDIF 
    130135               ! conversion from mol/l/atm to mol/m3/atm and from mol/m3/atm to mol/m3/pptv     
    131136               zsol = xconv4 * xconv3 * zsol * tmask(ji,jj,1)   
    132137               ! concentration at equilibrium 
    133                zca_cfc(ji,jj,jn) = xconv1 * pp_cfc(ji,jj,jn) * zsol * tmask(ji,jj,1)              
    134             END DO 
    135          END DO 
    136       END DO 
    137  
     138               zca_cfc = xconv1 * zpp_cfc * zsol * tmask(ji,jj,1)              
    138139   
    139       !------------------------------- 
    140       ! Computation of speed transfert 
    141       ! ------------------------------ 
    142  
    143       DO jn = 1, jptra 
    144          DO jj = 1, jpj 
    145             DO ji = 1, jpi 
    146                ! Schmidt number 
     140               ! Computation of speed transfert 
     141               !    Schmidt number 
    147142               zt1  = tn(ji,jj,1) 
    148143               zt2  = zt1 * zt1  
    149144               zt3  = zt1 * zt2 
    150145               zsch = sca1(jn) + sca2(jn) * zt1 + sca3(jn) * zt2 + sca4(jn) * zt3 
    151                ! speed transfert : formulae of wanninkhof 1992 
    152                zv2 = vatm(ji,jj) * vatm(ji,jj) 
    153                zsch = zsch / 660. 
    154                zak_cfc(ji,jj,jn) = ( 0.39 * xconv2 * zv2 / SQRT(zsch) ) * tmask(ji,jj,1) 
    155             END DO 
    156          END DO 
    157       END DO 
    158  
    159  
    160       !---------------------------------------------------------------- 
    161       ! Input function  : speed *( conc. at equil - concen at surface ) 
    162       ! trn in pico-mol/l idem qtr; ak in en m/s 
    163       !----------------------------------------------------------------- 
    164  
    165       DO jn = 1, jptra 
    166          DO jj = 1, jpj 
    167             DO ji = 1, jpi 
    168                qtr(ji,jj,jn) = -zak_cfc(ji,jj,jn) * ( trb(ji,jj,1,jn) - zca_cfc(ji,jj,jn) )   & 
     146               !    speed transfert : formulae of wanninkhof 1992 
     147               zv2     = vatm(ji,jj) * vatm(ji,jj) 
     148               zsch    = zsch / 660. 
     149               zak_cfc = ( 0.39 * xconv2 * zv2 / SQRT(zsch) ) * tmask(ji,jj,1) 
     150 
     151               ! Input function  : speed *( conc. at equil - concen at surface ) 
     152               ! trn in pico-mol/l idem qtr; ak in en m/s 
     153               qtr(ji,jj,jn) = -zak_cfc * ( trb(ji,jj,1,jn) - zca_cfc )   & 
    169154#if defined key_off_degrad 
    170                   &                               * facvol(ji,jj,1)                           & 
     155                  &                     * facvol(ji,jj,1)                           & 
    171156#endif 
    172                   &                               * tmask(ji,jj,1) * ( 1. - freeze(ji,jj) ) 
    173             END DO 
    174          END DO 
    175       END DO 
    176  
    177  
    178       ! --------------------- 
    179       ! Add the trend 
    180       ! --------------------- 
    181  
    182       DO jn = 1, jptra 
    183          DO  jj = 1, jpj 
    184             DO  ji = 1, jpi 
     157                  &                     * tmask(ji,jj,1) * ( 1. - freeze(ji,jj) ) 
     158 
     159               ! Add the surface flux to the trend 
    185160               tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + qtr(ji,jj,jn) / fse3t(ji,jj,1)  
    186             END DO 
    187          END DO 
    188       END DO 
    189  
    190       ! -------------------------------------------- 
    191       ! cumulation of tracer flux at each time step 
    192       ! -------------------------------------------- 
    193       DO jn = 1, jptra 
    194          DO jj = 1, jpj 
    195             DO ji = 1, jpi 
     161 
     162               ! cumulation of surface flux at each time step 
    196163               qint(ji,jj,jn) = qint (ji,jj,jn) + qtr(ji,jj,jn) * rdt 
    197             END DO 
    198          END DO 
    199       END DO 
    200       ! 
    201    END SUBROUTINE trc_freons 
    202  
    203  
    204    SUBROUTINE trc_freons_cst 
     164               !                                               !----------------! 
     165            END DO                                             !  end i-j loop  ! 
     166         END DO                                                !----------------! 
     167         !                                                  !----------------! 
     168      END DO                                                !  end CFC loop  ! 
     169      !                                                     !----------------! 
     170   END SUBROUTINE trc_cfc 
     171 
     172 
     173   SUBROUTINE trc_cfc_cst 
    205174      !!--------------------------------------------------------------------- 
    206       !!                     ***  trc_freons_cst  ***   
     175      !!                     ***  trc_cfc_cst  ***   
    207176      !! 
    208177      !! ** Purpose : sets constants for CFC model 
     
    217186            soa2(jn) =  319.6552 
    218187            soa3(jn) =  119.4471 
    219             soa4(jn) =  -1.39165 
    220             sob1(jn) =  -0.142382 
    221             sob2(jn) =   0.091459 
    222             sob3(jn) =  -0.0157274 
     188            soa4(jn) =   -1.39165 
     189            sob1(jn) =   -0.142382 
     190            sob2(jn) =    0.091459 
     191            sob3(jn) =   -0.0157274 
    223192             
    224193            ! coefficients for schmidt number in degre Celcius 
    225194            sca1(jn) = 3501.8 
    226195            sca2(jn) = -210.31 
    227             sca3(jn) = 6.1851 
    228             sca4(jn) = -0.07513 
     196            sca3(jn) =    6.1851 
     197            sca4(jn) =   -0.07513 
    229198 
    230199         ELSE IF( jn == jp12 ) THEN 
     
    234203            soa2(jn) =  298.9702 
    235204            soa3(jn) =  113.8049 
    236             soa4(jn) =  -1.39165 
    237             sob1(jn) =  -0.143566 
    238             sob2(jn) =   0.091015 
    239             sob3(jn) =  -0.0153924 
     205            soa4(jn) =   -1.39165 
     206            sob1(jn) =   -0.143566 
     207            sob2(jn) =    0.091015 
     208            sob3(jn) =   -0.0153924 
    240209                         
    241210            ! coefficients for schmidt number in degre Celcius 
    242211            sca1(jn) =  3845.4  
    243             sca2(jn) = -228.95 
    244             sca3(jn) = 6.1908  
    245             sca4(jn) = -0.067430 
     212            sca2(jn) =  -228.95 
     213            sca3(jn) =     6.1908  
     214            sca4(jn) =    -0.067430 
    246215         ENDIF 
    247216      ENDDO 
     
    256225      END DO 
    257226      ! 
    258    END SUBROUTINE trc_freons_cst 
     227   END SUBROUTINE trc_cfc_cst 
    259228    
    260229#else 
    261230   !!---------------------------------------------------------------------- 
    262    !!   Dummy module                                           No CFC model 
     231   !!   Dummy module                                         No CFC tracers 
    263232   !!---------------------------------------------------------------------- 
    264233CONTAINS 
    265    SUBROUTINE trc_freons( kt )       ! Empty routine 
    266       WRITE(*,*) 'trc_freons: You should not have seen this print! error?', kt 
    267    END SUBROUTINE trc_freons 
     234   SUBROUTINE trc_cfc( kt )       ! Empty routine 
     235      WRITE(*,*) 'trc_cfc: You should not have seen this print! error?', kt 
     236   END SUBROUTINE trc_cfc 
    268237#endif 
    269238 
    270239   !!====================================================================== 
    271 END MODULE trcfreons 
     240END MODULE trccfc 
  • branches/dev_001_GM/NEMO/TOP_SRC/CFC/trcctl.cfc.h90

    r764 r765  
    2525              WRITE (numout,*) ' =======   ============= ' 
    2626              WRITE (numout,*)                             & 
    27               &   ' STOP, change jptra to 1 or 2 in par_sms_cfc.h90 
     27              &   ' STOP, change jptra to 1 or 2 in par_CFC module 
    2828          END IF  
    2929          STOP 'TRC_CTL' 
  • branches/dev_001_GM/NEMO/TOP_SRC/par_trc.F90

    r763 r765  
    88   !!              -   !  2000-04  (O. Aumont, M.A. Foujols)  HAMOCC3 and P3ZD 
    99   !!             1.0  !  2004-03  (C. Ethe) Free form and module 
    10    !!             2.0  !  2007-12  (C. Ethe, G. Madec)  rewritting 
     10   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  revised architecture 
    1111   !!---------------------------------------------------------------------- 
    1212   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)  
    13    !! $Header:$  
     13   !! $Id:$  
    1414   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    1515   !!---------------------------------------------------------------------- 
    16 #if defined key_passivetrc 
    17    !!---------------------------------------------------------------------- 
    18    !!   'key_passivetrc'                                    Passive tracers 
    19    !!---------------------------------------------------------------------- 
    20    USE par_trc_trp 
     16   USE par_LOBSTER   ! LOBSTER model 
     17   USE par_PISCES    ! PISCES  model 
     18   USE par_CFC       ! CFC 11 and 12 tracers 
     19   USE par_MY_TRC    ! user defined passive tracers 
    2120 
    2221   IMPLICIT NONE 
    2322   PUBLIC 
    2423 
    25 # if defined key_trc_diatrd 
    26    !!---------------------------------------------------------------------- 
    27    !!   'key_trc_diatrd'                                  trend diagnostics 
    28    !!---------------------------------------------------------------------- 
    29 #  if defined key_trcldf_eiv 
    30 #   if defined key_trcdmp 
    31    INTEGER, PARAMETER :: jpdiatrc = 11      !: trends: 3*(advection + diffusion + eiv ) + damping + sms 
    32 #   else 
    33    INTEGER, PARAMETER :: jpdiatrc = 10      !: trends: 3*(advection + diffusion + eiv )           + sms 
    34 #   endif 
    35 #  else 
    36 #   if defined key_trcdmp 
    37    INTEGER, PARAMETER :: jpdiatrc =  8      !: trends: 3*(advection + diffusion       ) + damping + sms 
    38 #   else 
    39    INTEGER, PARAMETER :: jpdiatrc =  7      !: trends: 3*(advection + diffusion       ) + damping + sms 
    40 #   endif 
    41 #  endif 
    42  
     24   ! Passive tracers : Total size 
     25   ! ---------------               ! total number of passive tracers, of 2d and 3d output and trend arrays 
     26   INTEGER, PUBLIC, PARAMETER ::   jptra    =  jp_lobster    + jp_pisces     + jp_cfc     + jp_my_trc 
     27   INTEGER, PUBLIC, PARAMETER ::   jpdia2d  =  jp_lobster_2d + jp_pisces_2d  + jp_cfc_2d  + jp_my_trc_2d 
     28   INTEGER, PUBLIC, PARAMETER ::   jpdia3d  =  jp_lobster_3d + jp_pisces_3d  + jp_cfc_3d  + jp_my_trc_3d 
     29   !                     ! total number of sms diagnostic arrays 
     30   INTEGER, PUBLIC, PARAMETER ::   jpdiabio = jp_lobster_trd + jp_pisces_trd + jp_cfc_trd + jp_my_trc_trd 
     31    
     32   !  1D configuration ("key_cfg_1d") 
     33   ! ----------------- 
     34# if defined key_cfg_1d 
     35   LOGICAL, PUBLIC, PARAMETER ::   lk_trccfg_1d   = .TRUE.   !: 1D pass. tracer configuration flag 
     36# else    
     37   LOGICAL, PUBLIC, PARAMETER ::   lk_trccfg_1d   = .FALSE.  !: 1D pass. tracer configuration flag 
    4338# endif 
    4439 
     40   ! Passive tracers : size for TRP trends diagnotics (used if 'key_trc_diatrd' defined) 
     41#if defined key_trcldf_eiv 
     42# if defined key_trcdmp 
     43   INTEGER, PARAMETER :: jpdiatrc = 11      !: trends: 3*(advection + diffusion + eiv ) + damping + sms 
     44# else 
     45   INTEGER, PARAMETER :: jpdiatrc = 10      !: trends: 3*(advection + diffusion + eiv )           + sms 
     46# endif 
    4547#else 
    46    !!====================================================================== 
    47    !!  Empty module :                                     No passive tracer  
    48    !!====================================================================== 
     48# if defined key_trcdmp 
     49   INTEGER, PARAMETER :: jpdiatrc =  8      !: trends: 3*(advection + diffusion       ) + damping + sms 
     50# else 
     51   INTEGER, PARAMETER :: jpdiatrc =  7      !: trends: 3*(advection + diffusion       ) + damping + sms 
     52# endif 
    4953#endif 
    5054 
  • branches/dev_001_GM/NEMO/TOP_SRC/prtctl_trc.F90

    r763 r765  
    1515   !!   prt_ctl_trc_init :   ??? 
    1616   !!---------------------------------------------------------------------- 
    17    USE par_trc_trp      ! ??? 
     17   USE par_trc          ! TOP parameters 
    1818   USE oce_trc          ! ocean space and time domain variables 
    1919   USE in_out_manager   ! I/O manager 
  • branches/dev_001_GM/NEMO/TOP_SRC/sms.F90

    r764 r765  
    1717   USE par_oce 
    1818   USE par_trc 
    19    USE par_sms 
    2019 
    2120   IMPLICIT NONE 
     
    3433#  include "sms_pisces.h90" 
    3534 
    36 # elif defined key_cfc 
    37    !!---------------------------------------------------------------------- 
    38    !!   'key_cfc  '                                      CFC chemical model                   
    39    !!---------------------------------------------------------------------- 
    40 #  include "sms_cfc.h90" 
    41  
    4235# endif 
    4336 
  • branches/dev_001_GM/NEMO/TOP_SRC/trcdta.F90

    r763 r765  
    1515   !!---------------------------------------------------------------------- 
    1616   USE oce_trc 
     17   USE par_trc 
    1718   USE trc 
    18    USE par_sms 
    1919   USE lib_print 
    2020   USE iom 
  • branches/dev_001_GM/NEMO/TOP_SRC/trcsms.F90

    r763 r765  
    55   !!====================================================================== 
    66   !! History :   1.0  !  2005-03 (O. Aumont, A. El Moussaoui) F90 
     7   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  revised architecture 
    78   !!---------------------------------------------------------------------- 
    89#if defined key_passivetrc 
     
    1011   !!   'key_passivetrc'                                    Passive tracers 
    1112   !!---------------------------------------------------------------------- 
    12    !!   trc_sms    :  Time loop of passive tracers sms 
     13   !!   trc_sms        :  Time loop of passive tracers sms 
    1314   !!---------------------------------------------------------------------- 
    14    USE oce_trc 
    15    USE trc 
    16    USE trcfreons 
    17    USE prtctl_trc           ! Print control for debbuging 
     15   USE oce_trc         ! 
     16   USE trc             ! 
     17   USE trccfc          ! CFC 11 & 12  
     18   USE prtctl_trc      ! Print control for debbuging 
    1819 
    1920   IMPLICIT NONE 
    2021   PRIVATE 
    2122 
    22    PUBLIC      trc_sms      ! called in ??? 
     23   PUBLIC   trc_sms    ! called in trcstp.F90 
    2324 
    2425   !!---------------------------------------------------------------------- 
    25    !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)  
     26   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)  
    2627   !! $Header:$  
    2728   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     
    9798      ! ------------------ 
    9899 
    99       CALL trc_freons( kt )      ! surface fluxes of CFC 
     100      IF( lk_trc_cfc )   CALL trc_cfc( kt )      ! surface fluxes of CFC 
    100101 
    101102#endif 
     103 
     104      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     105         WRITE(charout, FMT="('SMS')") 
     106         CALL prt_ctl_trc_info(charout) 
     107         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm) 
     108      ENDIF 
    102109      ! 
    103110   END SUBROUTINE trc_sms 
  • branches/dev_001_GM/NEMO/TOP_SRC/trp_trc.F90

    r764 r765  
    1616 
    1717   !! passive tracers number 
    18    USE par_trc_trp , ONLY :   jptra    =>   jptra    !: number of passive tracers 
     18   USE par_trc, ONLY :   jptra    =>   jptra    !: number of passive tracers 
    1919 
    2020   !! passive tracers fields  
    21    USE trc         , ONLY :   trai     =>   trai     !: initial total tracer 
    22    USE trc         , ONLY :   trb      =>   trb      !: tracer field (before) 
    23    USE trc         , ONLY :   tra      =>   tra      !: tracer field (now) 
    24    USE trc         , ONLY :   trn      =>   trn      !: tracer field (after) 
     21   USE trc    , ONLY :   trai     =>   trai     !: initial total tracer 
     22   USE trc    , ONLY :   trb      =>   trb      !: tracer field (before) 
     23   USE trc    , ONLY :   tra      =>   tra      !: tracer field (now) 
     24   USE trc    , ONLY :   trn      =>   trn      !: tracer field (after) 
    2525 
    2626   !! time step 
    27    USE trc         , ONLY :   ndttrc   =>   ndttrc   !: frequency of step on passive tracers (NAMELIST) 
     27   USE trc    , ONLY :   ndttrc   =>   ndttrc   !: frequency of step on passive tracers (NAMELIST) 
    2828 
    2929   !! non-centered advection scheme (smolarkiewicz) 
    30    USE trc         , ONLY :   rtrn     =>   rtrn     !: value for truncation (NAMELIST) 
    31    USE trc         , ONLY :   ctrcnm   =>   ctrcnm   !: value for truncation (NAMELIST) 
     30   USE trc    , ONLY :   rtrn     =>   rtrn     !: value for truncation (NAMELIST) 
     31   USE trc    , ONLY :   ctrcnm   =>   ctrcnm   !: value for truncation (NAMELIST) 
    3232 
    3333# if defined key_trc_diaadd 
    34    USE par_trc_trp , ONLY :   jpdia2d  =>  jpdia2d   !: number of 2D passive tracers diag 
    35    USE par_trc_trp , ONLY :   jpdia3d  =>  jpdia3d   !: number of 3D passive tracers diag 
    36    USE trc         , ONLY :   trc2d    =>   trc2d    !: additional 2D variable for ouputs 
    37    USE trc         , ONLY :   trc3d    =>   trc3d    !: additional 3D variable for ouputs 
     34   USE par_trc, ONLY :   jpdia2d  =>  jpdia2d   !: number of 2D passive tracers diag 
     35   USE par_trc, ONLY :   jpdia3d  =>  jpdia3d   !: number of 3D passive tracers diag 
     36   USE trc    , ONLY :   trc2d    =>   trc2d    !: additional 2D variable for ouputs 
     37   USE trc    , ONLY :   trc3d    =>   trc3d    !: additional 3D variable for ouputs 
    3838# endif 
    3939 
Note: See TracChangeset for help on using the changeset viewer.