source: trunk/MESOSCALE_DEV/SRC/ARWpost/src/module_get_file_names.F90 @ 1068

Last change on this file since 1068 was 207, checked in by aslmd, 14 years ago

MESOSCALE: A GENERAL CLEAN-UP FOLLOWING UPDATING THE USER MANUAL. EVERYTHING ESSENTIAL IS IN MESOSCALE (much lighter than before). EVERYTHING FOR DEVELOPPERS OR EXPERTS IS IN MESOSCALE_DEV.

File size: 4.3 KB
Line 
1MODULE module_get_file_names
2
3!  To allow for multiple input files, we use a couple of UNIX
4!  commands.  These are activated from either the "system" command or
5!  the "exec" command.  Neither is part of the Fortran standard.
6
7   INTEGER                                       :: number_of_input_files
8   CHARACTER(LEN=132), DIMENSION(:), ALLOCATABLE :: input_file_names
9
10CONTAINS
11
12!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
13#ifdef crayx1
14   SUBROUTINE system(cmd)
15      IMPLICIT NONE
16      CHARACTER (LEN=*) , INTENT(IN) :: cmd
17      integer                        :: ierr
18      CALL pxfsystem(cmd, len(cmd), ierr)
19   RETURN
20   END SUBROUTINE system
21#endif
22
23   SUBROUTINE unix_ls ( root )
24
25      USE module_debug
26
27      IMPLICIT NONE
28     
29      CHARACTER (LEN=*), INTENT(IN) :: root
30      CHARACTER (LEN=132)           :: command
31      INTEGER                       :: ierr , loop , loslen , strlen
32
33
34      !  Build a UNIX command, and "ls", of all of the files mnatching the "root*" prefix.
35
36         loslen = LEN ( command )
37         CALL all_spaces ( command , loslen )
38         WRITE ( command , FMT='("ls -1 ",A,"* > .foo")' ) TRIM ( root )
39         
40         !  We stuck all of the matching files in the ".foo" file.  Now we place the
41         !  number of the those file (i.e. how many there are) in ".foo1".  Also, if we
42         !  do get inside one of these CPP ifdefs, then we set our access flag to true.
43
44         CALL SYSTEM ( TRIM ( command ) )
45         CALL SYSTEM ( '( cat .foo | wc -l > .foo1 )' )
46
47         !  Read the number of files.
48
49         OPEN (FILE   = '.foo1'       , &
50               UNIT   = 112           , &
51               STATUS = 'OLD'         , &
52               ACCESS = 'SEQUENTIAL'  , &
53               FORM   = 'FORMATTED'     )
54
55         READ ( 112 , * ) number_of_input_files
56         CLOSE ( 112 )
57
58         !  If there are zero files, we are toast.
59
60         IF ( number_of_input_files .LE. 0 ) THEN
61            CALL mprintf(.true.,STDOUT, ' Oops, we need at least ONE input file for the program to read.')
62            STOP
63         END IF
64
65      !  Allocate space for this many files.
66
67      ALLOCATE ( input_file_names(number_of_input_files) , STAT=ierr )
68
69      !  Did the allocate work OK?
70
71      IF ( ierr .NE. 0 ) THEN
72         CALL mprintf(.true.,STDOUT, ' tried to allocate %i  input files, (look at ./foo)', i1=number_of_input_files)
73         STOP
74      END IF
75
76      !  Initialize all of the file names to blank.
77
78      CALL init_module_get_file_names
79
80
81      !  Open the file that has the list of filenames.
82
83      OPEN (FILE   = '.foo'        , &
84            UNIT   = 111           , &
85            STATUS = 'OLD'         , &
86            ACCESS = 'SEQUENTIAL'  , &
87            FORM   = 'FORMATTED'     )
88
89      !  Read all of the file names and store them.
90
91      CALL mprintf(.true.,STDOUT, ' ')
92      CALL mprintf(.true.,STDOUT, 'FOUND the following input files:')
93
94      DO loop = 1 , number_of_input_files
95         READ ( 111 , FMT='(A)' ) input_file_names(loop)
96         CALL mprintf(.true.,STDOUT, ' %s ', s1=TRIM(input_file_names(loop)))
97      END DO
98      CLOSE ( 112 )
99      CALL mprintf(.true.,STDOUT, ' ')
100
101      !   We clean up our own messes.
102
103      CALL SYSTEM ( '/bin/rm -f .foo'  )
104      CALL SYSTEM ( '/bin/rm -f .foo1' )
105
106
107   END SUBROUTINE unix_ls
108
109!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
110
111   SUBROUTINE all_spaces ( command , length_of_char )
112
113      IMPLICIT NONE
114
115      INTEGER                        :: length_of_char
116      CHARACTER (LEN=length_of_char) :: command
117      INTEGER                        :: loop
118
119      DO loop = 1 , length_of_char
120         command(loop:loop) = ' '
121      END DO
122
123   END SUBROUTINE all_spaces
124
125!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
126
127   SUBROUTINE init_module_get_file_names
128   
129      IMPLICIT NONE
130      input_file_names = '                                                  ' // &
131                         '                                                  ' // &
132                         '                                '
133
134   END SUBROUTINE init_module_get_file_names
135
136!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
137
138END MODULE module_get_file_names
Note: See TracBrowser for help on using the repository browser.