-
Notifications
You must be signed in to change notification settings - Fork 0
/
mod_Cmdline.f03
99 lines (84 loc) · 3.26 KB
/
mod_Cmdline.f03
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
! Short Documentation:
!
! This module provies one object:
! - CommandLine: contains an array of strings with the commands. Element 0 is
! program execution, the rest are additional options
!
! The object provides three methods:
! - ReadCommandLine: is the constructor that reads the command line
! - NArgs(CommandLine): is a getter for number of arguments
! - RetrieveCommand(CommandLine, integer n): is a getter for argument number n
!
! JJ 2016
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
module Cmdline
implicit none
private
public :: CommandLine
type StringType
private
character(len=1), dimension(:), allocatable :: char
end type StringType
type CommandLIne
private
type(StringType), dimension(:), allocatable :: string
contains
procedure, public :: RetrieveCommand, ReadCommandLine, NArgs
end type CommandLIne
contains
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
! OBTAINS THE NUMBER OF ARGUMENTS INTRODUCED WHEN RUNNING THE PROGRAM
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
integer function NArgs(self)
class(CommandLIne), intent(in) :: self
NArgs=size(self%string)
end function NArgs
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
! CONSTRUCTOR THAT POPULATES THE COMMAND LINE VARIABLE
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
subroutine ReadCommandLine(self)
class(CommandLIne), intent(out) :: self
character(len=:), allocatable :: buffer
integer :: nargs, i, length
logical :: vflag
nargs=command_argument_count()
allocate(self%string(nargs))
do i=1, nargs
call get_command_argument(i, length=length)
if (allocated(buffer)) deallocate(buffer)
allocate(character(length) :: buffer)
call get_command_argument(i, buffer)
call ArchiveCommand(self, buffer, i)
enddo
end subroutine ReadCommandLine
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!PUTS A STRING IN SLOT 'i' IN THE COMMANDLINE VARIABLE
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
subroutine ArchiveCommand(self, inputstring, i)
class(CommandLIne), intent(inout) :: self
character(len=*),intent(in) :: inputstring
integer, intent(in) :: i
integer :: j,n
n=len(inputstring)
if(allocated(self%string(i)%char)) deallocate(self%string(i)%char)
allocate(self%string(i)%char(n))
do j=1, n
self%string(i)%char(j)=inputstring(j:j)
enddo
end subroutine ArchiveCommand
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
!OBTAINS THE STRING IN SLOT 'i' IN THE COMMANDLINE VARIABLE
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
subroutine RetrieveCommand(self, outputstring, i)
class(CommandLIne), intent(in) :: self
character(len=:), allocatable, intent(out) :: outputstring
integer, intent(in) :: i
integer :: j, n
n=size(self%string(i)%char)
allocate(character(n) :: outputstring)
do j=1, n
outputstring(j:j)=self%string(i)%char(j)
enddo
end subroutine RetrieveCommand
end module Cmdline