source: flexpart.git/src/readlanduse.f90 @ 3481cc1

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bug
Last change on this file since 3481cc1 was 3481cc1, checked in by Ignacio Pisso <ip@…>, 4 years ago

move license from headers to a different file

  • Property mode set to 100644
File size: 5.9 KB
Line 
1subroutine readlanduse
2
3  !*****************************************************************************
4  !                                                                            *
5  !      Reads the landuse inventory into memory and relates it to Leaf Area   *
6  !      Index and roughness length.                                           *
7  !                                                                            *
8  !      AUTHOR: Andreas Stohl, 10 January 1994                                *
9  !                                                                            *
10  !*****************************************************************************
11  !                                                                            *
12  ! Variables:                                                                 *
13  ! i                       loop indices                                       *
14  ! landinvent(1200,600,13) area fractions of 13 landuse categories            *
15  ! LENGTH(numpath)         length of the path names                           *
16  ! PATH(numpath)           contains the path names                            *
17  ! unitland                unit connected with landuse inventory              *
18  !                                                                            *
19  ! -----                                                                      *
20  ! Sabine Eckhardt, Dec 06 - new landuse inventary                            *
21  ! after                                                                      *
22  ! Belward, A.S., Estes, J.E., and Kline, K.D., 1999,                         *
23  ! The IGBP-DIS 1-Km Land-Cover Data Set DISCover:                            *
24  ! A Project Overview: Photogrammetric Engineering and Remote Sensing,        *
25  ! v. 65, no. 9, p. 1013-1020                                                 *
26  !                                                                            *
27  ! LANDUSE CATEGORIES:                                                        *
28  !                                                                            *
29  ! 1   Urban land                                                             *
30  ! 2   Agricultural land                                                      *
31  ! 3   Range land                                                             *
32  ! 4   Deciduous forest                                                       *
33  ! 5   Coniferous forest                                                      *
34  ! 6   Mixed forest including wetland                                         *
35  ! 7   water, both salt and fresh                                             *
36  ! 8   barren land mostly desert                                              *
37  ! 9   nonforested wetland                                                    *
38  ! 10  mixed agricultural and range land                                      *
39  ! 11  rocky open areas with low growing shrubs                               *
40  ! 12  ice                                                                    *
41  ! 13  rainforest                                                             *
42  !                                                                            *
43  !*****************************************************************************
44
45  use par_mod
46  use com_mod
47
48  implicit none
49
50  integer :: ix,jy,i,k,lu_cat,lu_perc
51  integer(kind=1) :: ilr
52  integer(kind=1) :: ilr_buffer(2160000)
53  integer :: il,irecread
54  real :: rlr, r2lr
55
56
57  ! Read landuse inventory
58  !***********************
59  ! The landuse information is saved in a compressed format and written
60  ! out by records of the length of 1 BYTE. Each grid cell consists of 3
61  ! Bytes, which include 3 landuse categories (val 1-13 and 16 percentage
62  ! categories) So one half byte is used to store the Landusecat the other
63  ! for the percentageclass in 6.25 steps (100/6.25=16)
64  ! e.g.
65  ! 4 3  percentage 4 = 4*6.25 => 25% landuse class 3
66  ! 2 1  percentage 2 = 2*6.25 => 13% landuse class 1
67  ! 1 12 percentage 1 = 1*6.26 => 6.25% landuse class 12
68
69  open(unitland,file=path(1)(1:length(1)) &
70       //'IGBP_int1.dat',status='old', &
71  !    +form='UNFORMATTED', err=998)
72       form='UNFORMATTED', err=998, convert='little_endian')
73!  print*,unitland
74  read (unitland) (ilr_buffer(i),i=1,2160000)
75  close(unitland)
76
77  irecread=1
78  do ix=1,1200
79    do jy=1,600
80  ! the 3 most abundant landuse categories in the inventory
81  ! first half byte contains the landuse class
82  ! second half byte contains the respective percentage
83      do k=1,3
84  ! 1 byte is read
85        ilr=ilr_buffer(irecread)
86  !      ilr=0
87        irecread=irecread+1
88  ! as only signed integer values exist an unsigned value is constructed
89        if (ilr.lt.0) then
90           il=ilr+256
91        else
92           il=ilr
93        endif
94  ! dividing by 16 has the effect to get rid of the right half of the byte
95  ! so just the left half remains, this corresponds to a shift right of 4
96  ! bits
97        rlr=real(il)/16.
98        lu_cat=int(rlr)
99  ! the left half of the byte is substracted from the whole in order to
100  ! get only the right half of the byte
101        r2lr=rlr-int(rlr)
102  ! shift left by 4
103        lu_perc=r2lr*16.
104        landinvent(ix,jy,k)=lu_cat
105        landinvent(ix,jy,k+3)=lu_perc
106  !       if ((jy.lt.10).and.(ix.lt.10)) write(*,*) 'reading: ' , ix, jy, lu_cat, lu_perc
107      end do
108    end do
109  end do
110
111  ! Read relation landuse,z0
112  !*****************************
113
114  open(unitsurfdata,file=path(1)(1:length(1))//'surfdata.t', &
115       status='old',err=999)
116
117  do i=1,4
118    read(unitsurfdata,*)
119  end do
120  do i=1,numclass
121    read(unitsurfdata,'(45x,f15.3)') z0(i)
122  end do
123  close(unitsurfdata)
124
125  return
126
127  ! Issue error messages
128  !*********************
129
130998   write(*,*) ' #### FLEXPART ERROR! FILE CONTAINING          ####'
131  write(*,*) ' #### LANDUSE INVENTORY DOES NOT EXIST         ####'
132  stop
133
134999   write(*,*) ' #### FLEXPART ERROR! FILE CONTAINING          ####'
135  write(*,*) ' #### RELATION LANDUSE,z0 DOES NOT EXIST       ####'
136  stop
137
138end subroutine readlanduse
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG