SOCA
soca_geom_iter_mod.F90
Go to the documentation of this file.
1 ! (C) Copyright 2019-2021 UCAR
2 !
3 ! This software is licensed under the terms of the Apache Licence Version 2.0
4 ! which can be obtained at http://www.apache.org/licenses/LICENSE-2.0.
5 
6 !> Geometry iterator
8 
9 use kinds, only : kind_real
10 use soca_geom_mod, only: soca_geom
11 
12 implicit none
13 private
14 
15 
16 ! ------------------------------------------------------------------------------
17 ! ------------------------------------------------------------------------------
18 
19 ! ------------------------------------------------------------------------------
20 !> Geometry iterator
21 !!
22 !! When initialized, the iterator points to the first valid local grid cell.
23 !! Calls to soca_geom_iter::next() moves the iterator forward, and calls to
24 !! soca_geom_iter::current() retrieves the lat/lon of the current grid cell.
25 !! The iterator is mainly used by soca_increment_mod::soca_increment::getpoint()
26 !! and soca_increment_mod::soca_increment::setpoint()
27 type, public :: soca_geom_iter
28  type(soca_geom), pointer, private :: geom => null() !< Geometry
29 
30  integer :: iind = 1 !< i index of current grid point
31  integer :: jind = 1 !< j index of current grid point
32 
33 contains
34 
35  !> \copybrief soca_geom_iter_setup \see soca_geom_iter_setup
36  procedure :: setup => soca_geom_iter_setup
37 
38  !> \copybrief soca_geom_iter_clone \see soca_geom_iter_clone
39  procedure :: clone => soca_geom_iter_clone
40 
41  !> \copybrief soca_geom_iter_equals \see soca_geom_iter_equals
42  procedure :: equals => soca_geom_iter_equals
43 
44  !> \copybrief soca_geom_iter_current \see soca_geom_iter_current
45  procedure :: current => soca_geom_iter_current
46 
47  !> \copybrief soca_geom_iter_next \see soca_geom_iter_next
48  procedure :: next => soca_geom_iter_next
49 
50 end type soca_geom_iter
51 
52 
53 ! ------------------------------------------------------------------------------
54 contains
55 ! ------------------------------------------------------------------------------
56 
57 
58 ! ------------------------------------------------------------------------------
59 !> Setup for the geometry iterator
60 !!
61 !! \relates soca_geom_iter_mod::soca_geom_iter
62 subroutine soca_geom_iter_setup(self, geom, iind, jind)
63  class(soca_geom_iter), intent(inout) :: self
64  type(soca_geom), pointer, intent( in) :: geom !< Pointer to geometry
65  integer, intent( in) :: iind, jind !< starting index
66 
67  ! Associate geometry
68  self%geom => geom
69 
70  ! Define iind/jind for local tile
71  self%iind = iind
72  self%jind = jind
73 
74 end subroutine soca_geom_iter_setup
75 
76 
77 ! ------------------------------------------------------------------------------
78 !> Clone for the geometry iterator from \p other to \p self
79 !!
80 !! \relates soca_geom_iter_mod::soca_geom_iter
81 subroutine soca_geom_iter_clone(self, other)
82  class(soca_geom_iter), intent(inout) :: self
83  type(soca_geom_iter), intent( in) :: other !< Other geometry iterator to clone from
84 
85  ! Associate geometry
86  self%geom => other%geom
87 
88  ! Copy iind/jind
89  self%iind = other%iind
90  self%jind = other%jind
91 
92 end subroutine soca_geom_iter_clone
93 
94 
95 ! ------------------------------------------------------------------------------
96 !> Check for the geometry iterator equality (pointing to same i/j location)
97 !!
98 !! \relates soca_geom_iter_mod::soca_geom_iter
99 subroutine soca_geom_iter_equals(self, other, equals)
100  class(soca_geom_iter), intent( in) :: self
101  type(soca_geom_iter), intent( in) :: other !< Other geometry iterator
102  integer, intent(out) :: equals !< Equality flag
103 
104  ! Initialization
105  equals = 0
106 
107  ! Check equality
108  if (associated(self%geom, other%geom) .and. (self%iind==other%iind) &
109  .and. (self%jind==other%jind)) equals = 1
110 
111 end subroutine soca_geom_iter_equals
112 
113 
114 ! ------------------------------------------------------------------------------
115 !> Get geometry iterator current lat/lon
116 !!
117 !! \throws abor1_ftn aborts if iterator is out of bounds
118 !! \relates soca_geom_iter_mod::soca_geom_iter
119 subroutine soca_geom_iter_current(self, lon, lat)
120  class(soca_geom_iter), intent( in) :: self
121  real(kind_real), intent(out) :: lat !< Latitude
122  real(kind_real), intent(out) :: lon !< Longitude
123 
124  ! Check iind/jind
125  if (self%iind == -1 .AND. self%jind == -1) then
126  ! special case of {-1,-1} means end of the grid
127  lat = self%geom%lat(self%geom%iec,self%geom%jec)
128  lon = self%geom%lon(self%geom%iec,self%geom%jec)
129  elseif (self%iind < self%geom%isc .OR. self%iind > self%geom%iec .OR. &
130  self%jind < self%geom%jsc .OR. self%jind > self%geom%jec) then
131  ! outside of the grid
132  call abor1_ftn('soca_geom_iter_current: iterator out of bounds')
133  else
134  ! inside of the grid
135  lat = self%geom%lat(self%iind,self%jind)
136  lon = self%geom%lon(self%iind,self%jind)
137  endif
138 
139 end subroutine soca_geom_iter_current
140 
141 
142 ! ------------------------------------------------------------------------------
143 !> Update geometry iterator to next point
144 !!
145 !! \todo skip over masked points
146 !! \relates soca_geom_iter_mod::soca_geom_iter
147 subroutine soca_geom_iter_next(self)
148  class(soca_geom_iter), intent(inout) :: self
149  integer :: iind, jind
150 
151  iind = self%iind
152  jind = self%jind
153 
154  ! do while ((iind.lt.self%geom%iec).and.(jind.lt.self%geom%jec))
155 
156  ! increment by 1
157  if (iind.lt.self%geom%iec) then
158  iind = iind + 1
159  elseif (iind.eq.self%geom%iec) then
160  iind = self%geom%isc
161  jind = jind + 1
162  end if
163 
164  ! ! skip this point if it is on land
165  ! if (self%geom%mask2d(iind,jind).lt.1) then
166  ! cycle
167  ! else
168  ! exit
169  ! endif
170 
171  ! end do
172 
173  if (jind > self%geom%jec) then
174  iind=-1
175  jind=-1
176  end if
177 
178  self%iind = iind
179  self%jind = jind
180 
181 end subroutine soca_geom_iter_next
182 ! ------------------------------------------------------------------------------
183 
184 end module soca_geom_iter_mod
Geometry iterator.
Geometry module.
Geometry data structure.