Line data Source code
1 : module gcr_ionization
2 :
3 : use shr_kind_mod, only : r8 => shr_kind_r8
4 : use cam_abortutils, only : endrun
5 : use spmd_utils, only : masterproc
6 : use tracer_data, only : trfld,trfile
7 : use cam_logfile, only : iulog
8 : use physics_buffer, only : physics_buffer_desc
9 : use physics_types, only : physics_state
10 : use ppgrid, only : begchunk, endchunk
11 : use ppgrid, only : pcols, pver
12 : use tracer_data, only : trcdata_init, advance_trcdata
13 :
14 : implicit none
15 : private
16 : public :: gcr_ionization_readnl
17 : public :: gcr_ionization_init
18 : public :: gcr_ionization_adv
19 : public :: gcr_ionization_ionpairs
20 :
21 : type(trfld), pointer :: fields(:)
22 : type(trfile), save :: file
23 :
24 : character(len=32) :: specifier(1) = 'prod'
25 : character(len=256) :: filename = 'NONE'
26 : character(len=256) :: filelist = ''
27 : character(len=256) :: datapath = ''
28 : character(len=32) :: datatype = 'SERIAL'
29 : logical :: rmv_file = .false.
30 : integer :: cycle_yr = 0
31 : integer :: fixed_ymd = 0
32 : integer :: fixed_tod = 0
33 :
34 : logical :: has_gcr_ionization = .false.
35 :
36 : contains
37 : !-------------------------------------------------------------------
38 : !-------------------------------------------------------------------
39 0 : subroutine gcr_ionization_readnl(nlfile)
40 :
41 : use namelist_utils, only: find_group_name
42 : use units, only: getunit, freeunit
43 : use mpishorthand
44 :
45 : character(len=*), intent(in) :: nlfile ! filepath for file containing namelist input
46 :
47 : ! Local variables
48 : integer :: unitn, ierr
49 : character(len=*), parameter :: subname = 'gcr_ionization_readnl'
50 :
51 : character(len=16) :: gcr_ionization_fldname
52 : character(len=256) :: gcr_ionization_filename
53 : character(len=256) :: gcr_ionization_datapath
54 : character(len=256) :: gcr_ionization_filelist
55 : character(len=32) :: gcr_ionization_datatype
56 : integer :: gcr_ionization_cycle_yr
57 : integer :: gcr_ionization_fixed_ymd
58 : integer :: gcr_ionization_fixed_tod
59 :
60 : namelist /gcr_ionization_nl/ &
61 : gcr_ionization_fldname, &
62 : gcr_ionization_filename, &
63 : gcr_ionization_datapath, &
64 : gcr_ionization_filelist, &
65 : gcr_ionization_datatype, &
66 : gcr_ionization_cycle_yr, &
67 : gcr_ionization_fixed_ymd, &
68 : gcr_ionization_fixed_tod
69 :
70 0 : gcr_ionization_fldname = specifier(1)
71 0 : gcr_ionization_filename = filename
72 0 : gcr_ionization_datapath = datapath
73 0 : gcr_ionization_filelist = filelist
74 0 : gcr_ionization_datatype = datatype
75 0 : gcr_ionization_cycle_yr = cycle_yr
76 0 : gcr_ionization_fixed_ymd = fixed_ymd
77 0 : gcr_ionization_fixed_tod = fixed_tod
78 :
79 : ! Read namelist
80 0 : if (masterproc) then
81 0 : unitn = getunit()
82 0 : open( unitn, file=trim(nlfile), status='old' )
83 0 : call find_group_name(unitn, 'gcr_ionization_nl', status=ierr)
84 0 : if (ierr == 0) then
85 0 : read(unitn, gcr_ionization_nl, iostat=ierr)
86 0 : if (ierr /= 0) then
87 0 : call endrun(subname // ':: ERROR reading namelist')
88 : end if
89 : end if
90 0 : close(unitn)
91 0 : call freeunit(unitn)
92 : end if
93 :
94 : #ifdef SPMD
95 : ! Broadcast namelist variables
96 0 : call mpibcast(gcr_ionization_fldname, len(gcr_ionization_fldname), mpichar, 0, mpicom)
97 0 : call mpibcast(gcr_ionization_filename, len(gcr_ionization_filename), mpichar, 0, mpicom)
98 0 : call mpibcast(gcr_ionization_filelist, len(gcr_ionization_filelist), mpichar, 0, mpicom)
99 0 : call mpibcast(gcr_ionization_datapath, len(gcr_ionization_datapath), mpichar, 0, mpicom)
100 0 : call mpibcast(gcr_ionization_datatype, len(gcr_ionization_datatype), mpichar, 0, mpicom)
101 0 : call mpibcast(gcr_ionization_cycle_yr, 1, mpiint, 0, mpicom)
102 0 : call mpibcast(gcr_ionization_fixed_ymd,1, mpiint, 0, mpicom)
103 0 : call mpibcast(gcr_ionization_fixed_tod,1, mpiint, 0, mpicom)
104 : #endif
105 :
106 : ! Update module variables with user settings.
107 0 : specifier(1) = gcr_ionization_fldname
108 0 : filename = gcr_ionization_filename
109 0 : filelist = gcr_ionization_filelist
110 0 : datapath = gcr_ionization_datapath
111 0 : datatype = gcr_ionization_datatype
112 0 : cycle_yr = gcr_ionization_cycle_yr
113 0 : fixed_ymd = gcr_ionization_fixed_ymd
114 0 : fixed_tod = gcr_ionization_fixed_tod
115 :
116 : ! Turn on galactic cosmic rays if user has specified an input dataset.
117 0 : if (len_trim(filename) > 0 .and. filename.ne.'NONE') has_gcr_ionization = .true.
118 :
119 0 : end subroutine gcr_ionization_readnl
120 :
121 : !-------------------------------------------------------------------
122 : !-------------------------------------------------------------------
123 0 : subroutine gcr_ionization_init()
124 :
125 0 : if (.not.has_gcr_ionization) return
126 :
127 0 : allocate(file%in_pbuf(size(specifier)))
128 0 : file%in_pbuf(:) = .false.
129 : call trcdata_init( specifier, filename, filelist, datapath, fields, file, &
130 0 : rmv_file, cycle_yr, fixed_ymd, fixed_tod, datatype )
131 :
132 : end subroutine gcr_ionization_init
133 :
134 : !-------------------------------------------------------------------
135 : !-------------------------------------------------------------------
136 0 : subroutine gcr_ionization_adv( pbuf2d, state )
137 : type(physics_state), intent(in):: state(begchunk:endchunk)
138 : type(physics_buffer_desc), pointer :: pbuf2d(:,:)
139 :
140 0 : if (.not.has_gcr_ionization) return
141 :
142 0 : call advance_trcdata( fields, file, state, pbuf2d )
143 :
144 : end subroutine gcr_ionization_adv
145 :
146 : !-------------------------------------------------------------------
147 : !-------------------------------------------------------------------
148 0 : subroutine gcr_ionization_ionpairs( ncol, lchnk, ionpairs )
149 :
150 : integer, intent(in) :: lchnk
151 : integer, intent(in) :: ncol
152 : real(r8), intent(out) :: ionpairs(:,:)
153 :
154 0 : ionpairs(:,:) = 0._r8
155 :
156 0 : if (.not.has_gcr_ionization) return
157 :
158 0 : ionpairs(:ncol,:) = fields(1)%data(:ncol,:,lchnk)
159 :
160 : end subroutine gcr_ionization_ionpairs
161 :
162 :
163 : end module gcr_ionization
|