source: branches/jerome/src_flexwrf_v3.1/readohfield.f90 @ 16

Last change on this file since 16 was 16, checked in by jebri, 10 years ago

sources for flexwrf v3.1

File size: 4.0 KB
Line 
1!**********************************************************************
2! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
3! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
4! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
5!                                                                     *
6! This file is part of FLEXPART.                                      *
7!                                                                     *
8! FLEXPART is free software: you can redistribute it and/or modify    *
9! it under the terms of the GNU General Public License as published by*
10! the Free Software Foundation, either version 3 of the License, or   *
11! (at your option) any later version.                                 *
12!                                                                     *
13! FLEXPART is distributed in the hope that it will be useful,         *
14! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
15! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
16! GNU General Public License for more details.                        *
17!                                                                     *
18! You should have received a copy of the GNU General Public License   *
19! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
20!**********************************************************************
21
22subroutine readohfield
23
24  !*****************************************************************************
25  !                                                                            *
26  ! Reads the OH field into memory                                             *
27  !                                                                            *
28  ! AUTHOR: Sabine Eckhardt, June 2007                                         *
29  !                                                                            *
30  !*****************************************************************************
31  !                                                                            *
32  ! Variables:                                                                 *
33  ! i                       loop indices                                       *
34  ! LENGTH(numpath)         length of the path names                           *
35  ! PATH(numpath)           contains the path names                            *
36  ! unitoh                  unit connected with OH field                       *
37  !                                                                            *
38  ! -----                                                                      *
39  !                                                                            *
40  !*****************************************************************************
41
42  use oh_mod
43  use par_mod
44  use com_mod
45
46  implicit none
47
48  integer :: ix,jy,lev,m
49
50
51  ! Read OH field and level heights
52  !********************************
53
54! write (*,*) 'reading OH'
55!  open(unitOH,file=path(1)(1:length(1))//'OH_7lev_agl.dat', &
56  open(unitOH,file='OH_7lev_agl.dat', &
57       status='old',form='UNFORMATTED', err=998)
58  do m=1,12
59    do lev=1,maxzOH
60      do ix=0,maxxOH-1
61  !      do 10 jy=0,maxyOH-1
62          read(unitOH) (OH_field(m,ix,jy,lev),jy=0,maxyOH-1)
63  !      if ((ix.eq.20).and.(lev.eq.1)) then
64  !          write(*,*) 'reading: ', m, OH_field(m,ix,20,lev)
65  !      endif
66      end do
67    end do
68  end do
69  close(unitOH)
70
71  do lev=1,7
72    OH_field_height(lev)=1000+real(lev-1)*2.*1000.
73  end do
74
75!  write (*,*) 'OH read'
76  return
77
78  ! Issue error messages
79  !*********************
80
81998   write(*,*) ' #### FLEXPART ERROR! FILE CONTAINING          ####'
82  write(*,*) ' #### OH FIELD DOES NOT EXIST                  ####'
83  write(*,*) ' #### IT IS NEEDED FOR OH REACTION             ####'
84  write(*,*) ' #### COPY DATA FROM src_flexwrf_v3.0/data     ####'
85  write(*,*) ' #### IN YOUR CURRENT DIRECTORY                ####'
86  write(*,*) ' #### OR USE A DIFFERENT SPECIES               ####'
87
88  stop
89
90end subroutine readohfield
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG