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 2047 for trunk/NEMO/TOP_SRC/CFC – NEMO

Ignore:
Timestamp:
2010-08-13T09:58:59+02:00 (14 years ago)
Author:
cetlod
Message:

Improve CFC and Bomb C14 models, see ticket:700

Location:
trunk/NEMO/TOP_SRC/CFC
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/TOP_SRC/CFC/par_cfc.F90

    r1253 r2047  
    2121 
    2222   IMPLICIT NONE 
    23    PUBLIC 
    2423 
    25    INTEGER, PUBLIC, PARAMETER ::   jp_lp      = jp_lobster     + jp_pisces     !: cumulative number of passive tracers 
    26    INTEGER, PUBLIC, PARAMETER ::   jp_lp_2d   = jp_lobster_2d  + jp_pisces_2d  !: 
    27    INTEGER, PUBLIC, PARAMETER ::   jp_lp_3d   = jp_lobster_3d  + jp_pisces_3d  !: 
    28    INTEGER, PUBLIC, PARAMETER ::   jp_lp_trd  = jp_lobster_trd + jp_pisces_trd !: 
     24   INTEGER, PARAMETER ::   jp_lc      = jp_lobster     + jp_pisces     !: cumulative number of passive tracers 
     25   INTEGER, PARAMETER ::   jp_lc_2d   = jp_lobster_2d  + jp_pisces_2d  !: 
     26   INTEGER, PARAMETER ::   jp_lc_3d   = jp_lobster_3d  + jp_pisces_3d  !: 
     27   INTEGER, PARAMETER ::   jp_lc_trd  = jp_lobster_trd + jp_pisces_trd !: 
    2928    
    3029#if defined key_cfc 
     
    3938    
    4039   ! assign an index in trc arrays for each CFC prognostic variables 
    41    INTEGER, PUBLIC, PARAMETER ::   jpc11       = jp_lp + 1   !: CFC-11  
    42    INTEGER, PUBLIC, PARAMETER ::   jpc12       = jp_lp + 2   !: CFC-12    
     40   INTEGER, PUBLIC, PARAMETER ::   jpc11       = jp_lc + 1   !: CFC-11  
     41   INTEGER, PUBLIC, PARAMETER ::   jpc12       = jp_lc + 2   !: CFC-12    
    4342#else 
    4443   !!--------------------------------------------------------------------- 
     
    5352 
    5453   ! Starting/ending CFC do-loop indices (N.B. no CFC : jp_cfc0 > jp_cfc1 the do-loop are never done) 
    55    INTEGER, PUBLIC, PARAMETER ::   jp_cfc0     = jp_lp + 1       !: First index of CFC tracers 
    56    INTEGER, PUBLIC, PARAMETER ::   jp_cfc1     = jp_lp + jp_cfc  !: Last  index of CFC tracers 
    57    INTEGER, PUBLIC, PARAMETER ::   jp_cfc0_2d  = jp_lp_2d  + 1       !: First index of CFC tracers 
    58    INTEGER, PUBLIC, PARAMETER ::   jp_cfc1_2d  = jp_lp_2d  + jp_cfc_2d  !: Last  index of CFC tracers 
    59    INTEGER, PUBLIC, PARAMETER ::   jp_cfc0_3d  = jp_lp_3d  + 1       !: First index of CFC tracers 
    60    INTEGER, PUBLIC, PARAMETER ::   jp_cfc1_3d  = jp_lp_3d  + jp_cfc_3d  !: Last  index of CFC tracers 
    61    INTEGER, PUBLIC, PARAMETER ::   jp_cfc0_trd = jp_lp_trd + 1       !: First index of CFC tracers 
    62    INTEGER, PUBLIC, PARAMETER ::   jp_cfc1_trd = jp_lp_trd + jp_cfc_trd  !: Last  index of CFC tracers 
     54   INTEGER, PUBLIC, PARAMETER ::   jp_cfc0     = jp_lc + 1       !: First index of CFC tracers 
     55   INTEGER, PUBLIC, PARAMETER ::   jp_cfc1     = jp_lc + jp_cfc  !: Last  index of CFC tracers 
     56   INTEGER, PUBLIC, PARAMETER ::   jp_cfc0_2d  = jp_lc_2d  + 1       !: First index of CFC tracers 
     57   INTEGER, PUBLIC, PARAMETER ::   jp_cfc1_2d  = jp_lc_2d  + jp_cfc_2d  !: Last  index of CFC tracers 
     58   INTEGER, PUBLIC, PARAMETER ::   jp_cfc0_3d  = jp_lc_3d  + 1       !: First index of CFC tracers 
     59   INTEGER, PUBLIC, PARAMETER ::   jp_cfc1_3d  = jp_lc_3d  + jp_cfc_3d  !: Last  index of CFC tracers 
     60   INTEGER, PUBLIC, PARAMETER ::   jp_cfc0_trd = jp_lc_trd + 1       !: First index of CFC tracers 
     61   INTEGER, PUBLIC, PARAMETER ::   jp_cfc1_trd = jp_lc_trd + jp_cfc_trd  !: Last  index of CFC tracers 
    6362 
    6463   !!====================================================================== 
  • trunk/NEMO/TOP_SRC/CFC/trcctl_cfc.F90

    r1801 r2047  
    5353      ! Check tracer names 
    5454      ! ------------------ 
    55       IF ( ctrcnm(jpc11) /= 'CFC11' .OR. ctrcnm(jpc12) /= 'CFC12' ) THEN  
    56             ctrcnm(jpc11) = 'CFC11' 
    57             ctrcnl(jpc11) = 'Chlorofuorocarbone 11 concentration' 
    58             ctrcnm(jpc12) = 'CFC12' 
    59             ctrcnl(jpc12) = 'Chlorofuorocarbone 12 concentration'  
     55      ctrcnm(jpc11) = 'CFC11' 
     56      ctrcnl(jpc11) = 'Chlorofuorocarbone 11 concentration' 
     57 
     58      IF ( jp_cfc == 2 ) THEN 
     59          ctrcnm(jpc12) = 'CFC12' 
     60          ctrcnl(jpc12) = 'Chlorofuorocarbone 12 concentration' 
    6061      ENDIF 
    6162 
    6263      IF(lwp) THEN 
    63          WRITE (numout,*) ' ===>>>> : w a r n i n g <<<<===' 
     64         WRITE (numout,*) ' ===>>>> : w a r n i n g ' 
     65         WRITE (numout,*) ' =======   ============= ' 
    6466         WRITE (numout,*) ' we force tracer names' 
    6567         DO jl = 1, jp_cfc 
     
    6870         END DO 
    6971         WRITE(numout,*) ' ' 
    70       ENDIF  
     72      ENDIF 
    7173 
    7274 
  • trunk/NEMO/TOP_SRC/CFC/trcini_cfc.F90

    r1581 r2047  
    2222 
    2323   PUBLIC   trc_ini_cfc   ! called by trcini.F90 module 
     24 
     25   CHARACTER (len=34) ::   clname = 'cfc1112.atm'   ! ??? 
    2426 
    2527   INTEGER  ::   inum                   ! unit number 
     
    5557      ! ---------------------------------------  
    5658      xphem (:,:)    = 0.e0 
    57       DO jl = 1, jp_cfc 
    58          jn = jp_cfc0 + jl - 1 
    59          DO jm = 1, jphem 
    60             DO js = 1, jpyear 
    61                p_cfc(js,jm,jn) = 0.0 
    62             END DO 
    63          END DO 
    64       END DO 
    65        
     59      p_cfc(:,:,:)   = 0.e0 
    6660       
    6761      ! Initialization of qint in case of  no restart  
     
    7367            WRITE(numout,*) 'Initialization de qint ; No restart : qint equal zero ' 
    7468         ENDIF 
     69         qint_cfc(:,:,:) = 0.e0 
    7570         DO jl = 1, jp_cfc 
    7671            jn = jp_cfc0 + jl - 1 
    7772            trn     (:,:,:,jn) = 0.e0 
    78             qint_cfc(:,:  ,jn) = 0.e0 
    7973         END DO 
    8074      ENDIF 
     
    8882      IF(lwp) WRITE(numout,*) 'read of formatted file cfc1112atm' 
    8983       
    90       CALL ctl_opn( inum, 'cfc1112.atm', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
     84      CALL ctl_opn( inum, clname, 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) 
    9185      REWIND(inum) 
    9286       
     
    9589      END DO 
    9690    
    97       DO jn = 31, 98      !   Read file 
    98          READ(inum,*) zyy, p_cfc(jn,1,1), p_cfc(jn,1,2), p_cfc(jn,2,1), p_cfc(jn,2,2) 
    99          WRITE(numout,'(f7.2, 4f8.2)' ) & 
     91      ! file starts in 1931 do jn represent the year in the century.jhh 
     92      ! Read file till the end 
     93      jn = 31 
     94      DO WHILE ( 1 /= 2 ) 
     95         READ(inum,*,END=100) zyy, p_cfc(jn,1,1), p_cfc(jn,1,2), p_cfc(jn,2,1), p_cfc(jn,2,2) 
     96         IF ( lwp) THEN 
     97           WRITE(numout,'(f7.2, 4f8.2)' ) & 
    10098            &         zyy, p_cfc(jn,1,1), p_cfc(jn,1,2), p_cfc(jn,2,1), p_cfc(jn,2,2) 
     99         ENDIF 
     100         jn = jn + 1 
    101101      END DO 
     102 100  npyear = jn - 1 
     103      IF ( lwp) WRITE(numout,*) '    ', npyear ,' years read' 
    102104 
    103105      p_cfc(32,1:2,1) = 5.e-4      ! modify the values of the first years 
  • trunk/NEMO/TOP_SRC/CFC/trcsms_cfc.F90

    r1459 r2047  
    2727   PUBLIC   trc_sms_cfc       ! called in ???     
    2828 
    29    INTEGER , PUBLIC, PARAMETER ::   jpyear = 100   ! temporal parameter  
     29   INTEGER , PUBLIC, PARAMETER ::   jpyear = 150   ! temporal parameter  
    3030   INTEGER , PUBLIC, PARAMETER ::   jphem  =   2   ! parameter for the 2 hemispheres 
    3131   INTEGER , PUBLIC    ::   ndate_beg      ! initial calendar date (aammjj) for CFC 
    3232   INTEGER , PUBLIC    ::   nyear_res      ! restoring time constant (year) 
    3333   INTEGER , PUBLIC    ::   nyear_beg      ! initial year (aa)  
     34   INTEGER , PUBLIC    ::   npyear         ! Number of years read in CFC1112 file 
    3435    
    3536   REAL(wp), PUBLIC, DIMENSION(jpyear,jphem, jp_cfc) ::   p_cfc    ! partial hemispheric pressure for CFC           
     
    9697      ! Temporal interpolation 
    9798      ! ---------------------- 
    98       iyear_beg = nyear + ( nyear_res - 1900 - nyear_beg  ) 
     99      iyear_beg = nyear - 1900 
    99100      IF ( nmonth <= 6 ) THEN 
    100          iyear_beg = iyear_beg - 2 + nyear_beg 
     101         iyear_beg = iyear_beg - 1 
    101102         im1       =  6 - nmonth + 1 
    102103         im2       =  6 + nmonth - 1 
    103104      ELSE 
    104          iyear_beg = iyear_beg - 1 + nyear_beg 
    105105         im1       = 12 - nmonth + 7 
    106106         im2       =      nmonth - 7 
Note: See TracChangeset for help on using the changeset viewer.