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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 51 - (hide annotations)
Tue Sep 20 09:14:34 2011 UTC (12 years, 9 months ago) by guez
File size: 739 byte(s)
Split "getincom.f90" into "getincom.f90" and "getincom2.f90". Split
"nuage.f" into "nuage.f90", "diagcld1.f90" and "diagcld2.f90". Created
module "chem" from included file "chem.h". Moved "YOEGWD.f90" to
directory "Orography".

In "physiq", for evaporation of water, "zlsdcp" was equal to
"zlvdc". Removed useless variables.

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

  ViewVC Help
Powered by ViewVC 1.1.21