/[lmdze]/trunk/libf/IOIPSL/Stringop/gensig.f90
ViewVC logotype

Diff of /trunk/libf/IOIPSL/Stringop/gensig.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 32 by guez, Tue Apr 6 17:52:58 2010 UTC revision 51 by guez, Tue Sep 20 09:14:34 2011 UTC
# Line 1  Line 1 
1  module gensig_m  module gensig_m
2    
3  implicit none    implicit none
4    
5  contains  contains
6    
7  !=    SUBROUTINE gensig (str, sig)
8     SUBROUTINE gensig (str, sig)  
9  !---------------------------------------------------------------------      ! Generate a signature from the first 30 characters of the string
10  !- Generate a signature from the first 30 characters of the string      ! This signature is not unique and thus when one looks for the one
11  !- This signature is not unique and thus when one looks for the      ! needs to also verify the string.
12  !- one needs to also verify the string.  
13  !---------------------------------------------------------------------      IMPLICIT NONE
14     IMPLICIT NONE  
15  !-      CHARACTER(LEN=*) str
16     CHARACTER(LEN=*) :: str      INTEGER sig
17     INTEGER          :: sig  
18  !-      INTEGER i
19     INTEGER :: i      INTEGER, DIMENSION(30):: prime = (/1, 2, 3, 5, 7, 11, 13, 17, 19, 23, 29, &
20     INTEGER, DIMENSION(30) :: prime=(/1,2,3,5,7,11,13,17,19,23,29,31,37,41,43, &           31, 37, 41, 43, 47, 53, 59, 61, 67, 71, 73, 79, 83, 89, 97, 101, &
21          47,53,59,61,67,71,73,79,83,89,97,101,103,107,109/)           103, 107, 109/)
22  !---------------------------------------------------------------------  
23     sig = 0      !---------------------------------------------------------------------
24     DO i=1,MIN(len_trim(str),30)  
25        sig = sig  + prime(i)*IACHAR(str(i:i))      sig = 0
26     ENDDO      DO i=1, MIN(len_trim(str), 30)
27  !-----------------------------         sig = sig  + prime(i)*IACHAR(str(i:i))
28   END SUBROUTINE gensig      ENDDO
29    
30      END SUBROUTINE gensig
31    
32  end module gensig_m  end module gensig_m

Legend:
Removed from v.32  
changed lines
  Added in v.51

  ViewVC Help
Powered by ViewVC 1.1.21