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 5841 for branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/MEDUSA/trcco2_medusa.F90 – NEMO

Ignore:
Timestamp:
2015-10-30T12:48:06+01:00 (8 years ago)
Author:
jpalmier
Message:

JPALM --30-10-2015-- Add MOCSY and DMS to MEDUSA-NEMO3.6

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/MEDUSA/trcco2_medusa.F90

    r5726 r5841  
    4747!======================================================================= 
    4848! 
    49       SUBROUTINE trc_co2_medusa( Temp, Sal, DIC, ALK, Depth, Wnd, pCO2a, & 
     49      SUBROUTINE trc_co2_medusa( Temp, Sal, DIC, ALK, Depth, xkw, pCO2a, & 
    5050      pH, pCO2w, h2co3, hco3, co3, om_cal, om_arg, co2flux, TDIC, TALK,  & 
    5151      dcf, henry, iters ) 
     
    7272! 17/02/2010. Update calculation of K1, K2, Kb to make consistant with the OCMIP protocols. 
    7373! 29/07/2011. Merged into MEDUSA with a raft of changes to this subroutine; less elsewhere 
     74! 23/06/2015. Modified to take gas transfer velocity as an input (rather than wind speed);  
     75!             alter CO2 flux to /s rather than /d for consistency with other schemes 
    7476! 
    7577! Changes for MEDUSA include:  
     
    8587      REAL(wp), INTENT( in )    :: ALK        ! meq  / m3 
    8688      REAL(wp), INTENT( in )    :: Depth      ! m 
    87       REAL(wp), INTENT( in )    :: Wnd        ! m / s 
     89!     REAL(wp), INTENT( in )    :: Wnd        ! m / s 
     90      REAL(wp), INTENT( in )    :: xkw        ! m / s 
    8891      REAL(wp), INTENT( in )    :: pCO2a      ! uatm 
    8992!---------------------------------------------------------------------- 
     
    9598      REAL(wp), INTENT( inout ) :: om_cal     ! normalised 
    9699      REAL(wp), INTENT( inout ) :: om_arg     ! normalised 
    97       REAL(wp), INTENT( inout ) :: co2flux    ! mmol / m2 / d 
     100      REAL(wp), INTENT( inout ) :: co2flux    ! mmol / m2 / s 
    98101      REAL(wp), INTENT( inout ) :: TDIC       ! umol / kg 
    99102      REAL(wp), INTENT( inout ) :: TALK       ! ueq  / kg 
     
    129132   !                 (i.e. surface calculations being performed) 
    130133   if (Depth .eq. 0.0) then 
    131       call Air_sea_exchange( Temp, Wnd, pCO2w, pCO2a, henry, dcf, &         ! inputs 
     134      call Air_sea_exchange( Temp, xkw, pCO2w, pCO2a, henry, dcf, &         ! inputs 
    132135         co2flux )                                                          ! output 
    133136   else 
     
    145148      IF(lwp) WRITE(numout,*) ' trc_co2_medusa: zdic    =', DIC 
    146149      IF(lwp) WRITE(numout,*) ' trc_co2_medusa: zalk    =', ALK 
    147       IF(lwp) WRITE(numout,*) ' trc_co2_medusa: f_wind  =', Wnd 
     150      IF(lwp) WRITE(numout,*) ' trc_co2_medusa: f_kw660 =', xkw 
    148151      IF(lwp) WRITE(numout,*) ' trc_co2_medusa: f_ph    =', ph 
    149152      IF(lwp) WRITE(numout,*) ' trc_co2_medusa: f_pco2w =', pCO2w 
     
    162165      &        ' DIC', DIC, ' ALK', ALK 
    163166      if (lwp) write (numout,'(a,a,f10.3,a,f10.3)') 'CO2FLUX-NAN', & 
    164       &        ' WND', Wnd, ' PH ', ph 
     167      &        ' XKW', xkw, ' PH ', ph 
    165168      if (lwp) write (numout,'(a,a,i6)') 'CO2FLUX-NAN', & 
    166169      &        ' ITERS', iters 
     
    196199!  WRITE(*,'(A27,F10.3)') "    Omega calcite       (~) = ", om_cal 
    197200!  WRITE(*,'(A27,F10.3)') "    Omega aragonite     (~) = ", om_arg 
    198 !  WRITE(*,'(A27,F10.3)') "    air sea flux(mmol/m2/d) = ", flux 
     201!  WRITE(*,'(A27,F10.3)') "    air sea flux(mmol/m2/s) = ", flux 
    199202!  WRITE(*,*) " " 
    200203 
     
    287290!======================================================================= 
    288291! 
    289       SUBROUTINE Air_sea_exchange( T, Wnd, pco2w, pco2a, henry, dcf, & 
     292      SUBROUTINE Air_sea_exchange( T, xkw, pco2w, pco2a, henry, dcf, & 
    290293      flux ) 
    291294!       
     
    302305!  pCO2a    partial pressure of CO2 in the atmosphere (usually external forcing). 
    303306!  T        temperature (C) 
    304 !  Wnd      wind speed, metres 
     307!  Wnd      wind speed, metres (DELETED) 
     308!  xkw      gas transfer velocity 
    305309!  Henry    henry's constant 
    306310!  density  the density of water for conversion between mmol/m3 and umol/kg 
     
    312316   IMPLICIT NONE 
    313317 
    314       REAL(wp), INTENT( in )    :: T, wnd, pco2w, pco2a, henry, dcf ! INPUT PARAMETERS: 
     318      REAL(wp), INTENT( in )    :: T, xkw, pco2w, pco2a, henry, dcf ! INPUT PARAMETERS: 
    315319!----------------------------------------------------------------------- 
    316320      REAL(wp), INTENT( inout ) :: flux                             ! OUTPUT Variables 
     
    320324! calculate the Schmidt number and unit conversions 
    321325          sc    = 2073.1-125.62*T+3.6276*T**2.0-0.0432190*T**3.0 
    322           fwind = (0.222d0 * wnd**2d0 + 0.333d0 * wnd)*(sc/660.d0)**(-0.5) 
     326!         fwind = (0.222d0 * wnd**2d0 + 0.333d0 * wnd)*(sc/660.d0)**(-0.5) 
     327          fwind = xkw * (sc/660.d0)**(-0.5) 
    323328          fwind = fwind*24.d0/100.d0   ! convert to m/day 
    324329 
     
    326331! here it is rescaled to mmol/m2/d 
    327332          flux = fwind * henry * ( pco2a - pco2w ) * dcf 
     333 
     334! AXY (23/06/15): let's get it from /d to /s 
     335          flux = flux / ( 86400. ) 
    328336 
    329337  RETURN  
Note: See TracChangeset for help on using the changeset viewer.