source: trunk/LMDZ.MARS/libf/aeronomars/iono_h.F90 @ 2325

Last change on this file since 2325 was 2158, checked in by emillour, 5 years ago

Mars GCM:

  • Updated chemical core to include ionospheric chemistry

FGG

File size: 6.2 KB
Line 
1MODULE iono_h
2
3      IMPLICIT NONE
4
5      character*1,save,allocatable :: o1d_eq(:)
6      character*1,save,allocatable :: ho2_eq(:)
7      character*1,save,allocatable :: oh_eq(:)
8      character*1,save,allocatable :: h_eq(:)
9      character*1,save,allocatable :: n2d_eq(:)
10      character*1,save,allocatable :: no2_eq(:)
11      character*1,save,allocatable :: o3_eq(:)
12      character*1,save,allocatable :: no_eq(:)
13      character*1,save,allocatable :: cplus_eq(:)
14      character*1,save,allocatable :: coplus_eq(:)
15      character*1,save,allocatable :: oplus_eq(:)
16      character*1,save,allocatable :: n2plus_eq(:)
17      character*1,save,allocatable :: hplus_eq(:)
18      character*1,save,allocatable :: co2plus_eq(:)
19      character*1,save,allocatable :: o2plus_eq(:)
20      character*1,save,allocatable :: noplus_eq(:)
21      character*1,save,allocatable :: nplus_eq(:)
22      character*1,save,allocatable :: hco2plus_eq(:)
23      real*8,save,allocatable ::   tauco2(:,:)
24      real*8,save,allocatable ::   tauo2(:,:)
25      real*8,save,allocatable ::   tauo3p(:,:)
26      real*8,save,allocatable ::   tauco(:,:)
27      real*8,save,allocatable ::   tauh(:,:)
28      real*8,save,allocatable ::   tauoh(:,:)
29      real*8,save,allocatable ::   tauho2(:,:)
30      real*8,save,allocatable ::   tauh2(:,:)
31      real*8,save,allocatable ::   tauh2o(:,:)
32      real*8,save,allocatable ::   tauo1d(:,:)
33      real*8,save,allocatable ::   tauh2o2(:,:)
34      real*8,save,allocatable ::   tauo3(:,:)
35      real*8,save,allocatable ::   taun(:,:)
36      real*8,save,allocatable ::   tauno(:,:)
37      real*8,save,allocatable ::   taun2(:,:)
38      real*8,save,allocatable ::   taun2d(:,:)
39      real*8,save,allocatable ::   tauno2(:,:)
40      real*8,save,allocatable ::   tauco2plus(:,:)
41      real*8,save,allocatable ::   tauoplus(:,:)
42      real*8,save,allocatable ::   tauo2plus(:,:)
43      real*8,save,allocatable ::   taucoplus(:,:)
44      real*8,save,allocatable ::   taucplus(:,:)
45      real*8,save,allocatable ::   taunplus(:,:)
46      real*8,save,allocatable ::   taunoplus(:,:)
47      real*8,save,allocatable ::   taun2plus(:,:)
48      real*8,save,allocatable ::   tauhplus(:,:)
49      real*8,save,allocatable ::   tauhco2plus(:,:)
50
51      CONTAINS
52
53         SUBROUTINE allocate_param_iono(nlayer,nreact)
54
55           IMPLICIT NONE
56
57           INTEGER :: nreact
58           INTEGER :: nlayer
59
60           allocate(o1d_eq(nlayer))
61           allocate(ho2_eq(nlayer))
62           allocate(oh_eq(nlayer))
63           allocate(h_eq(nlayer))
64           allocate(n2d_eq(nlayer))
65           allocate(no2_eq(nlayer))
66           allocate(o3_eq(nlayer))
67           allocate(no_eq(nlayer))
68           allocate(cplus_eq(nlayer))
69           allocate(coplus_eq(nlayer))
70           allocate(oplus_eq(nlayer))
71           allocate(n2plus_eq(nlayer))
72           allocate(hplus_eq(nlayer))
73           allocate(co2plus_eq(nlayer))
74           allocate(o2plus_eq(nlayer))
75           allocate(noplus_eq(nlayer))
76           allocate(nplus_eq(nlayer))
77           allocate(hco2plus_eq(nlayer))
78           allocate(tauco2(nreact,nlayer))
79           allocate(tauo2(nreact,nlayer))
80           allocate(tauo3p(nreact,nlayer))
81           allocate(tauco(nreact,nlayer))
82           allocate(tauh(nreact,nlayer))
83           allocate(tauoh(nreact,nlayer))
84           allocate(tauho2(nreact,nlayer))
85           allocate(tauh2(nreact,nlayer))
86           allocate(tauh2o(nreact,nlayer))
87           allocate(tauo1d(nreact,nlayer))
88           allocate(tauh2o2(nreact,nlayer))
89           allocate(tauo3(nreact,nlayer))
90           allocate(taun(nreact,nlayer))
91           allocate(tauno(nreact,nlayer))
92           allocate(taun2(nreact,nlayer))
93           allocate(taun2d(nreact,nlayer))
94           allocate(tauno2(nreact,nlayer))
95           allocate(tauco2plus(nreact,nlayer))
96           allocate(tauoplus(nreact,nlayer))
97           allocate(tauo2plus(nreact,nlayer))
98           allocate(taucoplus(nreact,nlayer))
99           allocate(taucplus(nreact,nlayer))
100           allocate(taunplus(nreact,nlayer))
101           allocate(taunoplus(nreact,nlayer))
102           allocate(taun2plus(nreact,nlayer))
103           allocate(tauhplus(nreact,nlayer))
104           allocate(tauhco2plus(nreact,nlayer))
105         
106         END SUBROUTINE allocate_param_iono
107
108
109!***********************************************************************
110      function temp_elect(zkm,tt,origin)
111
112!     Computes the electronic temperature, either from Viking (origin=1)
113!     or MAVEN (origin=2)
114
115!***********************************************************************
116     
117!     Arguments         
118
119      real            tt        ! Temperature
120      real            zkm       !  Altitude in km
121      integer         origin    ! Viking (origin=1) or MAVEN (origin=2)
122
123! local variables:
124      real          temp_elect     ! electronic temperatures
125      real          zhanson(9),tehanson(9)
126      real          incremento
127      integer       ii, i1, i2
128
129      zhanson(1:9) = (/ 120.,130.,150.,175.,200.,225.,250.,275.,300. /)
130      tehanson(2:9) = (/ 200.,300.,500.,1250.,2000.,2200.,2400.,2500. /)
131      tehanson(1) = tt
132
133      if(origin.eq.1) then
134         if ( zkm .le. 120. ) then
135            temp_elect = tt
136         else if(zkm .ge.300.) then
137            temp_elect=tehanson(9)
138         else
139            do ii=9,2,-1
140               if ( zkm .lt. zhanson(ii) ) then
141                  i1 = ii - 1
142                  i2 = ii
143               endif
144            enddo
145            incremento=(tehanson(i2)-tehanson(i1))/(zhanson(i2)-zhanson(i1))
146            temp_elect = tehanson(i1) + (zkm-zhanson(i1)) * incremento
147        endif
148      else if(origin.eq.2) then
149         !MAVEN measured electronic temperature (Ergun et al., GRL 2015)
150         !Note that the Langmuir probe is not sensitive below ~500K, so
151         !electronic temperatures in the lower thermosphere (<150 km) may
152         !be overestimated by this formula
153         if(zkm.le.120) then
154            temp_elect = tt
155         else
156            temp_elect=((3140.+120.)/2.)+((3140.-120.)/2.)*tanh((zkm-241.)/60.)
157         endif
158      else
159         write(*,*)'Error in function temp_elect:'
160         write(*,*)'Origin must be either 1 or 2'
161         write(*,*)'Using neutral temperature instead'
162         temp_elect = tt
163      endif
164
165      return
166
167      end function temp_elect
168
169END MODULE iono_h
Note: See TracBrowser for help on using the repository browser.