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 1534 for trunk/NEMO/OPA_SRC/SBC/sbccpl.F90 – NEMO

Ignore:
Timestamp:
2009-07-24T12:35:25+02:00 (15 years ago)
Author:
cetlod
Message:

Improve the coupling interface for the carbon cycle, see ticket:488

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/SBC/sbccpl.F90

    r1523 r1534  
    66   !! History :  2.0  !  06-2007  (R. Redler, N. Keenlyside, W. Park) Original code split into flxmod & taumod 
    77   !!            3.0  !  02-2008  (G. Madec, C Talandier)  surface module 
    8    !!            3.1  !  02-2009  (G. Madec, S. Masson, E. Maisonave, A. Caubel) generic coupled interface 
     8   !!            3.1  !  02-2009  (S. Masson, E. Maisonave, A. Caubel) generic coupled interface 
    99   !!---------------------------------------------------------------------- 
    1010#if defined key_oasis3 || defined key_oasis4 
     
    2727#endif 
    2828#if defined key_lim2 
    29    USE ice_2, ONLY : hicif, hsnif          ! Ice and Snow thickness 
     29   USE par_ice_2       ! ice parameters 
     30   USE ice_2           ! ice variables 
    3031#endif 
    3132   USE cpl_oasis3      ! OASIS3 coupling 
     
    4142   USE mod_prism_proto ! OASIS3 prism module: PRISM_* variables... 
    4243   USE phycst, ONLY : xlsn, rhosn 
     44#if defined key_cpl_carbon_cycle 
     45   USE p4zflx, ONLY : oce_co2 
     46#endif 
    4347   IMPLICIT NONE 
    4448   PRIVATE 
     
    7882   INTEGER, PARAMETER ::   jpr_rnf    = 28            !  
    7983   INTEGER, PARAMETER ::   jpr_cal    = 29            !  
     84#if ! defined key_cpl_carbon_cycle 
    8085   INTEGER, PARAMETER ::   jprcv      = 29            ! total number of fields recieved 
    81     
     86#else 
     87   INTEGER, PARAMETER ::   jpr_co2    = 30 
     88   INTEGER, PARAMETER ::   jprcv      = 30            ! total number of fields recieved 
     89#endif    
    8290   INTEGER, PARAMETER ::   jps_fice   =  1            ! ice fraction  
    8391   INTEGER, PARAMETER ::   jps_toce   =  2            ! ocean temperature 
     
    94102   INTEGER, PARAMETER ::   jps_ivy1   = 13            ! 
    95103   INTEGER, PARAMETER ::   jps_ivz1   = 14            ! 
     104#if ! defined key_cpl_carbon_cycle 
    96105   INTEGER, PARAMETER ::   jpsnd      = 14            ! total number of fields sended 
    97     
     106#else 
     107   INTEGER, PARAMETER ::   jps_co2    = 15 
     108   INTEGER, PARAMETER ::   jpsnd      = 15            ! total number of fields sended 
     109#endif    
    98110   !                                                         !!** namelist namsbc_cpl ** 
    99111   ! Send to the atmosphere                                   ! 
     
    105117   CHARACTER(len=100) ::   cn_snd_crt_orient  = 'local grid'  ! 'eastward-northward' or 'local grid' 
    106118   CHARACTER(len=100) ::   cn_snd_crt_grid    = 'T'           ! always at 'T' point 
    107     
     119#if defined key_cpl_carbon_cycle  
     120   CHARACTER(len=100) ::   cn_snd_co2         = 'none'        ! 'none' or 'coupled' 
     121#endif 
    108122   ! Recieved from the atmosphere                             ! 
    109123   CHARACTER(len=100) ::   cn_rcv_tau_nature  = 'oce only'    ! 'oce only' 'oce and ice' or 'mixed oce-ice' 
     
    118132   CHARACTER(len=100) ::   cn_rcv_rnf         = 'coupled'     ! 'coupled' 'climato' or 'mixed' 
    119133   CHARACTER(len=100) ::   cn_rcv_cal         = 'none'        ! 'none' or 'coupled' 
     134#if defined key_cpl_carbon_cycle  
     135   CHARACTER(len=100) ::   cn_rcv_co2         = 'none'        ! 'none' or 'coupled' 
     136#endif 
    120137 
    121138!!   CHARACTER(len=100), PUBLIC ::   cn_rcv_rnf   !: ???             ==>>  !!gm   treat this case in a different maner 
     
    160177         cn_rcv_tau_nature, cn_rcv_tau_refere , cn_rcv_tau_orient, cn_rcv_tau_grid ,                 & 
    161178         cn_rcv_dqnsdt    , cn_rcv_qsr        , cn_rcv_qns       , cn_rcv_emp      , cn_rcv_rnf , cn_rcv_cal 
     179#if defined key_cpl_carbon_cycle  
     180      NAMELIST/namsbc_cpl_co2/  cn_snd_co2, cn_rcv_co2 
     181#endif 
    162182      !!--------------------------------------------------------------------- 
    163183 
     
    195215      ENDIF 
    196216 
     217#if defined key_cpl_carbon_cycle  
     218      REWIND( numnam )                    ! ... read namlist namsbc_cpl_co2 
     219      READ  ( numnam, namsbc_cpl_co2 ) 
     220      IF(lwp) THEN                        ! control print 
     221         WRITE(numout,*) 
     222         WRITE(numout,*)'sbc_cpl_init : namsbc_cpl_co2 namelist ' 
     223         WRITE(numout,*)'~~~~~~~~~~~~' 
     224         WRITE(numout,*)'   received fields' 
     225         WRITE(numout,*)'       atm co2                            cn_rcv_co2         = ', cn_rcv_co2 
     226         WRITE(numout,*)'   sent fields' 
     227         WRITE(numout,*)'      oce co2 flux                        cn_snd_co2         = ', cn_snd_co2 
     228          WRITE(numout,*) 
     229      ENDIF 
     230#endif 
    197231      ! save current & stress in an array and suppress possible blank in the name 
    198232      cn_snd_crt(1) = TRIM( cn_snd_crt_nature )   ;   cn_snd_crt(2) = TRIM( cn_snd_crt_refere ) 
     
    372406      !                                                      !      10m wind module      !    
    373407      !                                                      ! ------------------------- ! 
    374       srcv(jpr_w10m  )%clname = 'O_Wind10'   ;   IF( TRIM(cn_rcv_w10m) == 'coupled' )   srcv(jpr_w10m)%laction = .TRUE.      
     408      srcv(jpr_w10m)%clname = 'O_Wind10'   ;   IF( TRIM(cn_rcv_w10m) == 'coupled' )   srcv(jpr_w10m)%laction = .TRUE.      
     409 
     410#if defined key_cpl_carbon_cycle 
     411      !                                                      ! ------------------------- ! 
     412      !                                                      !      Atmospheric CO2      ! 
     413      !                                                      ! ------------------------- ! 
     414      srcv(jpr_co2 )%clname = 'O_AtmCO2'   ;   IF( TRIM(cn_rcv_co2) == 'coupled' )    srcv(jpr_co2 )%laction = .TRUE. 
     415#endif 
    375416      
    376417      ! ================================ ! 
     
    450491      END SELECT 
    451492 
     493#if defined key_cpl_carbon_cycle 
     494      !                                                      ! ------------------------- ! 
     495      !                                                      !          CO2 flux         ! 
     496      !                                                      ! ------------------------- ! 
     497      ssnd(jps_co2)%clname = 'O_CO2FLX' ;  IF( TRIM(cn_snd_co2) == 'coupled' )    ssnd(jps_co2 )%laction = .TRUE. 
     498#endif 
     499      ! 
    452500      ! ================================ ! 
    453501      !   initialisation of the coupler  ! 
     
    632680         ! it not, we call sbc_tau2wnd in sbc_cpl_rcv (or later, after the ice???) 
    633681         ! 
     682#if defined  key_cpl_carbon_cycle 
     683         !                                                              ! atmosph. CO2 (ppm) 
     684         IF( srcv(jpr_co2)%laction )   atm_co2(:,:) = frcv(:,:,jpr_co2) 
     685#endif 
     686 
    634687      ENDIF 
    635688      ! 
     
    10701123      IF( ssnd(jps_hsnw)%laction )   CALL cpl_prism_snd( jps_hsnw, isec, hsnif(:,:) * fr_i(:,:), info ) 
    10711124      ! 
    1072       !                                                      ! ------------------------- ! 
     1125#if defined key_cpl_carbon_cycle 
     1126      !                                                      ! ------------------------- ! 
     1127      !                                                      !  CO2 flux from PISCES     !  
     1128      !                                                      ! ------------------------- ! 
     1129      IF( ssnd(jps_co2)%laction )   CALL cpl_prism_snd( jps_co2, isec, oce_co2 , info ) 
     1130      ! 
     1131#endif 
    10731132      IF( ssnd(jps_ocx1)%laction ) THEN                      !      Surface current      ! 
    10741133         !                                                   ! ------------------------- ! 
     
    11971256         IF( ssnd(jps_ivy1)%laction )   CALL cpl_prism_snd( jps_ivy1, isec, zity1, info )   ! ice   y current 1st grid 
    11981257         IF( ssnd(jps_ivz1)%laction )   CALL cpl_prism_snd( jps_ivz1, isec, zitz1, info )   ! ice   z current 1st grid 
    1199          ! 
     1258         !  
    12001259      ENDIF 
    12011260   ! 
     
    12391298      REAL(wp), INTENT(in   ), DIMENSION(:,:  ), OPTIONAL ::   psst    ! sea surface temperature      [Celcius] 
    12401299      REAL(wp), INTENT(in   ), DIMENSION(:,:,:), OPTIONAL ::   pist    ! ice surface temperature      [Kelvin] 
    1241       WRITE(*,*) 'sbc_cpl_snd: You should not have seen this print! error?', p_frld(1,1,1), palbi(1,1,1), psst (1,1), pist (1,1,1) 
     1300      WRITE(*,*) 'sbc_cpl_snd: You should not have seen this print! error?', p_frld(1,1,1) 
    12421301      ! stupid definition to avoid warning message when compiling... 
    12431302      pqns_tot(:,:) = 0. ; pqns_ice(:,:,:) = 0. ; pdqns_ice(:,:,:) = 0. 
Note: See TracChangeset for help on using the changeset viewer.