EMPIRE DA  v1.9.1
Data assimilation codes using EMPIRE communication
 All Classes Files Functions Variables Pages
Lorenz96_hidden_empire_v2.f90
Go to the documentation of this file.
1 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2 ! Implements Lorenz 1996 model with hidden fast modes as in
3 ! Bergemann 2010 http://doi.wiley.com/10.1002/qj.672
4 !
5 !The MIT License (MIT)
6 !
7 !Copyright (c) 2015 Philip A. Browne
8 !
9 !Permission is hereby granted, free of charge, to any person obtaining a copy
10 !of this software and associated documentation files (the "Software"), to deal
11 !in the Software without restriction, including without limitation the rights
12 !to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
13 !copies of the Software, and to permit persons to whom the Software is
14 !furnished to do so, subject to the following conditions:
15 !
16 !The above copyright notice and this permission notice shall be included in all
17 !copies or substantial portions of the Software.
18 !
19 !THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
20 !IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
21 !FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
22 !AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
23 !LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
24 !OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
25 !SOFTWARE.
26 !
27 !Email: p.browne@reading.ac.uk
28 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
29 
31  implicit none
32  include 'mpif.h'
33  real(kind=kind(1.0D0)) :: dt=2.5d-3
34  real(kind=kind(1.0D0)), allocatable, dimension(:,:) :: x,k1,k2,k3,k4
35  real(kind=kind(1.0d0)) :: F=8.0d0
36  real(kind=kind(1.0d0)) :: alpha=0.5d0
37  real(kind=kind(1.0d0)) :: delta=0.5d0
38  real(kind=kind(1.0d0)) :: epsilon=2.5d-3
39  real(kind=kind(1.0d0)) :: gamma=0.1d0
40  integer :: N=40
41  integer :: total_timesteps=1000
42  integer :: t
43  integer :: mpi_err,mdl_rank,cpl_root,cpl_mpi_comm
44  real(kind=kind(1.0d0)), dimension(0) :: send_null
45  integer :: tag
46  integer :: ios
47  logical :: l96_exists
48 
49  namelist/l96/n,&
50  &total_timesteps,&
51  &f,&
52  &dt,&
53  &delta,&
54  &epsilon,&
55  &alpha,&
56  &gamma
57 
58 
59  inquire(file='l96.nml', exist=l96_exists)
60  if(l96_exists) then
61  open(32,file='l96.nml',iostat=ios,action='read'&
62  &,status='old')
63  if(ios .ne. 0) stop 'Cannot open l96.nml'
64  read(32,nml=l96)
65  close(32)
66  end if
67 
68 
69  call initialise_mpi_v2(mdl_rank,cpl_root,cpl_mpi_comm)
70 
71  call empire_process_dimensions(n,cpl_root,cpl_mpi_comm)
72 
73  allocate(x(n,3),k1(n,3),k2(n,3),k3(n,3),k4(n,3))
74  x = f
75  x(:,1) = f
76  x(:,2) = f
77  x(:,3) = 0.
78  x(n/2,1) = f+0.05d0
79  print*,x(:,1)
80 
81 
82 
83  !send the state to da code with mpi_gatherv
84  call mpi_gatherv(x(:,1),n,mpi_double_precision,x(:,1)&
85  &,n,n,mpi_double_precision,cpl_root&
86  &,cpl_mpi_comm,mpi_err)
87 
88 
89  !get the state back from da code with mpi_gatherv
90  call mpi_scatterv(send_null,0,0,mpi_double_precision,x(:,1)&
91  &,n,mpi_double_precision,cpl_root,cpl_mpi_comm,mpi_err)
92  !get the tag from the da code
93  call mpi_bcast(tag,1,mpi_integer,cpl_root,cpl_mpi_comm,mpi_err)
94 2 continue
95 
96 
97  do t = 1,total_timesteps
98  k1 = g(x , n , f ,alpha,delta,epsilon,gamma)
99  k2 = g(x +0.5d0 * dt * k1 , n , f ,alpha,delta,epsilon,gamma)
100  k3 = g(x +0.5d0 * dt * k2 , n , f ,alpha,delta,epsilon,gamma)
101  k4 = g(x + dt * k3 , n , f ,alpha,delta,epsilon,gamma)
102  x = x + dt *( k1 + 2.0d0 *( k2 + k3 ) + k4 )/6.0d0
103 
104 
105  !send the state to da code with mpi_gatherv
106  call mpi_gatherv(x(:,1),n,mpi_double_precision,x(:,1)&
107  &,n,n,mpi_double_precision,cpl_root&
108  &,cpl_mpi_comm,mpi_err)
109 
110  !get the state back from da code with mpi_gatherv
111  call mpi_scatterv(send_null,0,0,mpi_double_precision,x(:,1)&
112  &,n,mpi_double_precision,cpl_root,cpl_mpi_comm,mpi_err)
113  !get the tag from the da code
114  call mpi_bcast(tag,1,mpi_integer,cpl_root,cpl_mpi_comm,mpi_err)
115 
116  print*,x(:,1)
117 
118  select case(tag)
119  case(2)
120  go to 2
121  case(3)
122  go to 3
123  case default
124  end select
125 
126 
127 
128  end do
129 3 continue
130  call mpi_finalize(mpi_err)
131 
132 contains
133  function g (X , N, F ,alpha,delta,epsilon,gamma)
134  implicit none
135  real(kind=kind(1.0D0)),intent(in),dimension(N,3) :: X
136  integer, intent(in) :: N
137  real(kind=kind(1.0D0)),dimension(N,3) :: g
138  real(kind=kind(1.0D0)),intent(in) :: F
139  real(kind=kind(1.0D0)),intent(in) :: alpha
140  real(kind=kind(1.0D0)),intent(in) :: delta
141  real(kind=kind(1.0D0)),intent(in) :: epsilon
142  real(kind=kind(1.0D0)),intent(in) :: gamma
143  integer :: j
144 
145  g(1,1) = (1.0d0-delta)*(x(2,1)-x(n-1,1) )*x(n,1) + delta*(x(n,1)*x(2,2)-x(n-1,1)*x(n,2)) - x(1,1) + f
146  g(1,2) = x(1,3)
147  g(1,3) = (-x(1,2) + alpha**2*(x(2,2)-2*x(1,2)+x(n,2)) + x(1,1) - gamma*epsilon**2*x(1,3))/(epsilon**2)
148 
149  g(2,1) = (1.0d0-delta)*(x(3,1)-x(n,1) )*x(1,1) + delta*(x(1,1)*x(3,2)-x(n,1)*x(1,2)) - x(2,1) + f
150  g(2,2) = x(2,3)
151  g(2,3) = (-x(2,2) + alpha**2*(x(3,2)-2*x(2,2)+x(1,2)) + x(2,1) - gamma*epsilon**2*x(2,3))/(epsilon**2)
152 
153 
154  do j = 3,n-1
155  g(j,1) = (1.0d0-delta)*(x(j+1,1)-x(j-2,1))*x(j-1,1) + delta*(x(j-1,1)*x(j+1,2)-x(j-2,1)*x(j-1,2)) - x(j,1) + f
156  g(j,2) = x(j,3)
157  g(j,3) = (-x(j,2) + alpha**2*(x(j+1,2)-2*x(j,2)+x(j-1,2)) + x(j,1) - gamma*epsilon**2*x(j,3))/(epsilon**2)
158  end do
159 
160  g(n,1) = (1.0d0-delta)*(x(1,1)-x(n-2,1) )*x(n-1,1) + delta*(x(n-1,1)*x(1,2)-x(n-2,1)*x(n-1,2)) - x(n,1) + f
161  g(n,2) = x(n,3)
162  g(n,3) = (-x(n,2) + alpha**2*(x(1,2)-2*x(n,2)+x(n-1,2)) + x(n,1) - gamma*epsilon**2*x(n,3))/(epsilon**2)
163 
164 
165 
166  end function g
167  subroutine initialise_mpi_v2(mdl_rank,cpl_root,cpl_mpi_comm)
168 
169 
170  implicit none
171 
172  include 'mpif.h'
173  integer, intent(out) :: mdl_rank
174  integer, intent(out) :: cpl_root
175  integer, intent(out) :: cpl_mpi_comm
176 
177  integer, parameter :: mdl_num_proc=1
178  integer :: mdl_mpi_comm
179 
180  integer :: mpi_err
181  integer :: world_rank
182  integer :: world_size
183 
184  integer :: temp_mdls_size
185  integer :: temp_cpl_comm
186  integer :: temp_mdls_comm
187  integer :: temp_mdls_rank
188  integer :: da
189  integer :: i
190  integer :: particle_rank
191  integer :: nda
192  integer :: nens
193  integer :: first_ptcl
194  integer :: final_ptcl
195  integer :: null_mpi_comm
196 
197  logical :: msg=.true.
198 
199 
200  call mpi_init(mpi_err)
201  if(mpi_err .eq. 0) then
202  if(msg) print*,'mpi_init successful'
203  else
204  print*,'mpi_init unsuccessful'
205  end if
206 
207 
208  call mpi_comm_rank(mpi_comm_world,world_rank,mpi_err)
209  if(mpi_err .eq. 0) then
210  if(msg) print*,'mpi_comm_rank successful'
211  if(msg) print*,'world_rank = ',world_rank
212  else
213  print*,'mpi_comm_rank unsuccessful'
214  end if
215 
216 
217  call mpi_comm_size(mpi_comm_world,world_size,mpi_err)
218  if(mpi_err .eq. 0) then
219  if(msg) print*,'mpi_comm_size successful'
220  if(msg) print*,'world_size = ',world_size
221  else
222  print*,'mpi_comm_size unsuccessful'
223  end if
224 
225 
226  cpl_root = world_size-1
227  if(msg) then
228  print*,'rank = ',world_rank,' on mpi_comm_world which has &
229  &size ',world_size
230  end if
231 
232  da = 0
233 
234 
235  call mpi_allreduce(mdl_num_proc,i,1,mpi_integer,mpi_max&
236  &,mpi_comm_world,mpi_err)
237  if(mpi_err .eq. 0) then
238  if(msg) print*,'mpi_allreduce successful'
239  if(msg) print*,'i = ',i
240  else
241  print*,'mpi_allreduce unsuccessful'
242  end if
243 
244 
245 
246  call mpi_comm_split(mpi_comm_world,da,world_rank,temp_mdls_comm&
247  &,mpi_err)
248  if(mpi_err .eq. 0) then
249  if(msg) print*,'mpi_comm_split successful: temp_mdls_comm created'
250  else
251  print*,'mpi_comm_split unsuccessful: temp_mdls_comm not created'
252  end if
253 
254  call mpi_comm_size(temp_mdls_comm,temp_mdls_size,mpi_err)
255  if(mpi_err .eq. 0) then
256  if(msg) print*,'mpi_comm_size successful'
257  if(msg) print*,'temp_mdls_size = ',temp_mdls_size
258  else
259  print*,'mpi_comm_size unsuccessful'
260  end if
261 
262 
263  if(mod(temp_mdls_size,mdl_num_proc) .ne. 0) then
264  print*,'MINIMAL MODEL LAUNCH ERROR.'
265  print*,'MUST LAUNCH A MULTIPLE OF ',mdl_num_proc,' copies of the &
266  &model'
267  stop
268  end if
269 
270 
271  nda = world_size-temp_mdls_size
272  if(nda .lt. 1) then
273  print*,'MINIMAL MODEL COMMS v2 ERROR: nda is less than 1.'
274  print*,'Make sure you launch with a DA CODE'
275  stop
276  end if
277 
278 
279 
280  nens = temp_mdls_size/mdl_num_proc
281  call mpi_comm_rank(temp_mdls_comm,temp_mdls_rank,mpi_err)
282  if(mpi_err .eq. 0) then
283  if(msg) print*,'mpi_comm_rank successful'
284  if(msg) print*,'temp_mdls_rank = ',temp_mdls_rank
285  else
286  print*,'mpi_comm_rank unsuccessful'
287  end if
288 
289 
290  particle_rank = temp_mdls_rank/mdl_num_proc
291 
292  call mpi_comm_split(temp_mdls_comm,particle_rank,temp_mdls_rank&
293  &,mdl_mpi_comm,mpi_err)
294  if(mpi_err .eq. 0) then
295  if(msg) print*,'mpi_comm_split successful: mdl_mpi_comm created'
296  else
297  print*,'mpi_comm_split unsuccessful: mdl_mpi_comm not created'
298  end if
299 
300 
301 
302  call mpi_comm_rank(mdl_mpi_comm,mdl_rank,mpi_err)
303  if(mpi_err .eq. 0) then
304  if(msg) print*,'mpi_comm_rank successful'
305  if(msg) print*,'mdl_rank = ',mdl_rank
306  else
307  print*,'mpi_comm_rank unsuccessful'
308  end if
309 
310 
311  cpl_root = nda*particle_rank/nens
312  if(msg) print*,'cpl_root = ',cpl_root
313 
314  if(cpl_root .lt. 0) then
315  print*,'MINIMAL MODEL COMMS v2 ERROR: cpl_root is less than 0.'
316  print*,'Make sure you launch with a DA CODE'
317  stop
318  end if
319 
320  call mpi_comm_split(mpi_comm_world,cpl_root,temp_mdls_rank,temp_cpl_comm,mpi_err)
321  if(mpi_err .eq. 0) then
322  if(msg) print*,'mpi_comm_split successful: temp_cpl_comm created'
323  else
324  print*,'mpi_comm_split unsuccessful: temp_cpl_comm not created'
325  end if
326 
327 
328 
329 
330 
331 
332  first_ptcl = ceiling(real(cpl_root)*real(nens)/real(nda))
333  final_ptcl = ceiling(real(cpl_root+1)*real(nens)/real(nda))-1
334 
335 
336  if(msg) print*,'range of particles = ',first_ptcl,final_ptcl
337 
338 
339 
340  do i = first_ptcl,final_ptcl
341  if(msg) print*,'i = ',i,' particle_rank = ',particle_rank
342  if(i .eq. particle_rank) then
343  call mpi_comm_split(temp_cpl_comm,1,temp_mdls_rank&
344  &,cpl_mpi_comm,mpi_err)
345  if(msg) print*,'created cpl_mpi_comm'
346  else
347  if(msg) print*,'doing null splitting'
348  call mpi_comm_split(temp_cpl_comm,0,temp_mdls_rank&
349  &,null_mpi_comm,mpi_err)
350  if(msg) print*,'created mpi_comm_null'
351  call mpi_comm_free(null_mpi_comm,mpi_err)
352  if(msg) print*,'freed up null_mpi_comm'
353  end if
354 
355 
356  end do
357 
358  cpl_root = mdl_num_proc
359 
360 
361 
362 
363  end subroutine initialise_mpi_v2
364 
365  subroutine empire_process_dimensions(N,cpl_root,cpl_mpi_comm)
366  implicit none
367  include 'mpif.h'
368  integer, intent(in) :: N
369  integer, intent(in) :: cpl_root
370  integer, intent(in) :: cpl_mpi_comm
371  integer :: mpi_err
372  logical :: msg = .true.
373 
374  if(msg) print*,'called empire_process_dimensions'
375  call mpi_gather(n,1,mpi_integer,n&
376  &,1,mpi_integer,cpl_root,cpl_mpi_comm,mpi_err)
377  if(msg) print*,'finished the gather on cpl_mpi_comm for empire_process_dimensions'
378  end subroutine empire_process_dimensions
379 
380 
381 
382 end program lorenz96_hidden_v2
subroutine empire_process_dimensions(N, cpl_root, cpl_mpi_comm)
program lorenz96_hidden_v2
real(kind=kind(1.0d0)) function, dimension(n, 3) g(X, N, F, alpha, delta, epsilon, gamma)
subroutine initialise_mpi_v2(mdl_rank, cpl_root, cpl_mpi_comm)