update 20251007
This commit is contained in:
@ -14,7 +14,7 @@
|
||||
!=================================================================
|
||||
|
||||
! Parameters
|
||||
INTEGER, PARAMETER :: LLGEOCAPE = 13
|
||||
INTEGER, PARAMETER :: LLGEOCAPE = 13 ! 卫星观测的垂直层数
|
||||
INTEGER, PARAMETER :: MAXGEOCAPE = 639059
|
||||
|
||||
|
||||
@ -25,7 +25,7 @@
|
||||
REAL*8 :: TOTERROR_INV( LLGEOCAPE, LLGEOCAPE )
|
||||
REAL*8 :: PRESSURE( LLGEOCAPE )
|
||||
REAL*8 :: PRESSURE_EDGE( LLGEOCAPE )
|
||||
REAL*8 :: RANDNUM( MAXGEOCAPE )
|
||||
REAL*8 :: RANDNUM( MAXGEOCAPE ) ! 保存了随机数的数组
|
||||
|
||||
|
||||
CONTAINS
|
||||
@ -37,7 +37,7 @@
|
||||
! Subroutine READ_GEOCAPE_INFO reads and stores information about the new
|
||||
! instrument, specifically AK, pressure levels and error covariance matrices.
|
||||
! (kjw, 07/24/11)
|
||||
!
|
||||
! 用于读取卫星观测的数据,保存 AK、气压以及误差协方差矩阵(没有观测值么),应该有观测值
|
||||
! Arguments as Input:
|
||||
! ============================================================================
|
||||
! (1 ) FILENAME (CHAR) : GEOCAPE filename to read
|
||||
@ -85,7 +85,7 @@
|
||||
|
||||
! Read and store one variable at a time
|
||||
|
||||
! ------ Averaging Kernel Matrix ------
|
||||
! ------ Averaging Kernel Matrix ------ 读取平均核函数,并保存在模块变量中
|
||||
! Filename to read
|
||||
READ_FILENAME = TRIM( '/home/kjw/new_satellites/geocape/' ) //
|
||||
& 'data/' // TRIM( 'geocape_AK.txt' )
|
||||
@ -116,7 +116,7 @@
|
||||
CLOSE( IU_IN )
|
||||
|
||||
|
||||
! ------ Observation Error Covariance Matrix ------
|
||||
! ------ Observation Error Covariance Matrix ------ 读取误差协方差矩阵
|
||||
! Filename to read
|
||||
READ_FILENAME = TRIM( '/home/kjw/new_satellites/geocape/' ) //
|
||||
& 'data/' // TRIM( 'geocape_obs_error.txt' )
|
||||
@ -129,7 +129,7 @@
|
||||
& STATUS='OLD', IOSTAT=IOS )
|
||||
IF ( IOS /= 0 ) CALL IOERROR( IOS, IU_IN, 'read_obs_error:1' )
|
||||
|
||||
! Read File and save info into module variable OBSERROR(:,:)
|
||||
! Read File and save info into module variable OBSERROR(:,:) 读取观测误差
|
||||
DO LN=1,LLGEOCAPE
|
||||
READ( IU_IN, '(13F18.12)', IOSTAT=IOS ) OBSERROR(LN,:)
|
||||
|
||||
@ -147,7 +147,7 @@
|
||||
CLOSE( IU_IN )
|
||||
|
||||
|
||||
! ------ Inverse of Observation Error Covariance Matrix ------
|
||||
! ------ Inverse of Observation Error Covariance Matrix ------ 对观测误差协方差矩阵求逆
|
||||
! Filename to read
|
||||
READ_FILENAME = TRIM( '/home/kjw/new_satellites/geocape/' ) //
|
||||
& 'data/' // TRIM( 'geocape_obs_error_inv.txt' )
|
||||
@ -209,7 +209,7 @@
|
||||
! CLOSE( IU_IN )
|
||||
|
||||
|
||||
! ------ Pressure Levels ------
|
||||
! ------ Pressure Levels ------ 读取气压数据
|
||||
! Filename to read
|
||||
READ_FILENAME = TRIM( '/home/kjw/new_satellites/geocape/' ) //
|
||||
& 'data/' // TRIM( 'geocape_pressure.txt' )
|
||||
@ -238,7 +238,7 @@
|
||||
CLOSE( IU_IN )
|
||||
|
||||
|
||||
! ------ Pressure Edges ------
|
||||
! ------ Pressure Edges ------ 获取气压的边界值
|
||||
! By finite difference on log(pressure) grid
|
||||
PRESSURE_EDGE(1) = PRESSURE(1)
|
||||
PRESSURE_EDGE(LLGEOCAPE) = 0.
|
||||
@ -248,7 +248,7 @@
|
||||
ENDDO
|
||||
|
||||
|
||||
! Return to calling program
|
||||
! Return to calling program 还真没有直接读取观测值
|
||||
END SUBROUTINE READ_GEOCAPE_INFO
|
||||
!------------------------------------------------------------------------------
|
||||
|
||||
@ -258,7 +258,7 @@
|
||||
!******************************************************************************
|
||||
! Subroutine CALC_GEOCAPE_CH4_FORCE calculates the adjoint forcing from the GEOCAPE
|
||||
! CH4 observations and updates the cost function. (kjw, 07/20/11)
|
||||
!
|
||||
! 该程序计算伴随强迫,并且更新代价函数
|
||||
!
|
||||
! Arguments as Input/Output:
|
||||
! ============================================================================
|
||||
@ -362,10 +362,10 @@
|
||||
NEW_COST(:) = 0d0
|
||||
|
||||
|
||||
! Open files for output
|
||||
! Open files for output 在第一次运行时会打开相关文件用于输出(?)
|
||||
IF ( FIRST ) THEN
|
||||
FILENAME = 'pres.NN.m'
|
||||
CALL EXPAND_NAME( FILENAME, N_CALC )
|
||||
CALL EXPAND_NAME( FILENAME, N_CALC ) ! 替换文件名中的 NN 为迭代次数
|
||||
FILENAME = TRIM( DIAGADJ_DIR ) // TRIM( FILENAME )
|
||||
OPEN( 101, FILE=TRIM( FILENAME ), STATUS='UNKNOWN',
|
||||
& IOSTAT=IOS, FORM='FORMATTED', ACCESS='SEQUENTIAL' )
|
||||
@ -471,11 +471,11 @@
|
||||
!FILENAME_OBS = TRIM( ADJTMP_DIR ) // TRIM( FILENAME_OBS )
|
||||
XTAU = GET_TAU()
|
||||
CALL READ_BPCH2( TRIM(FILENAME_OBS), 'IJ-OBS-$', 1,
|
||||
& XTAU, IIPAR, JJPAR,
|
||||
& LLPAR, DUMMY_TRUE , QUIET=.TRUE.)
|
||||
& XTAU, IIPAR, JJPAR, ! II, JJ, LL 都是维度大小而非坐标
|
||||
& LLPAR, DUMMY_TRUE , QUIET=.TRUE.) ! DUMMY_TRUE 为读取的观测数据?
|
||||
GC_CH4_TRUE_ARRAY(:,:,:) = DUMMY_TRUE(:,:,:)
|
||||
|
||||
! Convert from [kg] --> [v/v]
|
||||
! Convert from [kg] --> [v/v] 单位转换
|
||||
DO II=1,IIPAR
|
||||
DO JJ=1,JJPAR
|
||||
DO LG=1,LLPAR
|
||||
@ -543,7 +543,7 @@
|
||||
print*, ' - CALC_GEOCAPE_CH4_FORCE ', GET_NYMD(), GET_NHMS()
|
||||
|
||||
|
||||
! Loop over each grid box north of the minimum latitude
|
||||
! Loop over each grid box north of the minimum latitude 对于每个网格进行循环
|
||||
! 1. Determine number of observations in the current grid box
|
||||
! 2. Make obseravations
|
||||
DO II = 1, IIPAR
|
||||
@ -582,7 +582,7 @@
|
||||
! Get GEOS-Chem pressure and CH4 column corresponding to this grid box.
|
||||
! CH4 in [kg/box] and pressure in [hPa]
|
||||
! Get column of pressure centers and CH4 values
|
||||
DO LG=1,LLPAR
|
||||
DO LG=1,LLPAR ! 对垂直上进行循环,计算柱浓度
|
||||
|
||||
! Pressure centers [hPa]
|
||||
GC_PCENTER(LG) = GET_PCENTER(II,JJ,LG)
|
||||
@ -605,7 +605,7 @@
|
||||
! GEOS-Chem surface pressure < GEOCAPE pressure levels
|
||||
nlev = count( PRESSURE_EDGE .LT. GC_PEDGE(1) )
|
||||
IF ( nlev .LT. 13 ) nlev = nlev + 1
|
||||
lind = LLGEOCAPE + 1 - nlev ! minimum vertical index on GEOCAPE grid
|
||||
lind = LLGEOCAPE + 1 - nlev ! minimum vertical index on GEOCAPE grid 最小气压层的索引
|
||||
|
||||
|
||||
! Get interpolation matrix that maps GEOS-Chem to GEOCAPE grid
|
||||
@ -908,13 +908,13 @@
|
||||
!******************************************************************************
|
||||
! Subroutine CALC_GEOCAPE_CH4_FORCE calculates the adjoint forcing from the GEOCAPE
|
||||
! CH4 observations and updates the cost function. (kjw, 07/20/11)
|
||||
!
|
||||
! 似乎是伴随强迫使用的程序,输出不仅有代价函数,还有伴随强迫(不过需要输入扰动)
|
||||
!
|
||||
! Arguments as Input/Output:
|
||||
! ============================================================================
|
||||
! (1 ) COST_FUNC_A (REAL*8) : Cost funciton (INOUT) [unitless]
|
||||
! (2 ) PERT (Real*8) : Array of perturbations to CH4 column (+/- 0.1, for ex.)
|
||||
! (5 ) ADJ (REAL*8) : Array of adjoint forcings (OUT)
|
||||
! (2 ) PERT (Real*8) : Array of perturbations to CH4 column (+/- 0.1, for ex.) 扰动的柱浓度
|
||||
! (5 ) ADJ (REAL*8) : Array of adjoint forcings (OUT) 强迫伴随
|
||||
!
|
||||
! NOTES:
|
||||
! (1 )
|
||||
|
Reference in New Issue
Block a user