source: CPL/oasis3-mct_5.0/lib/mct/testsystem/testall/m_ACTEST.F90 @ 6328

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

First import of oasis3-mct_5.0 (from oasis git server, branch OASIS3-MCT_5.0)

File size: 19.7 KB
Line 
1!
2! !INTERFACE:
3
4 module m_ACTEST
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 :: Copy
17      public :: ImportExport
18      public :: Identical
19
20    interface testall
21       module procedure testaC_
22    end interface
23    interface IndexAttr
24       module procedure IndexTest_
25    end interface
26    interface Copy
27       module procedure CopyTest_
28    end interface
29    interface ImportExport
30       module procedure ImportExportTest_
31    end interface
32    interface Identical
33       module procedure Identical_
34    end interface
35
36
37! !REVISION HISTORY:
38!EOP ___________________________________________________________________
39
40  character(len=*),parameter :: myname='m_ACTEST'
41
42 contains
43
44!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
45!    Math and Computer Science Division, Argonne National Laboratory   !
46!BOP -------------------------------------------------------------------
47!
48! !IROUTINE: aCtest_ - Test the functions in the Accumulator module
49!
50! !DESCRIPTION:
51! This routine writes diagnostic information about the input
52! {\tt Accumulator}. Each line of the output will be preceded by the
53! character argument {\tt identifier}. The output device is specified
54! by the integer argument {\tt device}.
55!
56! !INTERFACE:
57
58 subroutine testaC_(aC, identifier, device)
59
60!
61! !USES:
62!
63
64      use m_Accumulator, only : Accumulator
65      use m_Accumulator, only : accumulate
66      use m_Accumulator, only : MCT_SUM, MCT_AVG
67      use m_Accumulator, only : nIAttr, nRAttr
68      use m_Accumulator, only : lsize
69      use m_Accumulator, only : clean
70      use m_Accumulator, only : Accumulator_init => init
71      use m_AttrVect, only    : AttrVect
72      use m_AttrVect, only    : AttrVect_init => init
73      use m_AttrVect, only    : AttrVect_clean => clean
74      use m_AttrVect, only    : AttrVect_copy => Copy
75      use m_List,     only    : List_allocated => allocated
76      use m_List,     only    : ListExportToChar => exporttoChar
77      use m_stdio
78      use m_die
79
80      implicit none
81
82! !INPUT PARAMETERS:
83
84      type(Accumulator),          intent(in)  :: aC
85      character(len=*),           intent(in)  :: identifier
86      integer,                    intent(in)  :: device
87
88! !REVISION HISTORY:
89! 23Sep02 - E.T. Ong <eong@mcs.anl.gov> - initial prototype.
90!EOP ___________________________________________________________________
91
92  character(len=*),parameter :: myname_=myname//'::aCtest_'
93
94  type(Accumulator) :: aCCopy1, aCCopy2, aCExactCopy
95  type(AttrVect) :: aVDummy
96  integer :: i,j,k
97
98!:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
99!:::::WRITE OUT INFO ABOUT THE ATTRVECT:::::::::::::::::::::::::::::::::
100!:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
101
102  write(device,*) identifier, ":: TYPE CHECK "
103  write(device,*) identifier, ":: NUM_STEPS = ", aC%num_steps
104  write(device,*) identifier, ":: STEPS_DONE = ", aC%steps_done
105
106  if(associated(aC%iAction)) then
107     write(device,*) identifier, ":: IACTION (SIZE,VALUES) = ", &
108          size(aC%iAction), aC%iAction
109  else
110     write(device,*) identifier, ":: IACTION NOT ASSOCIATED"
111  endif
112
113  if(associated(aC%rAction)) then
114     write(device,*) identifier, ":: RACTION (SIZE,VALUES) = ", &
115          size(aC%rAction), aC%rAction
116  else
117     write(device,*) identifier, ":: RACTION NOT ASSOCIATED"
118  endif
119
120  if(List_allocated(aC%data%iList)) then
121     write(device,*) identifier, ":: data%ILIST = ", &
122          ListExportToChar(aC%data%iList)
123  else
124     write(device,*) identifier, ":: data%ILIST NOT INITIALIZED"
125  endif
126
127  if(List_allocated(aC%data%rList)) then
128     write(device,*) identifier, ":: data%RLIST = ", &
129          ListExportToChar(aC%data%rList)
130  else
131     write(device,*) identifier, ":: data%RLIST NOT INITIALIZED"
132  endif
133
134!:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
135!:::::TESTING ACCUMULATION::::::::::::::::::::::::::::::::::::::::::::::
136!:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
137
138  call Accumulator_init(aC=aCExactCopy, bC=aC, lsize=lsize(aC), &
139                        num_steps=aC%num_steps, steps_done=aC%steps_done)
140
141  call AttrVect_copy(aVin=aC%data,aVout=aCExactCopy%data)
142
143  call Accumulator_init(aC=aCCopy1, bC=aC, lsize=100, &
144                        num_steps=aC%num_steps, steps_done=0)
145
146  call Accumulator_init(aC=aCCopy2, bC=aC, lsize=100, &
147                        num_steps=aC%num_steps, steps_done=0)
148
149  call AttrVect_init(aV=aVDummy, bV=aC%data, lsize=100)
150
151  if(nIAttr(aC)>0) then
152     aCCopy1%iAction=MCT_AVG
153     aCCopy2%iAction=MCT_SUM
154     aVDummy%iAttr = 1
155  endif
156
157  if(nRAttr(aC)>0) then
158     aCCopy1%rAction=MCT_AVG
159     aCCopy2%rAction=MCT_SUM
160     aVDummy%rAttr = 1.
161  endif
162
163  do i=1,aC%num_steps
164     call accumulate(aVDummy,ACCopy1)
165     call accumulate(aVDummy,ACCopy2)
166  enddo
167
168  call accumulate(aVDummy,ACCopy1)
169  call accumulate(aVDummy,ACCopy2)
170
171  if(.NOT. (aCCopy1%num_steps == aC%num_steps)) then
172     call die(myname_,"SEVERE: aCCopy1 num_steps value has changed!")
173  endif
174
175  if(.NOT. (aCCopy2%num_steps == aC%num_steps)) then
176     call die(myname_,"SEVERE: aCCopy2 num_steps value has changed!")
177  endif
178
179  if(.NOT. (aCCopy1%steps_done == aC%num_steps+1)) then
180     call die(myname_,"SEVERE: aCCopy1 stesp_done value is incorrect!")
181  endif
182
183  if(.NOT. (aCCopy2%steps_done == aC%num_steps+1)) then
184     call die(myname_,"SEVERE: aCCopy2 stesp_done value is incorrect!")
185  endif
186
187  do i=1,lsize(ACCopy1)
188     do j=1,nRAttr(aC)
189        if( (aCCopy1%data%rAttr(j,i) < 1.9) .or. &
190             (aCCopy1%data%rAttr(j,i) > 2.1) ) then
191           call die(myname_,"Averaging Reals failed")
192        endif
193        if( (aCCopy2%data%rAttr(j,i) < aC%num_steps+0.9) .or. &
194             (aCCopy2%data%rAttr(j,i) > aC%num_steps+1.1) ) then
195           call die(myname_,"Summing Reals failed")
196        endif
197     enddo
198  enddo
199
200  do i=1,lsize(aCCopy1)
201     do j=1,nIAttr(aC)
202        if( aCCopy1%data%iAttr(j,i) /= 2 ) then
203           call die(myname_,"Averaging Ints failed",aCCopy1%data%iAttr(j,i))
204        endif
205        if( aCCopy2%data%iAttr(j,i) /= aC%num_steps+1 ) then
206           call die(myname_,"Summing Ints failed",aCCopy1%data%iAttr(j,i))
207        endif
208     enddo
209  enddo
210
211!:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
212!:::::TESTING INDEXIA AND GETILIST::::::::::::::::::::::::::::::::::::::
213!:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
214
215  call IndexTest_(aC,identifier,device)
216
217!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
218!:::::TESTING COPY AND SHAREDATTRINDEXLIST:::::::::::::::::::::::::::::!
219!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
220
221  call CopyTest_(aC,identifier,device)
222
223!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
224!:::::TESTING EXPORT AND IMPORT FUNCTIONS:::::::::::::::::::::::::::::::!
225!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
226  call ImportExportTest_(aC,identifier,device)
227
228  ! Check that aC is unchanged!
229
230  if(.not.Identical_(ACC1=aC,ACC2=aCExactCopy,Range=1e-5)) then
231     call die(myname_,"aC has been unexpectedly modified!!!")
232  endif
233
234  call clean(aCCopy1)
235  call clean(aCCopy2)
236  call clean(aCExactCopy)
237  call AttrVect_clean(aVDummy)
238
239end subroutine testaC_
240
241!:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
242!:::::TEST FOR INDEXIA AND GETILIST::::::::::::::::::::::::::::::::::::::
243!:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
244
245  subroutine IndexTest_(aC,identifier,device)
246
247    use m_Accumulator, only: nIAttr, nRAttr, getIList, getRList, indexIA, indexRA, Accumulator
248    use m_List,   only: List_allocated   => allocated
249    use m_String, only: String
250    use m_String, only: StringToChar     => toChar
251    use m_String, only: String_clean     => clean
252    use m_stdio
253    use m_die
254
255    implicit none
256
257    type(Accumulator),          intent(in)  :: aC
258    character(len=*),           intent(in)  :: identifier
259    integer,                    intent(in)  :: device
260
261    character(len=*),parameter :: myname_=myname//'::IndexTest_'
262    type(String) :: ItemStr
263    integer :: i,j,k,ierr
264
265    if(nIAttr(aC)>0) then
266       write(device,*) identifier, ":: Testing indexIA and getIList::"
267    else
268       if(List_allocated(aC%data%iList)) then
269          call die(myname_,"iList has been allocated, :&
270               &but there are no atttributes. :&
271               &Please do not initialize a blank list.")
272       end if
273       if(associated(aC%data%iAttr)) then
274          if(size(aC%data%iAttr,1) /= 0) then
275             call die(myname_,"iAttr contains no attributes, &
276                  &yet its size /= 0",size(aC%data%iAttr,1))
277          endif
278       endif
279    end if
280
281    do i=1,nIAttr(aC)
282
283       call getIList(ItemStr,i,aC)
284       j = indexIA(aC,StringToChar(ItemStr))
285       if(i/=j) call die(myname_,"Function indexIA failed!")
286       write(device,*) identifier, &
287            ":: aC Index = ", j,      &
288            ":: Attribute Name = ", StringToChar(ItemStr)
289       call String_clean(ItemStr)
290
291    enddo
292
293    if(nRAttr(aC)>0) then
294       write(device,*) identifier, ":: Testing indexRA and getRList::"
295    else
296       if(List_allocated(aC%data%rList)) then
297          call die(myname_,"rList has been allocated, :&
298               &but there are no atttributes. :&
299               &Please do not initialize a blank list.")
300       end if
301       if(associated(aC%data%rAttr)) then
302          if(size(aC%data%rAttr,1) /= 0) then
303             call die(myname_,"rAttr contains no attributes, &
304                  &yet its size /= 0",size(aC%data%rAttr,1))
305          endif
306       endif
307    end if
308
309    do i=1,nRAttr(aC)
310
311       call getRList(ItemStr,i,aC)
312       j = indexRA(aC,StringToChar(ItemStr))
313       if(i/=j) call die(myname_,"Function indexIA failed!")
314       write(device,*) identifier,   &
315            "::aC Index = ", j,      &
316            "::Attribute Name = ", StringToChar(ItemStr)
317       call String_clean(ItemStr)
318
319    enddo
320
321  end subroutine IndexTest_
322
323!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
324!:::::TEST FOR COPY AND SHAREDATTRINDEXLIST:::::::::::::::::::::::::::::!
325!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
326
327! NOTE: SO FOR ONLY TESTING SHAREDATTRINDEX for reals
328
329  subroutine CopyTest_(aC,identifier,device)
330
331    use m_AttrVect, only : copy
332    use m_AttrVect, only : exportIListToChar,exportRListToChar
333    use m_AttrVect, only : AttrVect_init => init
334    use m_Accumulator
335    use m_List,     only   : List
336    use m_List,     only   : List_init        => init
337    use m_List,     only   : List_copy        => copy
338    use m_List,     only   : List_append      => append
339    use m_List,     only   : ListexportToChar => exportToChar
340    use m_List,     only   : List_clean       => clean
341    use m_String,   only   : String
342    use m_String,   only   : StringToChar     => toChar
343    use m_String,   only   : String_clean     => clean
344    use m_stdio
345    use m_die
346
347    implicit none
348
349    type(Accumulator),          intent(in)  :: aC
350    character(len=*),           intent(in)  :: identifier
351    integer,                    intent(in)  :: device
352
353    character(len=*),parameter :: myname_=myname//'::CopyTest_'
354    type(String) :: ItemStr1, ItemStr2
355    type(Accumulator) :: aCExactCopy
356    integer,dimension(:), pointer :: aCaCIndices1, aCaCIndices2
357    integer,dimension(:), pointer :: aVaCIndices1, aVaCIndices2
358    integer :: aCaCNumShared, aVaCNumShared
359    integer :: i,j,k,ierr
360
361    if( (nRAttr(aC)>0) ) then
362
363       write(device,*) identifier, ":: Testing Copy and SharedAttrIndexList ::"
364       write(device,*) identifier, ":: FIRST AV ATTRIBUTES::", &
365            " RATTR = ", exportRListToChar(aC%data)
366       call init(aCExactCopy,aC,lsize(aC))
367       write(device,*) identifier, ":: SECOND AV ATTRIBUTES::", &
368            " RATTR = ", exportRListToChar(aCExactCopy%data)
369       call zero(aCExactCopy)
370       call copy(aVin=aC%data, aVout=aCExactCopy%data)
371       call SharedAttrIndexList(aC,aCExactCopy,"REAL   ", &
372            aCaCNumShared,aCaCIndices1,aCaCIndices2)
373       call SharedAttrIndexList(aC%data,aCExactCopy,"REAL   ", &
374            aVaCNumShared,aVaCIndices1,aVaCIndices2)
375
376       if(aCaCNumShared/=aVaCNumShared) then
377          call die(myname_,"aCaCNumShared/=aVaCNumShared")
378       endif
379
380       do i=1,aCaCNumShared
381          if(aCaCIndices1(i)/=aVaCIndices1(i)) then
382             call die(myname_,"aCaCIndices1(i)/=aVaCIndices1(i)")
383          endif
384          if(aCaCIndices2(i)/=aVaCIndices2(i)) then
385             call die(myname_,"aCaCIndices2(i)/=aVaCIndices2(i)")
386          endif
387       enddo
388
389       write(device,*) identifier, ":: Indices1 :: Indices2 :: &
390            &Attribute1 :: Attribute2"
391       do i=1,aCaCNumShared
392          call getRList(ItemStr1,aCaCIndices1(i),aC)
393          call getRList(ItemStr2,aCaCIndices2(i),aCExactCopy)
394          write(device,*) identifier,":: ", aCaCIndices1(i), "::", &
395               aCaCIndices2(i), "::", StringToChar(ItemStr1), "::", &
396               StringToChar(ItemStr2)
397          call String_clean(ItemStr1)
398          call String_clean(ItemStr2)
399       enddo
400
401       do i=1,aCaCNumShared
402          do j=1,lsize(aC)
403             if(aC%data%rAttr(aCaCIndices1(i),j) /= &
404                  aCExactCopy%data%rAttr(aCaCIndices2(i),j)) then
405                write(device,*) identifier,aCaCIndices1(i),aCaCIndices2(i), j
406                call die(myname_,"Copy function is MALFUNCTIONING", ierr)
407             endif
408          enddo
409       enddo
410
411       deallocate(aCaCIndices1,aCaCIndices2,aVaCIndices1,aVaCIndices2,stat=ierr)
412       if(ierr/=0) call die(myname_,"deallocate(aCaCIndices,aVaCIndices)",ierr)
413
414       call clean(aCExactCopy)
415
416    else
417
418       write(device,*) identifier, &
419            ":: NOT Testing Copy and SharedAttrIndexList ::", &
420            ":: Consult m_ACTest.F90 to enable this function::"
421    endif
422
423  end subroutine CopyTest_
424
425!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
426!:::::TEST FOR EXPORT AND IMPORT FUNCTIONS:::::::::::::::::::::::::::::::!
427!::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::!
428
429  subroutine ImportExportTest_(aC,identifier,device)
430
431    use m_Accumulator
432    use m_AttrVect, only   : exportIList, exportRList
433    use m_AttrVect, only   : exportIListToChar, exportRListToChar
434    use m_List,     only   : List
435    use m_List,     only   : List_identical   => identical
436    use m_List,     only   : List_get         => get
437    use m_List,     only   : List_clean       => clean
438    use m_String,   only   : String
439    use m_String,   only   : StringToChar     => toChar
440    use m_String,   only   : String_clean     => clean
441    use m_stdio
442    use m_die
443
444    use m_realkinds, only : FP
445
446    implicit none
447
448    type(Accumulator),          intent(in)  :: aC
449    character(len=*),           intent(in)  :: identifier
450    integer,                    intent(in)  :: device
451
452    character(len=*),parameter :: myname_=myname//'::ImportExportTest_'
453    type(Accumulator) :: importAC
454    type(List) :: OutIList, OutRList
455    type(String) :: ItemStr
456    integer,dimension(:),pointer :: OutIVect
457    real(FP), dimension(:),pointer :: OutRVect
458    integer :: exportsize
459    integer :: i,j,k,ierr
460
461    write(device,*) identifier, ":: Testing import and export functions"
462
463    if(nIAttr(aC)>0) then
464
465       call exportIList(aV=aC%data,outIList=outIList)
466
467       if(.NOT. List_identical(aC%data%iList,outIList)) then
468          call die(myname_, "Function exportIList failed!")
469       endif
470
471       call List_get(ItemStr=ItemStr,ith=nIAttr(aC),aList=aC%data%iList)
472
473       allocate(outIVect(lsize(aC)),stat=ierr)
474       if(ierr/=0) call die(myname_,"allocate(outIVect)")
475
476       call exportIAttr(aC=aC,AttrTag=StringToChar(ItemStr), &
477            outVect=OutIVect,lsize=exportsize)
478
479       if(exportsize /= lsize(aC)) then
480          call die(myname_,"(exportsize /= lsize(aC))")
481       endif
482
483       do i=1,exportsize
484          if(aC%data%iAttr(nIAttr(aC),i) /= outIVect(i)) then
485             call die(myname_,"Function exportIAttr failed!")
486          endif
487       enddo
488
489       call init(aC=importAC,bC=aC,lsize=exportsize)
490       call zero(importAC)
491
492       call importIAttr(aC=importAC,AttrTag=StringToChar(ItemStr), &
493            inVect=outIVect,lsize=exportsize)
494
495       j=indexIA(importAC,StringToChar(ItemStr))
496       if(j<=0) call die(myname_,"indexIA(importAC,StringToChar(ItemStr))")
497       do i=1,exportsize
498          if(importAC%data%iAttr(j,i) /= outIVect(i)) then
499             call die(myname_,"Function importIAttr failed!")
500          endif
501       enddo
502
503       call clean(importAC)
504       call List_clean(outIList)
505       call String_clean(ItemStr)
506
507       deallocate(outIVect,stat=ierr)
508       if(ierr/=0) call die(myname_,"deallocate(outIVect)")
509
510    endif
511
512    if(nRAttr(aC)>0) then
513
514       call exportRList(aV=aC%data,outRList=outRList)
515
516       if(.NOT. List_identical(aC%data%rList,outRList)) then
517          call die(myname_, "Function exportRList failed!")
518       endif
519
520       call List_get(ItemStr=ItemStr,ith=nRAttr(aC),aList=aC%data%rList)
521
522       allocate(outRVect(lsize(aC)),stat=ierr)
523       if(ierr/=0) call die(myname_,"allocate(outRVect)")
524
525       call exportRAttr(aC=aC,AttrTag=StringToChar(ItemStr), &
526            outVect=OutRVect,lsize=exportsize)
527
528       if(exportsize /= lsize(aC)) then
529          call die(myname_,"(exportsize /= lsize(aC))")
530       endif
531
532       do i=1,exportsize
533          if(aC%data%rAttr(nRAttr(aC),i) /= outRVect(i)) then
534             call die(myname_,"Function exportRAttr failed!")
535          endif
536       enddo
537
538       call init(aC=importAC,bC=aC,lsize=exportsize)
539       call zero(importAC)
540
541       call importRAttr(aC=importAC,AttrTag=StringToChar(ItemStr), &
542            inVect=outRVect,lsize=exportsize)
543
544       j=indexRA(importAC,StringToChar(ItemStr))
545       if(j<=0) call die(myname_,"indexRA(importAC,StringToChar(ItemStr))")
546       do i=1,exportsize
547          if(importAC%data%rAttr(j,i) /= outRVect(i)) then
548             call die(myname_,"Function importRAttr failed!")
549          endif
550       enddo
551
552       call clean(importAC)
553       call List_clean(outRList)
554       call String_clean(ItemStr)
555
556       deallocate(outRVect,stat=ierr)
557       if(ierr/=0) call die(myname_,"deallocate(outRVect)")
558
559    endif
560
561  end subroutine ImportExportTest_
562
563  logical function Identical_(ACC1,ACC2,Range)
564
565    use m_Accumulator
566    use m_AVTEST,only: AttrVect_identical => Identical
567    use m_stdio
568    use m_die
569
570    use m_realkinds, only : FP
571
572    implicit none
573
574    type(Accumulator), intent(in) :: ACC1
575    type(Accumulator), intent(in) :: ACC2
576    real, optional,    intent(in) :: Range
577
578    character(len=*),parameter :: myname_=myname//'::Identical_'
579    integer :: i,j,k
580
581    Identical_=.true.
582
583    if(present(Range)) then
584       if(.NOT. AttrVect_identical(ACC1%data,ACC2%data,Range)) then
585          Identical_=.false.
586       endif
587    else
588       if(.NOT. AttrVect_identical(ACC1%data,ACC2%data)) then
589          Identical_=.false.
590       endif
591    endif
592
593    if(ACC1%num_steps/=ACC2%num_steps) then
594       Identical_=.false.
595    endif
596
597    if(ACC1%steps_done/=ACC2%steps_done) then
598       Identical_=.false.
599    endif
600
601    j=0
602    k=0
603
604    if(associated(ACC1%iAction).or.associated(ACC2%iAction)) then
605       if(size(ACC1%iAction) /= size(ACC2%iAction)) then
606          Identical_=.FALSE.
607       endif
608       j=size(ACC1%iAction)
609    endif
610
611    if(associated(ACC1%rAction).or.associated(ACC2%rAction)) then
612       if(size(ACC1%rAction) /= size(ACC2%rAction)) then
613          Identical_=.FALSE.
614       endif
615       k=size(ACC2%rAction)
616    endif
617
618    do i=1,j
619       if(ACC1%iAction(i)/=ACC2%iAction(i)) then
620          Identical_=.FALSE.
621       endif
622    enddo
623
624    do i=1,k
625       if(ACC1%rAction(i)/=ACC2%rAction(i)) then
626          Identical_=.FALSE.
627       endif
628    enddo
629
630  end function Identical_
631
632
633end module m_ACTEST
Note: See TracBrowser for help on using the repository browser.