source: CPL/oasis3-mct/branches/OASIS3-MCT_2.0_branch/lib/mct/mpeu/m_IndexBin_char.F90 @ 4775

Last change on this file since 4775 was 4775, checked in by aclsce, 5 years ago
  • Imported oasis3-mct from Cerfacs svn server (not suppotred anymore).

The version has been extracted from https://oasis3mct.cerfacs.fr/svn/branches/OASIS3-MCT_2.0_branch/oasis3-mct@1818

File size: 6.9 KB
Line 
1!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2!       NASA/GSFC, Data Assimilation Office, Code 910.3, GEOS/DAS      !
3!-----------------------------------------------------------------------
4! CVS m_IndexBin_char.F90,v 1.3 2004-04-21 22:54:44 jacob Exp
5! CVS MCT_2_8_0 
6!BOP -------------------------------------------------------------------
7!
8! !MODULE: m_IndexBin_char - Template of indexed bin-sorting module
9!
10! !DESCRIPTION:
11!
12! !INTERFACE:
13
14    module m_IndexBin_char
15      implicit none
16      private   ! except
17
18      public :: IndexBin
19      interface IndexBin; module procedure      &
20        IndexBin0_,     &
21        IndexBin1_,     &
22        IndexBin1w_
23      end interface
24
25! !REVISION HISTORY:
26!       17Feb99 - Jing Guo <guo@thunder> - initial prototype/prolog/code
27!EOP ___________________________________________________________________
28
29  character(len=*),parameter :: myname='MCT(MPEU)::m_IndexBin_char'
30
31contains
32!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
33!       NASA/GSFC, Data Assimilation Office, Code 910.3, GEOS/DAS      !
34!BOP -------------------------------------------------------------------
35!
36! !IROUTINE: IndexBin0_ - Indexed sorting for a single value
37!
38! !DESCRIPTION:
39!
40! !INTERFACE:
41
42    subroutine IndexBin0_(n,indx,keys,key0,ln0)
43      use m_stdio, only : stderr
44      use m_die,   only : die
45      implicit none
46
47      integer, intent(in) :: n
48      integer, dimension(n), intent(inout) :: indx
49      character(len=*), dimension(n), intent(in) :: keys
50      character(len=*), intent(in) :: key0 ! value
51      integer,optional,intent(out) :: ln0
52
53! !REVISION HISTORY:
54!       16Feb99 - Jing Guo <guo@thunder> - initial prototype/prolog/code
55!       27Sep99 - Jing Guo <guo@thunder> - Fixed a bug pointed out by
56!                                          Chris Redder
57!EOP ___________________________________________________________________
58
59  character(len=*),parameter :: myname_=myname//'::IndexBin0_'
60  integer,allocatable,dimension(:) :: inew
61  integer :: ni,ix,i,ier
62  integer :: ln(0:1),lc(0:1)
63!________________________________________
64
65        allocate(inew(n),stat=ier)
66                if(ier /= 0) then
67                  write(stderr,'(2a,i4)') myname_,      &
68                        ': allocate() error, stat =',ier
69                  call die(myname_)
70                endif
71!________________________________________
72                ! Count numbers entries for the given key0
73       
74  lc(0)=1       ! the location of values the same as key0
75  ln(0)=0
76  do i=1,n
77    if(keys(i) == key0) ln(0)=ln(0)+1
78  end do
79
80  lc(1)=ln(0)+1 ! the location of values not the same as key0
81!________________________________________
82                ! Reset the counters
83  ln(0:1)=0
84  do i=1,n
85    ix=indx(i)
86    if(keys(ix) == key0) then
87      ni=lc(0)+ln(0)
88      ln(0)=ln(0)+1
89     
90    else
91      ni=lc(1)+ln(1)
92      ln(1)=ln(1)+1
93    endif
94
95    inew(ni)=ix
96  end do
97
98!________________________________________
99                ! Sort out the old pointers according to the new order
100  indx(:)=inew(:)
101  if(present(ln0)) ln0=ln(0)
102!________________________________________
103
104          deallocate(inew)
105
106end subroutine IndexBin0_
107
108!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
109!       NASA/GSFC, Data Assimilation Office, Code 910.3, GEOS/DAS      !
110!BOP -------------------------------------------------------------------
111!
112! !IROUTINE: IndexBin1_ - Indexed sorting into a set of given bins
113!
114! !DESCRIPTION:
115!
116! !INTERFACE:
117
118    subroutine IndexBin1_(n,indx,keys,bins,lcs,lns)
119      use m_stdio, only : stderr
120      use m_die,   only : die
121      implicit none
122
123      integer, intent(in) :: n
124      integer, dimension(n),intent(inout) :: indx
125      character(len=*),dimension(n),intent(in) :: keys
126      character(len=*),dimension(:),intent(in) :: bins ! values
127      integer, dimension(:),intent(out)   :: lcs ! locs. of the bins
128      integer, dimension(:),intent(out)   :: lns ! sizes of the bins
129
130! !REVISION HISTORY:
131!       16Feb99 - Jing Guo <guo@thunder> - initial prototype/prolog/code
132!EOP ___________________________________________________________________
133
134  character(len=*),parameter :: myname_=myname//'::IndexBin1_'
135  integer,allocatable,dimension(:) :: ibin,inew
136  integer :: nbin,lc0,ln0
137  integer :: ni,ix,ib,i,ier
138!________________________________________
139
140  nbin=size(bins)
141  if(nbin==0) return
142!________________________________________
143
144        allocate(ibin(n),inew(n),stat=ier)
145                if(ier /= 0) then
146                  write(stderr,'(2a,i4)') myname_,      &
147                        ': allocate() error, stat =',ier
148                  call die(myname_)
149                endif
150!________________________________________
151
152  do ib=1,nbin
153    lns(ib)=0
154    lcs(ib)=0
155  end do
156!________________________________________
157                ! Count numbers in every bin, and store the bin-ID for
158                ! later use.
159  do i=1,n
160    ix=indx(i)
161
162    call search_(keys(ix),nbin,bins,ib) ! ib = 1:nbin; =0 if not found
163
164    ibin(i)=ib
165    if(ib /= 0) lns(ib)=lns(ib)+1
166  end do
167!________________________________________
168                ! Count the locations of every bin.
169  lc0=1
170  do ib=1,nbin
171    lcs(ib)=lc0
172    lc0=lc0+lns(ib)
173  end do
174!________________________________________
175                ! Reset the counters
176  ln0=0
177  lns(1:nbin)=0
178  do i=1,n
179    ib=ibin(i)  ! the bin-index of keys(indx(i))
180    if(ib/=0) then
181      ni=lcs(ib)+lns(ib)
182      lns(ib)=lns(ib)+1
183    else
184      ni=lc0+ln0
185      ln0=ln0+1
186    endif
187    inew(ni)=indx(i)    ! the current value is put in the new order
188  end do
189!________________________________________
190                ! Sort out the old pointers according to the new order
191  indx(:)=inew(:)
192!________________________________________
193
194          deallocate(ibin,inew)
195
196contains
197subroutine search_(key,nbin,bins,ib)
198  implicit none
199  character(len=*), intent(in) :: key
200  integer,intent(in) :: nbin
201  character(len=*), intent(in),dimension(:) :: bins
202  integer,intent(out) :: ib
203  integer :: i
204
205  ib=0
206  do i=1,nbin
207    if(key==bins(i)) then
208      ib=i
209      return
210    endif
211  end do
212end subroutine search_
213
214end subroutine IndexBin1_
215!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
216!       NASA/GSFC, Data Assimilation Office, Code 910.3, GEOS/DAS      !
217!BOP -------------------------------------------------------------------
218!
219! !IROUTINE: IndexBin1w_ - IndexBin1_ wrapped without working arrays
220!
221! !DESCRIPTION:
222!
223! !INTERFACE:
224
225    subroutine IndexBin1w_(n,indx,keys,bins)
226      use m_stdio, only : stderr
227      use m_die,   only : die
228      implicit none
229
230      integer,             intent(in)    :: n
231      integer,dimension(n),intent(inout) :: indx
232      character(len=*),dimension(n),intent(in)    :: keys
233      character(len=*),dimension(:),intent(in)    :: bins ! values
234
235! !REVISION HISTORY:
236!       17Feb99 - Jing Guo <guo@thunder> - initial prototype/prolog/code
237!EOP ___________________________________________________________________
238
239  character(len=*),parameter :: myname_=myname//'::IndexBin1w_'
240  integer :: ier
241  integer,dimension(:),allocatable :: lcs,lns
242  integer :: nbin
243
244  nbin=size(bins)
245  if(nbin==0) return
246
247  allocate(lcs(nbin),lns(nbin),stat=ier)
248  if(ier /= 0) then
249    write(stderr,'(2a,i4)') myname_,': allocate() error, stat =',ier
250    call die(myname_)
251  endif
252
253  call IndexBin1_(n,indx,keys,bins,lcs,lns)
254
255  deallocate(lcs,lns)
256end subroutine IndexBin1w_
257end module m_IndexBin_char
Note: See TracBrowser for help on using the repository browser.