Add files via upload

This commit is contained in:
Xuesong (Steve)
2018-08-28 00:33:48 -04:00
committed by GitHub
parent cc7a9f1d91
commit f842cc9639
63 changed files with 110207 additions and 0 deletions

View File

@ -0,0 +1,99 @@
! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
!
! Initialization File
!
! Generated by KPP-2.2 symbolic chemistry Kinetics PreProcessor
! (http://www.cs.vt.edu/~asandu/Software/KPP)
! KPP is distributed under GPL, the general public licence
! (http://www.gnu.org/copyleft/gpl.html)
! (C) 1995-1997, V. Damian & A. Sandu, CGRER, Univ. Iowa
! (C) 1997-2005, A. Sandu, Michigan Tech, Virginia Tech
! With important contributions from:
! M. Damian, Villanova University, USA
! R. Sander, Max-Planck Institute for Chemistry, Mainz, Germany
!
! File : gckpp_adj_Initialize.f90
! Time : Tue May 14 19:43:54 2013
! Working directory : /home/daven/kpp-2.2.1/GC_KPP
! Equation file : gckpp_adj.kpp
! Output root filename : gckpp_adj
!
! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
MODULE gckpp_adj_Initialize
USE gckpp_adj_Parameters, ONLY: dp, NVAR, NFIX
IMPLICIT NONE
CONTAINS
! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
!
! Initialize - function to initialize concentrations
! Arguments :
!
! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
SUBROUTINE Initialize ( )
USE gckpp_adj_Global
USE gckpp_adj_Util, ONLY : Shuffle_user2kpp
USE gckpp_adj_Monitor
INTEGER :: i
! INLINED initializations
CALL Shuffle_user2kpp(V_CSPEC,VAR)
DO i = 1, NFIX
FIX(i) = 1.d0
END DO
! End INLINED initializations
! need to add this to the INLINED for OpenMP (dkh, 07/31/09)
DO I = 1, NVAR
C(I) = VAR(I)
ENDDO
DO I = 1, NFIX
C(NVAR+I) = FIX(I)
ENDDO
END SUBROUTINE Initialize
! End of Initialize function
! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
! Initialize_adj - function to initialize concentrations
! Arguments :
!
! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
SUBROUTINE Initialize_adj ( )
USE gckpp_adj_Global
USE gckpp_adj_Util, ONLY : Shuffle_user2kpp
USE gckpp_adj_Monitor
INTEGER :: i
! INLINED initializations
CALL Shuffle_user2kpp(V_CSPEC_ADJ,VAR_ADJ)
! End INLINED initializations
END SUBROUTINE Initialize_adj
! End of Initialize function
! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
END MODULE gckpp_adj_Initialize