source: CPL/oasis3-mct/branches/OASIS3-MCT_5.0_branch/lib/mct/testsystem/testall/m_AVTEST.F90 @ 6331

Last change on this file since 6331 was 6331, checked in by aclsce, 17 months ago

Moved oasis-mct_5.0 in oasis3-mct/branches directory.

File size: 26.8 KB
Line 
1!
2! !INTERFACE:
3
4 module m_AVTEST
5!
6! !USES:
7!
8      implicit none
9
10      private   ! except
11
12! !PUBLIC MEMBER FUNCTIONS:
13
14      public :: testall
15      public :: IndexAttr
16      public :: SortPermute
17      public :: Copy
18      public :: ImportExport
19      public :: Reduce
20      public :: Identical
21
22    interface testall
23       module procedure testaV_
24    end interface
25    interface IndexAttr
26       module procedure IndexTest_
27    end interface
28    interface SortPermute
29       module procedure SortPermuteTest_
30    end interface
31    interface Copy
32       module procedure CopyTest_
33    end interface
34    interface ImportExport
35       module procedure ImportExportTest_
36    end interface
37    interface Reduce
38       module procedure ReduceTest_
39    end interface
40    interface Identical
41       module procedure Identical_
42    end interface
43
44! !REVISION HISTORY:
45!EOP ___________________________________________________________________
46
47  character(len=*),parameter :: myname='m_AVTest'
48
49 contains
50
51!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
52!    Math and Computer Science Division, Argonne National Laboratory   !
53!BOP -------------------------------------------------------------------
54!
55! !IROUTINE: aVtest_ - Test the functions in the AttrVect module
56!
57! !DESCRIPTION:
58! This routine writes diagnostic information about the input
59! {\tt AttrVect}. Each line of the output will be preceded by the
60! character argument {\tt identifier}. The output device is specified
61! by the integer argument {\tt device}.
62!
63! !INTERFACE:
64
65 subroutine testaV_(aV, identifier, device)
66
67!
68! !USES:
69!
70      use m_AttrVect         ! Use all AttrVect routines
71      use m_stdio
72      use m_die
73
74      implicit none
75
76! !INPUT PARAMETERS:
77
78      type(AttrVect),             intent(in)  :: aV
79      character(len=*),           intent(in)  :: identifier
80      integer,                    intent(in)  :: device
81
82! !REVISION HISTORY:
83! 23Sep02 - E.T. Ong <eong@mcs.anl.gov> - initial prototype.
84!EOP ___________________________________________________________________
85
86  character(len=*),parameter :: myname_=myname//'::aVtest_'
87  type(AttrVect) :: aVExactCopy
88
89!::::MAKE A COPY::::!
90
91  call init(aVExactCopy,aV,lsize(aV))
92  call Copy(aVin=aV,aVout=aVExactCopy)
93
94!:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
95!:::::WRITE OUT INFO ABOUT THE ATTRVECT:::::::::::::::::::::::::::::::::
96!:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
97
98  write(device,*) identifier, ":: lsize = ", lsize(aV)
99  write(device,*) identifier, ":: nIAttr = ", nIAttr(aV)
100  write(device,*) identifier, ":: nRAttr = ", nRAttr(aV)
101
102  if(nIAttr(aV)>0) then
103     write(device,*) identifier, ":: exportIListToChar = ", &
104                                      exportIListToChar(aV)
105  endif
106
107  if(nRAttr(aV)>0) then
108     write(device,*) identifier, ":: exportRListToChar = ", &
109                                      exportRListToChar(aV)
110  endif
111
112!:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
113!:::::TESTING INDEXIA AND GETILIST::::::::::::::::::::::::::::::::::::::
114!:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
115
116  call IndexTest_(aV,identifier,device)
117
118
119!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
120!:::::TESTING SORT AND PERMUTE:::::::::::::::::::::::::::::::::::::::::!
121!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
122
123! NOTE: THIS IS NOT A CHECK FOR CORRECTNESS, JUST A CHECK FOR CONSISTENCY
124
125  call SortPermuteTest_(aV,identifier,device)
126
127!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
128!:::::TESTING COPY AND SHAREDATTRINDEXLIST:::::::::::::::::::::::::::::!
129!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
130
131  call CopyTest_(aV,identifier,device)
132
133!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
134!:::::TESTING EXPORT AND IMPORT FUNCTIONS::::::::::::::::::::::::::::::::!
135!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
136
137  call ImportExportTest_(aV,identifier,device)
138
139!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
140!:::::TESTING LOCAL REDUCE FUNCTIONS:::::::::::::::::::::::::::::::::::::!
141!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
142
143  call ReduceTest_(aV,identifier,device)
144
145
146  ! Check that aV is unchanged!
147
148  if(.NOT.Identical_(aV,aVExactCopy,1e-5)) then
149     call die(myname_,"aV has been unexpectedly altered!!!")
150  endif
151
152  call clean(aVExactCopy)
153
154end subroutine testaV_
155
156!:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
157!:::::TEST FOR INDEXIA AND GETILIST::::::::::::::::::::::::::::::::::::::
158!:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
159
160  subroutine IndexTest_(aV,identifier,device)
161
162    use m_AttrVect, only: AttrVect, nIattr, nRattr,getIList, getRList,indexIa,indexRA
163    use m_List,   only: List_allocated   => allocated
164    use m_String, only: String
165    use m_String, only: StringToChar     => toChar
166    use m_String, only: String_clean     => clean
167    use m_stdio
168    use m_die
169
170    implicit none
171
172    type(AttrVect),             intent(in)  :: aV
173    character(len=*),           intent(in)  :: identifier
174    integer,                    intent(in)  :: device
175
176    character(len=*),parameter :: myname_=myname//'::IndexTest_'
177    type(String) :: ItemStr
178    integer :: i,j,k,ierr
179
180    if(nIAttr(aV)>0) then
181       write(device,*) identifier, ":: Testing indexIA and getIList::"
182    else
183       if(List_allocated(aV%iList)) then
184          call die(myname_,"iList has been allocated, :&
185               &but there are no atttributes. :&
186               &Please do not initialize a blank list.")
187       end if
188       if(associated(aV%iAttr)) then
189          if(size(aV%iAttr,1) /= 0) then
190             call die(myname_,"iAttr contains no attributes, &
191                  &yet its size /= 0",size(aV%iAttr,1))
192          endif
193       endif
194    end if
195
196    do i=1,nIAttr(aV)
197
198       call getIList(ItemStr,i,aV)
199       j = indexIA(aV,StringToChar(ItemStr))
200       if(i/=j) call die(myname_,"Function indexIA failed!")
201       write(device,*) identifier, &
202            ":: aV Index = ", j,      &
203            ":: Attribute Name = ", StringToChar(ItemStr)
204       call String_clean(ItemStr)
205
206    enddo
207
208    if(nRAttr(aV)>0) then
209       write(device,*) identifier, ":: Testing indexRA and getRList::"
210    else
211       if(List_allocated(aV%rList)) then
212          call die(myname_,"rList has been allocated, :&
213               &but there are no atttributes. :&
214               &Please do not initialize a blank list.")
215       end if
216       if(associated(aV%rAttr)) then
217          if(size(aV%rAttr,1) /= 0) then
218             call die(myname_,"rAttr contains no attributes, &
219                  &yet its size /= 0",size(aV%rAttr,1))
220          endif
221       endif
222    end if
223
224    do i=1,nRAttr(aV)
225
226       call getRList(ItemStr,i,aV)
227       j = indexRA(aV,StringToChar(ItemStr))
228       if(i/=j) call die(myname_,"Function indexIA failed!")
229       write(device,*) identifier,   &
230            "::aV Index = ", j,      &
231            "::Attribute Name = ", StringToChar(ItemStr)
232       call String_clean(ItemStr)
233
234    enddo
235
236  end subroutine IndexTest_
237
238!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
239!:::::TEST FOR SORT AND PERMUTE:::::::::::::::::::::::::::::::::::::::::!
240!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
241
242! NOTE: THIS IS NOT A CHECK FOR CORRECTNESS, JUST A CHECK FOR CONSISTENCY
243
244  subroutine SortPermuteTest_(aV,identifier,device)
245
246    use m_AttrVect
247    use m_stdio
248    use m_die
249
250    implicit none
251
252    type(AttrVect),             intent(in)  :: aV
253    character(len=*),           intent(in)  :: identifier
254    integer,                    intent(in)  :: device
255
256    character(len=*),parameter :: myname_=myname//'::SortPermuteTest_'
257    type(AttrVect) :: AVCOPY1, AVCOPY2
258    logical,dimension(:), pointer :: descend
259    integer,dimension(:), pointer :: perm
260    integer :: i,j,k,ierr
261    real :: r
262
263    write(device,*) identifier, ":: Testing Sort and Permute"
264
265    call init(aV=AVCOPY1,bV=aV,lsize=100)
266    call init(av=AVCOPY2,bV=aV,lsize=100)
267
268    if( (nIAttr(AVCOPY1)>0) .or. (nRAttr(AVCOPY1)>0) ) then
269
270    if(nIAttr(AVCOPY1)>0) then
271
272       allocate(descend(nIAttr(AVCOPY1)),stat=ierr)
273       if(ierr /= 0) call die(myname_,"allocate(descend)")
274
275       call zero(AVCOPY1)
276       call zero(AVCOPY2)
277
278       k=0
279       do i=1,nIAttr(AVCOPY1)
280          do j=1,lsize(AVCOPY1)
281             k=k+1
282             AVCOPY1%iAttr(i,j) = k
283             AVCOPY2%iAttr(i,j) = k
284          enddo
285       enddo
286
287       descend=.true.
288       call Sort(aV=AVCOPY1,key_list=AVCOPY1%iList,perm=perm,descend=descend)
289       call Permute(aV=AVCOPY1,perm=perm)
290
291       call SortPermute(aV=AVCOPY2,key_list=AVCOPY2%iList,descend=descend)
292
293       do i=1,nIAttr(AVCOPY1)
294          do j=1,lsize(AVCOPY1)
295             if(AVCOPY1%iAttr(i,j) /= AVCOPY2%iAttr(i,j)) then
296                call die(myname_,"Sort Testing FAILED!")
297             endif
298          enddo
299       enddo
300
301       write(device,*) identifier, ":: INTEGER AV IN DESCENDING ORDER:: ", &
302            AVCOPY1%iAttr(1,1:5)
303
304       deallocate(perm,stat=ierr)
305       if(ierr /= 0) call die(myname_,"deallocate(perm)")
306
307       deallocate(descend,stat=ierr)
308       if(ierr /= 0) call die(myname_,"deallocate(descend)")
309
310    endif
311
312    if(nRAttr(AVCOPY1)>0) then
313
314       allocate(descend(nRAttr(AVCOPY1)),stat=ierr)
315       if(ierr /= 0) call die(myname_,"allocate(descend)")
316
317       call zero(AVCOPY1)
318       call zero(AVCOPY2)
319
320       r=0.
321       do i=1,nRAttr(AVCOPY1)
322          do j=1,lsize(AVCOPY1)
323             r=r+1.29
324             AVCOPY1%rAttr(i,j) = r
325             AVCOPY2%rAttr(i,j) = r
326          enddo
327       enddo
328
329       descend=.true.
330       call Sort(aV=AVCOPY1,key_list=AVCOPY1%rList,perm=perm,descend=descend)
331       call Permute(aV=AVCOPY1,perm=perm)
332
333       call SortPermute(aV=AVCOPY2,key_list=AVCOPY2%rList,descend=descend)
334
335       do i=1,nRAttr(AVCOPY1)
336          do j=1,lsize(AVCOPY1)
337             if(AVCOPY1%rAttr(i,j) /= AVCOPY2%rAttr(i,j)) then
338                call die(myname_,"Sort Testing FAILED!")
339             endif
340          enddo
341       enddo
342
343       write(device,*) identifier, ":: REAL AV IN DESCENDING ORDER:: ", &
344            AVCOPY1%rAttr(1,1:5)
345
346       deallocate(perm,stat=ierr)
347       if(ierr /= 0) call die(myname_,"deallocate(perm)")
348
349       deallocate(descend,stat=ierr)
350       if(ierr /= 0) call die(myname_,"deallocate(descend)")
351
352    endif
353    else
354    write(device,*) identifier, ":: NOT TESTING SORTING AND PERMUTING. CONSULT &
355         &SOURCE CODE TO ENABLE TESTING."
356    endif
357
358    call clean(AVCOPY1)
359    call clean(AVCOPY2)
360
361  end subroutine SortPermuteTest_
362
363!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
364!:::::TEST FOR COPY AND SHAREDATTRINDEXLIST:::::::::::::::::::::::::::::!
365!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
366
367! NOTE: SO FOR ONLY TESTING SHAREDATTRINDEX for reals
368
369  subroutine CopyTest_(aV,identifier,device)
370
371    use m_AttrVect
372    use m_List,     only   : List
373    use m_List,     only   : List_init        => init
374    use m_List,     only   : List_copy        => copy
375    use m_List,     only   : List_append      => append
376    use m_List,     only   : ListexportToChar => exportToChar
377    use m_List,     only   : List_clean       => clean
378    use m_String,   only   : String
379    use m_String,   only   : StringToChar     => toChar
380    use m_String,   only   : String_clean     => clean
381    use m_stdio
382    use m_die
383
384    implicit none
385
386    type(AttrVect),             intent(in)  :: aV
387    character(len=*),           intent(in)  :: identifier
388    integer,                    intent(in)  :: device
389
390    character(len=*),parameter :: myname_=myname//'::CopyTest_'
391    type(String) :: ItemStr1, ItemStr2
392    type(List) :: OneIList, HalfIList, FullIList
393    type(List) :: OneRList, HalfRList, FullRList
394    type(AttrVect) :: aVExactCopy, aVPartialCopy, aVOtherCopy
395    type(AttrVect) :: HalfAV
396    integer,dimension(:), pointer :: Indices1, Indices2
397    integer :: NumShared
398    integer :: i,j,k,ierr
399
400    if( (nIAttr(aV)>0) .and. (nRAttr(aV)>0) ) then
401
402       !:::INITIALIZE LISTS FOR USE IN COPY TESTS:::!
403       do i=1,nIAttr(aV)
404
405          call getIList(ItemStr1,i,aV)
406
407          if(i==1) then
408             call List_init(HalfIList,ItemStr1)
409             call List_init(FullIList,ItemStr1)
410          else
411             if(mod(i,2) == 0) then ! if EVEN
412                call List_init(OneIList,'REPLACE_'//ACHAR(64+i))
413                call List_append(FullIList,OneIList)
414                call List_clean(OneIList)
415             else                   ! if ODD
416                call List_init(OneIList,ItemStr1)
417                call List_append(HalfIList,OneIList)
418                call List_append(FullIList,OneIList)
419                call List_clean(OneIList)
420             endif
421          endif
422
423          call String_clean(ItemStr1)
424
425       enddo
426
427       do i=1,nRAttr(aV)
428
429          call getRList(ItemStr1,i,aV)
430
431          if(i==1) then
432             call List_init(OneRList,'REPLACE_'//ACHAR(64+i))
433             call List_copy(FullRList,OneRList)
434             call List_clean(OneRList)
435          else
436             if(mod(i,2) == 0) then ! IF EVEN
437                call List_init(OneRList,ItemStr1)
438                if(i==2) then
439                   call List_init(HalfRList,ItemStr1)
440                else
441                   call List_append(HalfRList,OneRList)
442                endif
443                call List_append(FullRList,OneRList)
444                call List_clean(OneRList)
445             else                   ! IF ODD
446                call List_init(OneRList,'REPLACE_'//ACHAR(64+i))
447                call List_append(FullRList,OneRList)
448                call List_clean(OneRList)
449             endif
450          endif
451
452          call String_clean(ItemStr1)
453
454       enddo
455
456       write(device,*) identifier, ":: Testing Copy and SharedAttrIndexList ::"
457       write(device,*) identifier, ":: FIRST AV ATTRIBUTES::", &
458            "IATTR = ", exportIListToChar(aV), &
459            " RATTR = ", exportRListToChar(aV)
460       call init(aVExactCopy,aV,lsize(aV))
461       write(device,*) identifier, ":: SECOND AV ATTRIBUTES::", &
462            "IATTR = ", exportIListToChar(aVExactCopy), &
463            " RATTR = ", exportRListToChar(aVExactCopy)
464       call zero(aVExactCopy)
465       call copy(aVin=aV, aVout=aVExactCopy)
466       !     call copy(aVin=aV,rList=exportRListToChar(aV), &
467       !          iList=exportIListToChar(aV),aVout=aVExactCopy)
468       call SharedAttrIndexList(aV,aVExactCopy,"REAL   ", &
469            NumShared,Indices1,Indices2)
470       write(device,*) identifier, ":: Indices1 :: Indices2 :: &
471            &Attribute1 :: Attribute2"
472       do i=1,NumShared
473          call getRList(ItemStr1,Indices1(i),aV)
474          call getRList(ItemStr2,Indices2(i),aVExactCopy)
475          write(device,*) identifier,":: ", Indices1(i), "::", Indices2(i), &
476               "::", StringToChar(ItemStr1), "::", StringToChar(ItemStr2)
477          call String_clean(ItemStr1)
478          call String_clean(ItemStr2)
479       enddo
480
481       do i=1,NumShared
482          do j=1,lsize(aV)
483             if(aV%rAttr(Indices1(i),j) /= &
484                  aVExactCopy%rAttr(Indices2(i),j)) then
485                call die(myname_,"Copy function is MALFUNCTIONING", ierr)
486             endif
487          enddo
488       enddo
489
490       deallocate(Indices1,Indices2,stat=ierr)
491       if(ierr/=0) call die(myname_,"deallocate(Indices1,Indices2)",ierr)
492
493!:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
494
495       call init(aVPartialCopy,aV,lsize(aV))
496       write(device,*) identifier, ":: FIRST AV ATTRIBUTES::", &
497            "IATTR = ", exportIListToChar(aVPartialCopy), &
498            " RATTR = ", exportRListToChar(aVPartialCopy)
499       call zero(aVPartialCopy)
500       call copy(aVin=aV,rList=ListexportToChar(HalfRList), &
501            iList=ListexportToChar(HalfIList),aVout=aVPartialCopy)
502       call init(aV=HalfAV,iList=HalfIList,rList=HalfRList,lsize=1)
503       write(device,*) identifier, ":: SECOND AV ATTRIBUTES::", &
504            "IATTR = ", exportIListToChar(HalfAV), &
505            " RATTR = ", exportRListToChar(HalfAV)
506       call SharedAttrIndexList(aV,HalfAV,"REAL   ", &
507            NumShared,Indices1,Indices2)
508       write(device,*) identifier, ":: Indices1 :: Indices2 :: &
509            &Attribute1 :: Attribute2"
510       do i=1,NumShared
511          call getRList(ItemStr1,Indices1(i),aV)
512          call getRList(ItemStr2,Indices2(i),HalfAV)
513          write(device,*) identifier,":: ", Indices1(i), "::", Indices2(i), &
514               "::", StringToChar(ItemStr1), "::", StringToChar(ItemStr2)
515          call String_clean(ItemStr1)
516          call String_clean(ItemStr2)
517       enddo
518
519       do i=1,NumShared
520          do j=1,lsize(aV)
521             if(aV%rAttr(Indices1(i),j) /= &
522                  aVPartialCopy%rAttr(Indices1(i),j)) then
523                call die(myname_,"Copy function is MALFUNCTIONING", ierr)
524             endif
525          enddo
526       enddo
527
528       call List_clean(HalfIList)
529       call List_clean(HalfRList)
530
531       deallocate(Indices1,Indices2,stat=ierr)
532       if(ierr/=0) call die(myname_,"deallocate(Indices1,Indices2)",ierr)
533
534!:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
535
536       call init(aVOtherCopy,FullIList,FullRList,lsize(aV))
537       write(device,*) identifier, ":: FIRST AV ATTRIBUTES::", &
538            "IATTR = ", exportIListToChar(aV), &
539            " RATTR = ", exportRListToChar(aV)
540       write(device,*) identifier, ":: SECOND AV ATTRIBUTES::", &
541            "IATTR = ", exportIListToChar(aVOtherCopy), &
542            " RATTR = ", exportRListToChar(aVOtherCopy)
543       call zero(aVOtherCopy)
544       call copy(aV,rList=exportRListToChar(aV), &
545            TrList=ListexportToChar(FullRList), &
546            iList=exportIListToChar(aV), &
547            TiList=ListexportToChar(FullIList), &
548            aVout=aVOtherCopy)
549       call SharedAttrIndexList(aV,aVOtherCopy,"REAL", &
550            NumShared,Indices1,Indices2)
551       write(device,*) identifier, ":: Indices1 :: Indices2 :: &
552            &Attribute1 :: Attribute2"
553       do i=1,NumShared
554          call getRList(ItemStr1,Indices1(i),aV)
555          call getRList(ItemStr2,Indices2(i),aVOtherCopy)
556          write(device,*) identifier,":: ", Indices1(i), "::", Indices2(i), &
557               "::", StringToChar(ItemStr1), "::", StringToChar(ItemStr2)
558          call String_clean(ItemStr1)
559          call String_clean(ItemStr2)
560       enddo
561
562       do i=1,NumShared
563          do j=1,lsize(aV)
564             if(aV%rAttr(Indices1(i),j) /= &
565                  aVOtherCopy%rAttr(Indices2(i),j)) then
566                write(device,*) identifier,Indices1(i),Indices2(i), j
567                call die(myname_,"Copy function is MALFUNCTIONING", ierr)
568             endif
569          enddo
570       enddo
571
572       call List_clean(FullIList)
573       call List_clean(FullRList)
574
575       deallocate(Indices1,Indices2,stat=ierr)
576       if(ierr/=0) call die(myname_,"deallocate(Indices1,Indices2)",ierr)
577
578       call clean(aVExactCopy)
579       call clean(aVPartialCopy)
580       call clean(aVOtherCopy)
581       call clean(HalfAV)
582
583    else
584
585       write(device,*) identifier, &
586            ":: NOT Testing Copy and SharedAttrIndexList ::", &
587            ":: Consult m_MCTTest.F90 to enable this function::"
588    endif
589
590  end subroutine CopyTest_
591
592!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
593!:::::TEST FOR EXPORT AND IMPORT FUNCTIONS:::::::::::::::::::::::::::::::!
594!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
595
596  subroutine ImportExportTest_(aV,identifier,device)
597
598    use m_AttrVect
599    use m_List,     only   : List
600    use m_List,     only   : List_identical   => identical
601    use m_List,     only   : List_get         => get
602    use m_List,     only   : List_clean       => clean
603    use m_String,   only   : String
604    use m_String,   only   : StringToChar     => toChar
605    use m_String,   only   : String_clean     => clean
606    use m_stdio
607    use m_die
608
609    use m_realkinds, only : FP
610
611    implicit none
612
613    type(AttrVect),             intent(in)  :: aV
614    character(len=*),           intent(in)  :: identifier
615    integer,                    intent(in)  :: device
616
617    character(len=*),parameter :: myname_=myname//'::ImportExportTest_'
618    type(AttrVect) :: importAV
619    type(List) :: OutIList, OutRList
620    type(String) :: ItemStr
621    integer,dimension(:),pointer :: OutIVect
622    real(FP), dimension(:),pointer :: OutRVect
623    integer :: exportsize
624    integer :: i,j,k,ierr
625
626    write(device,*) identifier, ":: Testing import and export functions"
627
628    if(nIAttr(aV)>0) then
629
630       call exportIList(aV=aV,outIList=outIList)
631
632       if(.NOT. List_identical(aV%iList,outIList)) then
633          call die(myname_, "Function exportIList failed!")
634       endif
635
636       call List_get(ItemStr=ItemStr,ith=nIAttr(aV),aList=aV%iList)
637
638       allocate(outIVect(lsize(aV)),stat=ierr)
639       if(ierr/=0) call die(myname_,"allocate(outIVect)")
640
641       call exportIAttr(aV=aV,AttrTag=StringToChar(ItemStr), &
642            outVect=OutIVect,lsize=exportsize)
643
644       if(exportsize /= lsize(aV)) then
645          call die(myname_,"(exportsize /= lsize(aV))")
646       endif
647
648       do i=1,exportsize
649          if(aV%iAttr(nIAttr(aV),i) /= outIVect(i)) then
650             call die(myname_,"Function exportIAttr failed!")
651          endif
652       enddo
653
654       call init(aV=importAV,iList=exportIListToChar(aV),lsize=exportsize)
655       call zero(importAV)
656
657       call importIAttr(aV=importAV,AttrTag=StringToChar(ItemStr), &
658            inVect=outIVect,lsize=exportsize)
659
660       j=indexIA(importAV,StringToChar(ItemStr))
661       if(j<=0) call die(myname_,"indexIA(importAV,StringToChar(ItemStr))")
662       do i=1,exportsize
663          if(importAV%iAttr(j,i) /= outIVect(i)) then
664             call die(myname_,"Function importIAttr failed!")
665          endif
666       enddo
667
668       call clean(importAV)
669       call List_clean(outIList)
670       call String_clean(ItemStr)
671
672       deallocate(outIVect,stat=ierr)
673       if(ierr/=0) call die(myname_,"deallocate(outIVect)")
674
675    endif
676
677    if(nRAttr(aV)>0) then
678
679       call exportRList(aV=aV,outRList=outRList)
680
681       if(.NOT. List_identical(aV%rList,outRList)) then
682          call die(myname_, "Function exportRList failed!")
683       endif
684
685       call List_get(ItemStr=ItemStr,ith=nRAttr(aV),aList=aV%rList)
686
687       allocate(outRVect(lsize(aV)),stat=ierr)
688       if(ierr/=0) call die(myname_,"allocate(outRVect)")
689
690       call exportRAttr(aV=aV,AttrTag=StringToChar(ItemStr), &
691            outVect=OutRVect,lsize=exportsize)
692
693       if(exportsize /= lsize(aV)) then
694          call die(myname_,"(exportsize /= lsize(aV))")
695       endif
696
697       do i=1,exportsize
698          if(aV%rAttr(nRAttr(aV),i) /= outRVect(i)) then
699             call die(myname_,"Function exportRAttr failed!")
700          endif
701       enddo
702
703       call init(aV=importAV,rList=exportRListToChar(aV),lsize=exportsize)
704       call zero(importAV)
705
706       call importRAttr(aV=importAV,AttrTag=StringToChar(ItemStr), &
707            inVect=outRVect,lsize=exportsize)
708
709       j=indexRA(importAV,StringToChar(ItemStr))
710       if(j<=0) call die(myname_,"indexRA(importAV,StringToChar(ItemStr))")
711       do i=1,exportsize
712          if(importAV%rAttr(j,i) /= outRVect(i)) then
713             call die(myname_,"Function importRAttr failed!")
714          endif
715       enddo
716
717       call clean(importAV)
718       call List_clean(outRList)
719       call String_clean(ItemStr)
720
721       deallocate(outRVect,stat=ierr)
722       if(ierr/=0) call die(myname_,"deallocate(outRVect)")
723
724    endif
725
726  end subroutine ImportExportTest_
727
728  subroutine ReduceTest_(aV,identifier,device)
729
730    use m_AttrVectReduce
731    use m_AttrVect
732    use m_List, only : ListExportToChar => ExportToChar
733    use m_stdio
734    use m_die
735
736    implicit none
737
738    type(AttrVect),             intent(in)  :: aV
739    character(len=*),           intent(in)  :: identifier
740    integer,                    intent(in)  :: device
741
742    character(len=*),parameter :: myname_=myname//'::ReduceTest_'
743    integer :: i,j,k,ierr
744    type(AttrVect) :: reducedAVsum, reducedAVmin, reducedAVmax
745    type(AttrVect) :: reducedAVRsum, reducedAVRmin, reducedAVRmax
746
747    if( (nIAttr(aV)==0).and.(nRAttr(aV)>0) ) then
748
749       call LocalReduce(aV,reducedAVsum,AttrVectSUM)
750       call LocalReduce(aV,reducedAVmin,AttrVectMIN)
751       call LocalReduce(aV,reducedAVmax,AttrVectMAX)
752
753       call LocalReduceRAttr(aV,reducedAVRsum,AttrVectSUM)
754       call LocalReduceRAttr(aV,reducedAVRmin,AttrVectMIN)
755       call LocalReduceRAttr(aV,reducedAVRmax,AttrVectMAX)
756
757       if(.NOT.Identical_(reducedAVsum,reducedAVRsum,1e-4)) then
758          call die(myname_,"LocalReduce -SUM- functions produced inconsistent &
759               &results!")
760       endif
761
762       if(.NOT.Identical_(reducedAVmin,reducedAVRmin,1e-4)) then
763          call die(myname_,"LocalReduce -MIN- functions produced inconsistent &
764               &results!")
765       endif
766
767       if(.NOT.Identical_(reducedAVmax,reducedAVRmax,1e-4)) then
768          call die(myname_,"LocalReduce -MAX- functions produced inconsistent &
769               &results!")
770       endif
771
772       write(device,*) identifier,":: RESULTS OF ATTRVECT LOCAL REDUCE :: &
773            &(Name, rList, Values)"
774       write(device,*) identifier,":: REDUCEDAVSUM = ", &
775            ListExportToChar(reducedAVsum%rList), &
776            reducedAVsum%rAttr
777       write(device,*) identifier,":: REDUCEDAVMIN = ", &
778            ListExportToChar(reducedAVmin%rList), &
779            reducedAVmin%rAttr
780       write(device,*) identifier,":: REDUCEDAVMAX = ", &
781            ListExportToChar(reducedAVmax%rList), &
782            reducedAVmax%rAttr
783
784       call clean(reducedAVsum)
785       call clean(reducedAVmin)
786       call clean(reducedAVmax)
787       call clean(reducedAVRsum)
788       call clean(reducedAVRmin)
789       call clean(reducedAVRmax)
790
791    else
792
793       write(device,*) identifier,":: NOT TESTING LOCAL REDUCE. &
794            &PLEASE CONSULT SOURCE CODE."
795
796    endif
797
798  end subroutine ReduceTest_
799
800  logical function Identical_(aV1,aV2,Range)
801
802    use m_AttrVect
803    use m_stdio
804    use m_die
805
806    use m_realkinds, only : FP
807
808    implicit none
809
810    type(AttrVect), intent(in) :: aV1
811    type(AttrVect), intent(in) :: aV2
812    real, optional, intent(in) :: Range
813
814    integer :: i,j,k,AVSize
815
816    Identical_=.true.
817
818    AVSize = lsize(aV1)
819
820    if(lsize(aV1) /= lsize(aV2)) then
821       AVSize=0
822       Identical_=.false.
823    endif
824
825    do i=1,AVSize
826       do j=1,nIAttr(aV1)
827          if(AV1%iAttr(j,i) /= AV2%iAttr(j,i)) then
828             Identical_=.false.
829          endif
830       enddo
831    enddo
832
833    if(present(Range)) then
834
835       do i=1,AVSize
836          do j=1,nRAttr(aV1)
837             if( ABS(AV1%rAttr(j,i)-AV2%rAttr(j,i)) > Range ) then
838                Identical_=.false.
839             endif
840          enddo
841       enddo
842
843    else
844
845       do i=1,AVSize
846          do j=1,nRAttr(aV1)
847             if(AV1%rAttr(j,i) /= AV2%rAttr(j,i)) then
848                Identical_=.false.
849             endif
850          enddo
851       enddo
852
853    endif
854
855  end function Identical_
856
857end module m_AVTEST
Note: See TracBrowser for help on using the repository browser.