/[MITgcm]/MITgcm/pkg/dic/dic_atmos.F
ViewVC logotype

Diff of /MITgcm/pkg/dic/dic_atmos.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph | View Patch Patch

revision 1.4 by stephd, Tue Nov 6 15:57:45 2007 UTC revision 1.5 by jmc, Thu Nov 8 22:35:23 2007 UTC
# Line 1  Line 1 
1    C $Header$
2    C $Name$
3    
4  #include "DIC_OPTIONS.h"  #include "DIC_OPTIONS.h"
5  #include "PTRACERS_OPTIONS.h"  #include "PTRACERS_OPTIONS.h"
6  #include "GCHEM_OPTIONS.h"  #include "GCHEM_OPTIONS.h"
# Line 6  CBOP Line 9  CBOP
9  C !ROUTINE: DIC_ATMOS  C !ROUTINE: DIC_ATMOS
10    
11  C !INTERFACE: ==========================================================  C !INTERFACE: ==========================================================
12        SUBROUTINE DIC_ATMOS(myIter,myTime,myThid,istate)        SUBROUTINE DIC_ATMOS( istate, myTime, myIter, myThid )
13    
14  C !DESCRIPTION:  C !DESCRIPTION:
15  C  Calculate the atmospheric pCO2  C  Calculate the atmospheric pCO2
16  C  gchem_int1:  C  gchem_int1:
17  C  0=use default 278.d-6  C  0=use default 278.d-6
18  C  1=use constant value - gchem_rl1, read in from data.gchem  C  1=use constant value - gchem_rl1, read in from data.gchem
19  C  2=read in from file  C  2=read in from file
20  C  3=interact with atmospheric box  C  3=interact with atmospheric box
21  C !USES: ===============================================================  C !USES: ===============================================================
22        IMPLICIT NONE        IMPLICIT NONE
# Line 70  c if coupled to atmsopheric model, use t Line 73  c if coupled to atmsopheric model, use t
73  c Co2 value passed from the coupler  c Co2 value passed from the coupler
74  #ifndef USE_ATMOSCO2  #ifndef USE_ATMOSCO2
75    
76          IF ( nThreads .GT. 1 ) THEN
77    C     Problem with I/O and global-sum for multi-threaded execution
78    C     Needs to be fixed before using this S/R in multi-threaded run
79            STOP 'S/R DIC_ATMOS: multi-threaded not right'
80          ENDIF
81    
82  c default - set only once  c default - set only once
83        if (gchem_int1.eq.0.and.istate.eq.0) then        if (gchem_int1.eq.0.and.istate.eq.0) then
84         DO bj=myByLo(myThid),myByHi(myThid)         DO bj=myByLo(myThid),myByHi(myThid)
# Line 105  c                   gchem_int2=number en Line 114  c                   gchem_int2=number en
114  c                   gchem_int3=start timestep,  c                   gchem_int3=start timestep,
115  c                   gchem_int4=timestep between file entries)  c                   gchem_int4=timestep between file entries)
116         if (gchem_int1.eq.2) then         if (gchem_int1.eq.2) then
117          if (istate.eq.0) then                  if (istate.eq.0) then
118            OPEN(28,FILE='co2atmos.dat',STATUS='old')            OPEN(28,FILE='co2atmos.dat',STATUS='old')
119            do it=1,gchem_int2            do it=1,gchem_int2
120              READ(28,*) co2atmos(it)              READ(28,*) co2atmos(it)
# Line 114  c                   gchem_int4=timestep Line 123  c                   gchem_int4=timestep
123           endif           endif
124  c linearly interpolate between file entries  c linearly interpolate between file entries
125            ntim=int((myIter-gchem_int3)/gchem_int4)+1            ntim=int((myIter-gchem_int3)/gchem_int4)+1
126            aWght=0.5+float(myIter-gchem_int3)/float(gchem_int4)-            aWght = FLOAT(myIter-gchem_int3)
127       &                      float(ntim-1)            bWght = FLOAT(gchem_int4)
128            if (aWght.gt.1.d0) then            aWght = 0.5 _d 0 + aWght/bWght - FLOAT(ntim-1)
129              if (aWght.gt.1. _d 0) then
130              ntim=ntim+1              ntim=ntim+1
131              aWght=aWght-1.d0              aWght=aWght-1. _d 0
132            endif            endif
133            bWght=1.d0-aWght            bWght = 1. _d 0 - aWght
134            tmp=co2atmos(ntim)*bWght+co2atmos(ntim+1)*aWght            tmp=co2atmos(ntim)*bWght+co2atmos(ntim+1)*aWght
135  c         print*,'weights',ntim, aWght, bWght, tmp  c         print*,'weights',ntim, aWght, bWght, tmp
136    
# Line 135  c         print*,'weights',ntim, aWght, Line 145  c         print*,'weights',ntim, aWght,
145              ENDDO              ENDDO
146    
147             print*,'AtmospCO2(20,20)',AtmospCO2(20,20,bi,bj)             print*,'AtmospCO2(20,20)',AtmospCO2(20,20,bi,bj)
148    
149             ENDDO             ENDDO
150            ENDDO            ENDDO
151    
# Line 172  c for 278ppmv we need total_atmos_carbon Line 182  c for 278ppmv we need total_atmos_carbon
182              if (istate.gt.0) then              if (istate.gt.0) then
183                total_flux=total_flux+FluxCO2(i,j,bi,bj)*rA(i,j,bi,bj)*                total_flux=total_flux+FluxCO2(i,j,bi,bj)*rA(i,j,bi,bj)*
184       &                        hFacC(i,j,1,bi,bj)*dTtracerLev(1)       &                        hFacC(i,j,1,bi,bj)*dTtracerLev(1)
185              endif              endif
186              DO k=1,nR              DO k=1,nR
187                total_ocean_carbon= total_ocean_carbon+                total_ocean_carbon= total_ocean_carbon+
188       &              ( Ptracer(i,j,k,bi,bj,1)+       &              ( Ptracer(i,j,k,bi,bj,1)+
# Line 226  c write values to new pickup Line 236  c write values to new pickup
236    
237        atpco2=total_atmos_carbon/total_atmos_moles        atpco2=total_atmos_carbon/total_atmos_moles
238    
239  c     print*,'QQpCO2', total_atmos_carbon, atpco2, total_ocean_carbon,  c     print*,'QQpCO2', total_atmos_carbon, atpco2, total_ocean_carbon,
240  c    &                 total_flux  c    &                 total_flux
241    
242         DO bj=myByLo(myThid),myByHi(myThid)         DO bj=myByLo(myThid),myByHi(myThid)
# Line 245  c    &                 total_flux Line 255  c    &                 total_flux
255        total_carbon=total_atmos_carbon + total_ocean_carbon        total_carbon=total_atmos_carbon + total_ocean_carbon
256        total_carbon_old=total_atmos_carbon_old + total_ocean_carbon_old        total_carbon_old=total_atmos_carbon_old + total_ocean_carbon_old
257        carbon_diff=total_carbon-total_carbon_old        carbon_diff=total_carbon-total_carbon_old
258        print*,'QQ total C, current, old, diff', total_carbon,        print*,'QQ total C, current, old, diff', total_carbon,
259       &                         total_carbon_old, carbon_diff       &                         total_carbon_old, carbon_diff
260        carbon_diff=total_ocean_carbon-total_ocean_carbon_old        carbon_diff=total_ocean_carbon-total_ocean_carbon_old
261        tmp=carbon_diff-total_flux        tmp=carbon_diff-total_flux

Legend:
Removed from v.1.4  
changed lines
  Added in v.1.5

  ViewVC Help
Powered by ViewVC 1.1.22