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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 32 - (show annotations)
Tue Apr 6 17:52:58 2010 UTC (14 years, 2 months ago) by guez
File size: 865 byte(s)
Split "stringop.f90" into single-procedure files. Gathered files in directory
"IOIPSL/Stringop".

Split "flincom.f90" into "flincom.f90" and "flinget.f90". Removed
unused procedures from module "flincom". Removed unused argument
"filename" of procedure "flinopen_nozoom".

Removed unused files.

Split "grid_change.f90" into "grid_change.f90" and
"gr_phy_write_3d.f90".

Removed unused procedures from modules "calendar", "ioipslmpp",
"grid_atob", "gath_cpl" and "getincom". Removed unused procedures in
files "ppm3d.f" and "thermcell.f".

Split "mathelp.f90" into "mathelp.f90" and "mathop.f90".

Removed unused variable "dpres" of module "comvert".

Use argument "itau" instead of local variables "iadvtr" and "first" to
control algorithm in procedure "fluxstokenc".

Removed unused arguments of procedure "integrd".

Removed useless computations at the end of procedure "leapfrog".

Merged common block "matrfil" into module "parafilt".

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

  ViewVC Help
Powered by ViewVC 1.1.21