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 6945 for trunk/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zche.F90 – NEMO

Ignore:
Timestamp:
2016-09-23T12:31:28+02:00 (8 years ago)
Author:
cetlod
Message:

trunk: bugfixes on PISCES carbon chemistry, see ticket #1774

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zche.F90

    r6291 r6945  
    3131   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sio3eq   ! chemistry of Si 
    3232   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   fekeq    ! chemistry of Fe 
    33    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,: ::   chemc    ! Solubilities of O2 and CO2 
     33   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   chemc    ! Solubilities of O2 and CO2 
    3434   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   chemo2   ! Solubilities of O2 and CO2 
     35   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tempis   ! In situ temperature 
    3536 
    3637   REAL(wp), PUBLIC ::   atcox  = 0.20946         ! units atm 
     
    3940   REAL(wp) ::   o2atm  = 1. / ( 1000. * 0.20946 )   
    4041 
    41    REAL(wp) ::   akcc1  = -171.9065       ! coeff. for apparent solubility equilibrium 
    42    REAL(wp) ::   akcc2  =   -0.077993     ! Millero et al. 1995 from Mucci 1983 
    43    REAL(wp) ::   akcc3  = 2839.319         
    44    REAL(wp) ::   akcc4  =   71.595         
    45    REAL(wp) ::   akcc5  =   -0.77712       
    46    REAL(wp) ::   akcc6  =    0.00284263    
    47    REAL(wp) ::   akcc7  =  178.34         
    48    REAL(wp) ::   akcc8  =   -0.07711      
    49    REAL(wp) ::   akcc9  =    0.0041249    
    50  
    51    REAL(wp) ::   rgas   = 83.143         ! universal gas constants 
     42   REAL(wp) ::   rgas   = 83.14472       ! universal gas constants 
    5243   REAL(wp) ::   oxyco  = 1. / 22.4144   ! converts from liters of an ideal gas to moles 
    5344 
    5445   REAL(wp) ::   bor1   = 0.00023        ! borat constants 
    5546   REAL(wp) ::   bor2   = 1. / 10.82 
    56  
    57    REAL(wp) ::   ca0    = -162.8301      ! WEISS & PRICE 1980, units mol/(kg atm) 
    58    REAL(wp) ::   ca1    =  218.2968 
    59    REAL(wp) ::   ca2    =   90.9241 
    60    REAL(wp) ::   ca3    =   -1.47696 
    61    REAL(wp) ::   ca4    =    0.025695 
    62    REAL(wp) ::   ca5    =   -0.025225 
    63    REAL(wp) ::   ca6    =    0.0049867 
    64  
    65    REAL(wp) ::   c10    = -3670.7        ! Coeff. for 1. dissoc. of carbonic acid (Edmond and Gieskes, 1970)    
    66    REAL(wp) ::   c11    =    62.008      
    67    REAL(wp) ::   c12    =    -9.7944     
    68    REAL(wp) ::   c13    =     0.0118      
    69    REAL(wp) ::   c14    =    -0.000116 
    70  
    71    REAL(wp) ::   c20    = -1394.7       ! coeff. for 2. dissoc. of carbonic acid (Millero, 1995)    
    72    REAL(wp) ::   c21    =    -4.777    
    73    REAL(wp) ::   c22    =     0.0184    
    74    REAL(wp) ::   c23    =    -0.000118 
    7547 
    7648   REAL(wp) ::   st1    =      0.14     ! constants for calculate concentrations for sulfate 
     
    144116      REAL(wp) ::   ztgg , ztgg2, ztgg3 , ztgg4 , ztgg5 
    145117      REAL(wp) ::   zpres, ztc  , zcl   , zcpexp, zoxy  , zcpexp2 
    146       REAL(wp) ::   zsqrt, ztr  , zlogt , zcek1 
    147       REAL(wp) ::   zis  , zis2 , zsal15, zisqrt 
     118      REAL(wp) ::   zsqrt, ztr  , zlogt , zcek1, zc1, zplat 
     119      REAL(wp) ::   zis  , zis2 , zsal15, zisqrt, za1  , za2 
    148120      REAL(wp) ::   zckb , zck1 , zck2  , zckw  , zak1 , zak2  , zakb , zaksp0, zakw 
    149121      REAL(wp) ::   zst  , zft  , zcks  , zckf  , zaksp1 
     
    151123      ! 
    152124      IF( nn_timing == 1 )  CALL timing_start('p4z_che') 
     125      ! 
     126      ! Computations of chemical constants require in situ temperature 
     127      ! Here a quite simple formulation is used to convert  
     128      ! potential temperature to in situ temperature. The errors is less than  
     129      ! 0.04°C relative to an exact computation 
     130      ! --------------------------------------------------------------------- 
     131      DO jk = 1, jpk 
     132         DO jj = 1, jpj 
     133            DO ji = 1, jpi 
     134               zpres = gdept_n(ji,jj,jk) / 1000. 
     135               za1 = 0.04 * ( 1.0 + 0.185 * tsn(ji,jj,jk,jp_tem) + 0.035 * (tsn(ji,jj,jk,jp_sal) - 35.0) ) 
     136               za2 = 0.0075 * ( 1.0 - tsn(ji,jj,jk,jp_tem) / 30.0 ) 
     137               tempis(ji,jj,jk) = tsn(ji,jj,jk,jp_tem) - za1 * zpres + za2 * zpres**2 
     138            END DO 
     139         END DO 
     140      END DO 
    153141      ! 
    154142      ! CHEMICAL CONSTANTS - SURFACE LAYER 
     
    157145         DO ji = 1, jpi 
    158146            !                             ! SET ABSOLUTE TEMPERATURE 
    159             ztkel = tsn(ji,jj,1,jp_tem) + 273.15 
     147            ztkel = tempis(ji,jj,1) + 273.15 
    160148            zt    = ztkel * 0.01 
    161149            zt2   = zt * zt 
     
    165153            !                             ! LN(K0) OF SOLUBILITY OF CO2 (EQ. 12, WEISS, 1980) 
    166154            !                             !     AND FOR THE ATMOSPHERE FOR NON IDEAL GAS 
    167             zcek1 = ca0 + ca1 / zt + ca2 * zlogt + ca3 * zt2 + zsal * ( ca4 + ca5 * zt + ca6 * zt2 ) 
     155            zcek1 = 9345.17/ztkel - 60.2409 + 23.3585 * LOG(zt) + zsal*(0.023517 - 0.00023656*ztkel    & 
     156            &       + 0.0047036e-4*ztkel**2) 
    168157            !                             ! SET SOLUBILITIES OF O2 AND CO2  
    169             chemc(ji,jj) = EXP( zcek1 ) * 1.e-6 * rhop(ji,jj,1) / 1000.  ! mol/(L uatm) 
     158            chemc(ji,jj,1) = EXP( zcek1 ) * 1.e-6 * rhop(ji,jj,1) / 1000. ! mol/(kg uatm) 
     159            chemc(ji,jj,2) = -1636.75 + 12.0408*ztkel - 0.0327957*ztkel**2 + 0.0000316528*ztkel**3 
     160            chemc(ji,jj,3) = 57.7 - 0.118*ztkel 
    170161            ! 
    171162         END DO 
     
    177168         DO jj = 1, jpj 
    178169            DO ji = 1, jpi 
    179               ztkel = tsn(ji,jj,jk,jp_tem) + 273.15 
     170              ztkel = tempis(ji,jj,jk) + 273.15 
    180171              zsal  = tsn(ji,jj,jk,jp_sal) + ( 1.- tmask(ji,jj,jk) ) * 35. 
    181172              zsal2 = zsal * zsal 
    182               ztgg  = LOG( ( 298.15 - tsn(ji,jj,jk,jp_tem) ) / ztkel )  ! Set the GORDON & GARCIA scaled temperature 
     173              ztgg  = LOG( ( 298.15 - tempis(ji,jj,jk) ) / ztkel )  ! Set the GORDON & GARCIA scaled temperature 
    183174              ztgg2 = ztgg  * ztgg 
    184175              ztgg3 = ztgg2 * ztgg 
     
    200191            DO ji = 1, jpi 
    201192 
    202                ! SET PRESSION 
    203                zpres   = 1.025e-1 * gdept_n(ji,jj,jk) 
     193               ! SET PRESSION ACCORDING TO SAUNDER (1980) 
     194               zplat   = SIN ( ABS(gphit(ji,jj)*3.141592654/180.) ) 
     195               zc1 = 5.92E-3 + zplat**2 * 5.25E-3 
     196               zpres = ((1-zc1)-SQRT(((1-zc1)**2)-(8.84E-6*gdept_n(ji,jj,jk)))) / 4.42E-6 
     197               zpres = zpres / 10.0 
    204198 
    205199               ! SET ABSOLUTE TEMPERATURE 
    206                ztkel   = tsn(ji,jj,jk,jp_tem) + 273.15 
     200               ztkel   = tempis(ji,jj,jk) + 273.15 
    207201               zsal    = tsn(ji,jj,jk,jp_sal) + ( 1.-tmask(ji,jj,jk) ) * 35. 
    208202               zsqrt  = SQRT( zsal ) 
     
    213207               zis2   = zis * zis 
    214208               zisqrt = SQRT( zis ) 
    215                ztc     = tsn(ji,jj,jk,jp_tem) + ( 1.- tmask(ji,jj,jk) ) * 20. 
     209               ztc     = tempis(ji,jj,jk) + ( 1.- tmask(ji,jj,jk) ) * 20. 
    216210 
    217211               ! CHLORINITY (WOOSTER ET AL., 1969) 
     
    246240 
    247241 
    248                zck1    = c10 * ztr + c11 + c12 * zlogt + c13 * zsal + c14 * zsal * zsal 
    249                zck2    = c20 * ztr + c21 + c22 * zsal   + c23 * zsal**2 
     242               ! DISSOCIATION COEFFICIENT FOR CARBONATE ACCORDING TO  
     243               ! MEHRBACH (1973) REFIT BY MILLERO (1995), seawater scale 
     244               zck1    = -1.0*(3633.86*ztr - 61.2172 + 9.6777*zlogt  & 
     245                  - 0.011555*zsal + 0.0001152*zsal*zsal) 
     246               zck2    = -1.0*(471.78*ztr + 25.9290 - 3.16967*zlogt      & 
     247                  - 0.01781*zsal + 0.0001122*zsal*zsal) 
    250248 
    251249               ! PKW (H2O) (DICKSON AND RILEY, 1979) 
     
    256254               ! APPARENT SOLUBILITY PRODUCT K'SP OF CALCITE IN SEAWATER 
    257255               !       (S=27-43, T=2-25 DEG C) at pres =0 (atmos. pressure) (MUCCI 1983) 
    258                zaksp0  = akcc1 + akcc2 * ztkel + akcc3 * ztr + akcc4 * LOG10( ztkel )   & 
    259                   &   + ( akcc5 + akcc6 * ztkel + akcc7 * ztr ) * zsqrt + akcc8 * zsal + akcc9 * zsal15 
     256               zaksp0  = -171.9065 -0.077993*ztkel + 2839.319*ztr + 71.595*LOG10( ztkel )   & 
     257                  &      + (-0.77712 + 0.00284263*ztkel + 178.34*ztr) * zsqrt  & 
     258                  &      - 0.07711*zsal + 0.0041249*zsal15 
    260259 
    261260               ! K1, K2 OF CARBONIC ACID, KB OF BORIC ACID, KW (H2O) (LIT.?) 
     
    327326      !!                     ***  ROUTINE p4z_che_alloc  *** 
    328327      !!---------------------------------------------------------------------- 
    329       ALLOCATE( sio3eq(jpi,jpj,jpk), fekeq(jpi,jpj,jpk), chemc(jpi,jpj), chemo2(jpi,jpj,jpk),   & 
    330       &         STAT=p4z_che_alloc ) 
     328      ALLOCATE( sio3eq(jpi,jpj,jpk), fekeq(jpi,jpj,jpk), chemc(jpi,jpj,3), chemo2(jpi,jpj,jpk),   & 
     329      &         tempis(jpi,jpj,jpk), STAT=p4z_che_alloc ) 
    331330      ! 
    332331      IF( p4z_che_alloc /= 0 )   CALL ctl_warn('p4z_che_alloc : failed to allocate arrays.') 
Note: See TracChangeset for help on using the changeset viewer.