source: trunk/LMDZ.COMMON/libf/evolution/math_mod.F90 @ 3532

Last change on this file since 3532 was 3532, checked in by jbclement, 3 weeks ago

PEM:
Removing unecessary module/subroutine "interpol_TI_PEM2PCM.F90" + Few small corrections/cleanings.
JBC

File size: 4.9 KB
Line 
1module math_mod
2!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
3!!!
4!!! Purpose: The module contains all the mathematical SUBROUTINE used in the PEM
5!!!
6!!! Author: Adapted from Schorgofer MSIM (N.S, Icarus 2010), impletented here by LL
7!!!
8!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
9
10implicit none
11
12!=======================================================================
13  contains
14!=======================================================================
15
16SUBROUTINE deriv1(z,nz,y,y0,ybot,dzY)
17!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
18!!!
19!!! Purpose: Compute the first derivative of a function y(z) on an irregular grid
20!!!
21!!! Author: From N.S (N.S, Icarus 2010), impletented here by LL
22!!!
23!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
24! first derivative of a function y(z) on irregular grid
25! upper boundary conditions: y(0) = y0
26! lower boundary condition.: yp = ybottom
27
28implicit none
29
30integer, intent(in) :: nz      ! number of layer
31real,    intent(in) :: z(nz)   ! depth layer
32real,    intent(in) :: y(nz)   ! function which needs to be derived
33real,    intent(in) :: y0,ybot ! boundary conditions
34real, intent(out) :: dzY(nz) ! derivative of y w.r.t depth
35! local
36integer :: j
37real    :: hm, hp, c1, c2, c3
38
39hp = z(2) - z(1)
40c1 = z(1)/(hp*z(2))
41c2 = 1/z(1) - 1/(z(2) - z(1))
42c3 = -hp/(z(1)*z(2))
43dzY(1) = c1*y(2) + c2*y(1) + c3*y0
44do j = 2,nz - 1
45    hp = z(j + 1) - z(j)
46    hm = z(j) - z(j - 1)
47    c1 = +hm/(hp*(z(j + 1) - z(j - 1)))
48    c2 = 1/hm - 1/hp
49    c3 = -hp/(hm*(z(j + 1) - z(j - 1)))
50    dzY(j) = c1*y(j + 1) + c2*y(j) + c3*y(j - 1)
51enddo
52dzY(nz) = (ybot - y(nz - 1))/(2.*(z(nz) - z(nz - 1)))
53
54END SUBROUTINE deriv1
55
56!=======================================================================
57
58SUBROUTINE deriv2_simple(z,nz,y,y0,yNp1,yp2)
59!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
60!!!
61!!! Purpose: Compute the second derivative of a function y(z) on an irregular grid
62!!!
63!!! Author: N.S (raw copy/paste from MSIM)
64!!!
65!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
66! second derivative y_zz on irregular grid
67! boundary conditions: y(0) = y0, y(nz + 1) = yNp1
68
69implicit none
70
71integer, intent(in) :: nz
72real,    intent(in) :: z(nz), y(nz), y0, yNp1
73real, intent(out) :: yp2(nz)
74integer :: j
75real    :: hm, hp, c1, c2, c3
76
77c1 = +2./((z(2) - z(1))*z(2))
78c2 = -2./((z(2) - z(1))*z(1))
79c3 = +2./(z(1)*z(2))
80yp2(1) = c1*y(2) + c2*y(1) + c3*y0
81do j = 2,nz - 1
82    hp = z(j + 1) - z(j)
83    hm = z(j) - z(j - 1)
84    c1 = +2./(hp*(z(j + 1) - z(j - 1)))
85    c2 = -2./(hp*hm)
86    c3 = +2./(hm*(z(j + 1) - z(j-1)))
87    yp2(j) = c1*y(j + 1) + c2*y(j) + c3*y(j - 1)
88enddo
89yp2(nz) = (yNp1 - 2*y(nz) + y(nz - 1))/(z(nz) - z(nz - 1))**2
90
91END SUBROUTINE deriv2_simple
92
93!=======================================================================
94
95SUBROUTINE  deriv1_onesided(j,z,nz,y,dy_zj)
96!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
97!!!
98!!! Purpose: First derivative of function y(z) at z(j)  one-sided derivative on irregular grid
99!!!
100!!! Author: N.S (raw copy/paste from MSIM)
101!!!
102!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
103
104  implicit none
105
106integer, intent(in) :: nz, j
107real,    intent(in) :: z(nz), y(nz)
108real, intent(out) :: dy_zj
109real :: h1, h2, c1, c2, c3
110
111if (j < 1 .or. j > nz - 2) then
112    dy_zj = -1.
113else
114    h1 = z(j + 1) - z(j)
115    h2 = z(j + 2)- z(j + 1)
116    c1 = -(2*h1 + h2)/(h1*(h1 + h2))
117    c2 = (h1 + h2)/(h1*h2)
118    c3 = -h1/(h2*(h1 + h2))
119    dy_zj = c1*y(j) + c2*y(j + 1) + c3*y(j + 2)
120endif
121
122END SUBROUTINE deriv1_onesided
123
124!=======================================================================
125
126PURE SUBROUTINE colint(y,z,nz,i1,i2,integral)
127!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
128!!!
129!!! Purpose:  Column integrates y on irregular grid
130!!!
131!!! Author: N.S (raw copy/paste from MSIM)
132!!!
133!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
134
135implicit none
136
137integer, intent(in) :: nz, i1, i2
138real,    intent(in) :: y(nz), z(nz)
139real, intent(out) :: integral
140integer i
141real dz(nz)
142
143dz(1) = (z(2) - 0.)/2
144do i = 2,nz - 1
145    dz(i) = (z(i + 1) - z(i - 1))/2.
146enddo
147dz(nz) = z(nz) - z(nz - 1)
148integral = sum(y(i1:i2)*dz(i1:i2))
149
150END SUBROUTINE colint
151
152!=======================================================================
153
154SUBROUTINE findroot(y1,y2,z1,z2,zr)
155!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
156!!!
157!!! Purpose: Compute the root zr, between two values y1 and y2 at depth z1,z2
158!!!
159!!! Author: LL
160!!!
161!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
162
163implicit none
164
165real, intent(in) :: y1, y2 ! difference between surface water density and at depth  [kg/m^3]
166real, intent(in) :: z1, z2 ! depth [m]
167real, intent(out) :: zr    ! depth at which we have zero
168
169zr = (y1*z2 - y2*z1)/(y1 - y2)
170
171END SUBROUTINE findroot
172
173end module math_mod
Note: See TracBrowser for help on using the repository browser.