source: palm/trunk/UTIL/chemistry/gasphase_preproc/kpp/drv/general_tlm.f90 @ 3997

Last change on this file since 3997 was 2696, checked in by kanani, 6 years ago

Merge of branch palm4u into trunk

File size: 4.2 KB
Line 
1!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2!   Driver for the tangent linear model (TLM)
3!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
4
5PROGRAM KPP_ROOT_TLM_Driver
6
7  USE KPP_ROOT_Model
8  USE KPP_ROOT_Initialize, ONLY: Initialize
9
10      KPP_REAL :: T, DVAL(NSPEC)
11      INTEGER :: i, j, ind_1 = 1, ind_2 = 2
12      ! INTEGER :: ind_1 = ind_NO2, ind_2 = ind_O3
13
14!~~~>  NTLM = Number of sensitivity coefficients to compute
15!      Note: this value is set for sensitivities w.r.t. all initial values
16!            the setting may have to be changed for other applications
17      INTEGER, PARAMETER :: NTLM = NVAR
18      KPP_REAL, DIMENSION(NVAR,NTLM) ::  Y_tlm, ATOL_tlm, RTOL_tlm
19
20 
21!~~~>  Control (in) and status (out) vectors for the integrator
22      INTEGER,  DIMENSION(20) :: ICNTRL, ISTATUS
23      KPP_REAL, DIMENSION(20) :: RCNTRL, RSTATUS
24
25      STEPMIN = 0.0d0
26      STEPMAX = 0.0d0
27
28!~~~> Tolerances for calculating concentrations       
29      DO i=1,NVAR
30        RTOL(i) = 1.0d-4
31        ATOL(i) = 1.0d-3
32      END DO
33     
34!~~~> Tolerances for calculating sensitivities
35!     are used for controlling sensitivity truncation error
36!     and for solving the linear sensitivity equations by iterations 
37!     Note: Sensitivities typically span many orders of magnitude
38!           and a careful tuning of ATOL_tlm may be necessary     
39      DO j=1,NTLM
40        DO i=1,NVAR
41          RTOL_tlm(i,j) = 1.0d-4
42          ATOL_tlm(i,j) = 1.0d-3
43        END DO
44      END DO
45     
46      CALL Initialize()
47!~~~> Note: the initial values below are for sensitivities
48!           w.r.t. initial values;
49!           they may have to be changed for other applications
50      Y_tlm(1:NVAR,1:NTLM) = 0.0d0
51      DO j=1,NTLM
52        Y_tlm(j,j) = 1.0d0
53      END DO
54
55!~~~> Default control options
56      ICNTRL(1:20) = 0
57      RCNTRL(1:20) = 0.0d0       
58
59!~~~> Begin time loop
60
61      CALL InitSaveData()
62
63      T = TSTART
64     
65kron: DO WHILE (T < TEND)
66       
67        TIME = T
68        CALL GetMass( C, DVAL )
69        WRITE(6,991) (T-TSTART)/(TEND-TSTART)*100, T,      &
70                    (TRIM(SPC_NAMES(MONITOR(i))),          &
71                      C(MONITOR(i))/CFACTOR, i=1,NMONITOR),&
72                    (TRIM(SMASS(i)),DVAL(i)/CFACTOR, i=1,NMASS)
73
74        CALL SaveData()
75        CALL Update_SUN() 
76        CALL Update_RCONST()
77
78        CALL INTEGRATE_TLM( NTLM, VAR, Y_tlm, T, T+DT,     &
79                            ATOL_tlm, RTOL_tlm,            &
80                            ICNTRL, RCNTRL, ISTATUS, RSTATUS )
81
82        T = T+DT
83
84      END DO kron
85
86      CALL GetMass( C, DVAL )
87      WRITE(6,991) (T-TSTART)/(TEND-TSTART)*100, T,        &
88                  (TRIM(SPC_NAMES(MONITOR(i))),            &
89                    C(MONITOR(i))/CFACTOR, i=1,NMONITOR),  &
90                  (TRIM(SMASS(i)),DVAL(i)/CFACTOR, i=1,NMASS)
91
92      CALL SaveData()
93
94!~~~> End time loop ~~~~~~~~~~
95
96      OPEN(20, FILE='KPP_ROOT_TLM_results.m')
97      WRITE(6,*) '**************************************************'
98      WRITE(6,*) ' Concentrations and Sensitivities at final time '
99      WRITE(6,*) ' were written in the file KPP_ROOT_TLM_results.m'
100      WRITE(6,*) '**************************************************'
101      DO j=1,NTLM
102        WRITE(20,993) ( Y_tlm(i,j), i=1,NVAR )         
103      END DO
104
105      CALL CloseSaveData()
106
107      WRITE(6,995) TRIM(SPC_NAMES(ind_1)),TRIM(SPC_NAMES(ind_1)), &
108                   Y_tlm(ind_1,1)
109      WRITE(6,995) TRIM(SPC_NAMES(ind_2)),TRIM(SPC_NAMES(ind_2)), &
110                   Y_tlm(ind_2,2)
111      WRITE(6,995) TRIM(SPC_NAMES(ind_1)),TRIM(SPC_NAMES(ind_2)), &
112                   Y_tlm(ind_2,1)
113      WRITE(6,995) TRIM(SPC_NAMES(ind_2)),TRIM(SPC_NAMES(ind_1)), &
114                   Y_tlm(ind_1,2)
115                 
116                 
117 991  FORMAT(F6.1,'%. T=',E10.3,3X,20(A,'=',E10.4,';',1X))
118 993  FORMAT(1000(E24.16,2X))
119 995  FORMAT('TLM: d[',A,'](tf)/d[',A,'](t0)=',E14.7)
120 
121 
122      !~~~> The entire matrix of sensitivities
123      WRITE(6,996) ( 'd ',TRIM(SPC_NAMES(i)), i=1,NVAR ) 
124      DO j=1,NTLM
125        WRITE(6,997) TRIM(SPC_NAMES(j)),( Y_tlm(i,j), i=1,NVAR )         
126      END DO
127 996  FORMAT(12X,100('  ',A2,A6,4X))
128 997  FORMAT('d/d',A6,' = ',100(E12.5,2X))
129 
130
131END PROGRAM KPP_ROOT_TLM_Driver
132
Note: See TracBrowser for help on using the repository browser.