Fortran 2003 / 2008: Elegant default arguments? - fortran

In fortran, we can define default arguments. However, if an optional argument is not present, it can also not be set. When using arguments as keyword arguments with default values, this leads to awkward constructs like
PROGRAM PDEFAULT
CALL SUB
CALL SUB(3)
CONTAINS
SUBROUTINE SUB(VAL)
INTEGER, OPTIONAL :: VAL
INTEGER :: AVAL ! short for "actual val"
IF(PRESENT(VAL)) THEN
AVAL = VAL
ELSE
AVAL = -1 ! default value
END IF
WRITE(*,'("AVAL is ", I0)') AVAL
END SUBROUTINE SUB
END PROGRAM PDEFAULT
Personally, I often ran into the problem of accidentially typing VAL instead of AVAL, i.e. the disconnect between the variable name in the interface, and the initialized value used in the code can introduce runtime bugs – let alone that this manner of initialization is rather verbose.
Is there some more elegant way of using optional arguments with a default value?
Example It would feel more natural to write something like
IF(NOT(PRESENT(VAL))) VAL = -1
because it avoids the VAL vs AVAL confusion. But it isn't valid, presumably because Fortran passes arguments by reference and thus if VAL is not present in the CALL statement, no memory is associated with VAL and VAL = -1 would cause a segfault.

You described the situation rather well. There is no other way I am aware off and that is standard conforming. The pattern with a local variable named similarly is what people often use. The other option is to just put if (present()) else everywhere, but that is awkward.
The point is that they are optional arguments, not default arguments. Fortran doesn't have default arguments. The may have been better, but that is not what the committee members have chosen in the 80s when preparing Fortran 90.

While also looking into this, I found out that you can in fact do something like the proposed example using the OPTIONAL and VALUE attributes (at least with gfortran, not sure how different compilers might handle it). E.g.:
PROGRAM PDEFAULT
CALL SUB
CALL SUB(3)
CONTAINS
SUBROUTINE SUB(VAL)
INTEGER, OPTIONAL,VALUE :: VAL
IF(.NOT. PRESENT(VAL)) VAL = -1 ! default value
WRITE(*,'("VAL is ", I0)') VAL
END SUBROUTINE SUB
END PROGRAM PDEFAULT
This was implemented in version 4.9 of gfortran. And here's the relevant explanation in the documentation for argument passing conventions:
For OPTIONAL dummy arguments, an absent argument is denoted by a NULL
pointer, except for scalar dummy arguments of type INTEGER, LOGICAL,
REAL and COMPLEX which have the VALUE attribute. For those, a hidden
Boolean argument (logical(kind=C_bool),value) is used to indicate
whether the argument is present.
I also found this discussion interesting as historical context.
Maybe somebody more knowledgeable might have comments on whether doing this is a bad idea (aside from being compiler dependent), but at least at face value it seems like a nice workaround.
Note that this behavior is not part of the Fortran standard, and depends on the implementation of a given compiler. For example, the example code segfaults when using ifort (version 16.0.2).

The Fortran standard lib (https://github.com/fortran-lang/stdlib) provides a function called optval that is used in stdlib_logger for example:
subroutine add_log_file( self, filename, unit, action, position, status, stat )
...
character(*), intent(in), optional :: action
...
character(16) :: aaction
...
aaction = optval(action, 'write')
...
end subroutine add_log_file
So their way of representing the "actual" value is a prepended a.
IMHO, I like the option with an appended _, since the optional values are visually marked as such in the call signature.

Whilst I certainly wouldn't advocate doing so in most situations (and indeed you can't in some situations), one may sometimes use an interface to provide a single entry point for multiple routines with different required arguments rather than using an optional argument. For example your code could be written like
MODULE subs
implicit none
public :: sub
interface sub
module procedure sub_default
module procedure sub_arg
end interface
contains
SUBROUTINE SUB_arg(VAL)
INTEGER :: VAL
WRITE(*,'("VAL is ", I0)') VAL
END SUBROUTINE SUB_arg
SUBROUTINE SUB_default
integer, parameter :: default = 3
CALL SUB_arg(default)
END SUBROUTINE SUB_default
END MODULE SUBS
PROGRAM test
use subs, only: sub
call sub
call sub(5)
END PROGRAM TEST
Again, I don't recommend this approach, but I thought I should include it anyway as an alternative way of providing something that looks like a default.

Another possibility is to use an associate block which associates the local variable name with a variable of the same name as the optional argument eg.
SUBROUTINE SUB(VAL)
INTEGER, OPTIONAL :: VAL
INTEGER :: AVAL ! short for "actual val"
IF (PRESENT(VAL)) THEN
AVAL = VAL
ELSE
AVAL = -1 ! default value
END IF
ASSOCIATE (VAL => AVAL)
WRITE(*,'("VAL is ", I0)') VAL
END ASSOCIATE
END SUBROUTINE SUB
Not ideal but allows you to use the same variable name for the argument and in the body of the routine. I shudder to think of the amount of untidy code I've written coping with the lack of default values for optional arguments - roll on F202X.

I hope Fortran to support a popular syntax like
subroutine mysub( x, val = -1 )
integer, optional :: val
or in a more Fortran style
subroutine mysub( x, val )
integer, optional :: val = -1 !! not SAVE attribute intended
but this seems not supported (as of 2016). So some workaround needs to be done by the users' side...
In my case, after trial-and-errors, I settled down to attaching one underscore to the optional dummy argument, so doing something like (*)
subroutine mysub( x, val_)
integer, optional :: val_
integer val
Other people seem to like the opposite pattern (i.e., dummy variable => sep, local variable => sep_, see split() in StringiFor, for example). As seen in this line, the shortest way to set the default value is
val = -1 ; if (present(val_)) val = val_
But because even this line is somewhat verbose, I usually define a macro like
#define optval(x,opt,val) x = val; if (present(opt)) x = opt
in a common header file and use it as
subroutine mysub( x, val_, eps_ )
integer :: x
integer, optional :: val_
real, optional :: eps_
integer val
real eps
optval( val, val_, -1 )
optval( eps, eps_, 1.0e-5 )
print *, "x=", x, "val=", val, "eps=", eps
endsubroutine
...
call mysub( 100 )
call mysub( 100, val_= 3 )
call mysub( 100, val_= 3, eps_= 1.0e-8 )
However, I believe this is still far from elegant and no more than an effort to make it slightly less error-prone (by using the desired variable name in the body of the subroutine).
Another workaround for a very "big" subroutine might be to pass a derived type that contains all the remaining keyword arguments. For example,
#define getkey(T) type(T), optional :: key_; type(T) key; if (present(key_)) key = key_
module mymod
implicit none
type mysub_k
integer :: val = -1
real :: eps = 1.0e-3
endtype
contains
subroutine mysub( x, seed_, key_ )
integer :: x
integer, optional :: seed_
integer :: seed
getkey(mysub_k) !! for all the remaining keyword arguments
optval( seed, seed_, 100 )
print *, x, seed, key% val, key% eps
endsubroutine
endmodule
program main
use mymod, key => mysub_k
call mysub( 10 )
call mysub( 20, key_= key( val = 3 ) )
call mysub( 30, seed_=200, key_= key( eps = 1.0e-8 ) ) ! ugly...
endprogram
This might be a bit close to what is done by some dynamic languages under the hood, but this is again far from elegant in the above form...
(*) I know it is often considered ugly to use CPP macros, but IMO it depends on how they are used; if they are restricted to limited extensions of Fortran syntax, I feel it is reasonable to use (because there is no metaprogramming facility in Fortran); on the other hand, defining program-dependent constants or branches should probably be avoided. Also, I guess it would be more powerful to use Python etc to make more flexible preprocessors (e.g., PreForM.py and fypp and so on), e.g., to allow a syntax like subroutine sub( val = -1 )

Here is an elegant (i.e., short, clear, standard-conforming) solution:
subroutine sub(val)
integer, optional :: val
write(*,'("aval is ", i0)') val_or_default(val, default=-1)
end subroutine
integer function val_or_default(val, default)
integer, optional, intent(in) :: val
integer, intent(in) :: default
if (present(val)) then ! False if `val` is is not present in `sub`.
val_or_default = val
else
val_or_default = default
endif
end function
This uses the fact that optional arguments can still be passed to a function, even when they are not present,
so long as the corresponding dummy argument is also optional.
There is at least one generic implementation of val_or_default on GitHub
for all intrinsic data types.
(They call it optval.)

Related

How can I protect a module variable that should only be readable through a pointer in fortran?

I have an example program that looks like this:
module important_module
integer, dimension(5), protected, target :: important_array
contains
function testFunction() result(important_array_pointer)
integer, dimension(:), pointer :: important_array_pointer
integer :: i
do i = 1, size(important_array)
important_array(i) = 0
end do
important_array_pointer=>important_array
end function testFunction
end module important_module
Program TEST
use important_module
integer, dimension(:), pointer :: important_array_pointer
important_array_pointer=>testFunction()
print *, important_array_pointer(1) ! prints 0
important_array_pointer(1) = 1
print *, important_array_pointer(1) ! prints 1
End Program TEST
I would like important_array to only be writable from within the important_module module, hence the protected definition. This is because this array is used in conjunction with the fortran FFTW interface and holds information where a fourier transform is performed on, and it's suboptimal to have the input- or output arrays of these operations be public or be accessible from anywhere outside of this module. This example simplifies this as a 1d integer array.
If I generate a pointer to this array, it still becomes writable from the outside, even though I expected some kind of violation error.
Is there a way to ensure that this variable is actually protected and cannot be written to from anywhere outside of the corresponding module?
To start, I agree with #francescalus about pointer usage in Modern Fortran. To me, it is still not clear why you are using a pointer to that important variable you want to protect, approach you clearly noticed, it does not protect your variable as you'd like.
If possible, I would remove the target attribute.
But in the case you have to keep it, then the only (to my knowledge) way is to build an interface layer on top of it:
module important_module
implicit none
private
public :: testfun
integer, parameter :: array_size = 5
integer, target :: important_array(array_size)
contains
function testfun() result(important_array_pointer)
integer, dimension(:), pointer :: important_array_pointer
integer :: i
do i = 1, array_size
important_array(i) = i
end do
important_array_pointer => important_array
end function
end module important_module
module interfmodule
use important_module
implicit none
public
integer, pointer, protected :: var_interf(:)
contains
subroutine setVarPtr()
var_interf => testfun()
end subroutine
end module
Program TEST
use interfmodule
implicit none
call setVarPtr()
print *, var_interf(3)
print *, var_interf(4)
! ! Trying to write gives error !
! var_interf(2) = 10
End Program TEST

Where do you use Fortran block? [duplicate]

I am looking at some code and there is this:
BLOCK
...lines of code...
END BLOCK
What is the purpose of BLOCK? I tried to google it, but all I found was something about BLOCK DATA and COMMON blocks. I'm not sure whether they are related.
From the Fortran 2008 standard:
The BLOCK construct is an executable construct that may contain declarations.
It is not related to common blocks or to block data program units.
So, the main use is this "containing declarations".
As scoping units we have things like
integer i
block
integer j ! A local integer
integer i ! Another i
save i ! ... which can even be SAVEd
end block
which affords locality of declarations:
! ... lots of code
block
integer something
read *, something
end block
! ... lots more code
These scoping blocks allow automatic objects:
integer i
i = 5
block
real x(i)
end block
As executable constructs, they also have useful flow control:
this_block: block
if (something) exit this_block
! ... lots of code
end block
They also have finalization control:
type(t) x
block
type(t) y
end block ! y is finalized
end ! x is not finalized
for x and y of finalizable type.
Oh, and let's not forget how you can confuse people with implicit typing.
I have composed a few more fun examples. What if you want to invoke an assumed length function with different lengths in the same instance of a subprogram? You need a specification statement to tell the compiler the length you want, so a BLOCK construct can do this for you
function F(x)
implicit none
character(*) F
character x(:)
integer i
do i = 1, len(F)
F(i:i) = x(1)
end do
end function F
program blox1
implicit none
integer i
character c
do i = 1, 7
c = achar(65+modulo(i**4+6*i**2+1,26))
block
character(2*i+1), external :: F
call blox1a(F)
end block
end do
contains
subroutine blox1a(F)
interface
function F(x)
import
implicit none
character(2*i+1) F
character x(:)
end function F
end interface
write(*,'(a)') F([c])
end subroutine blox1a
end program blox1
Output with gfortran:
III
PPPPP
GGGGGGG
PPPPPPPPP
WWWWWWWWWWW
FFFFFFFFFFFFF
SSSSSSSSSSSSSSS
Or how about when you need the appropriate KIND for a REAL literal? This requires a named constant and the KIND might be given in the specification statements of another MODULE and may even be given as an expression. In that case you might try defining a named constant with the value of that expression, but if an unlucky choice is made that name might override another host associated name. A BLOCK construct makes it all OK:
module mytypes
use ISO_FORTRAN_ENV
implicit none
type T(KIND)
integer, kind :: KIND
real(KIND) x
end type T
interface assignment(=)
module procedure assign8, assign4
end interface assignment(=)
contains
subroutine assign8(x,y)
real(REAL64), intent(in) :: y
type(T(kind(y))), intent(out) :: x
x%x = y
end subroutine assign8
subroutine assign4(x,y)
real(REAL32), intent(in) :: y
type(T(kind(y))), intent(out) :: x
x%x = y
end subroutine assign4
end module mytypes
program blox2
use mytypes
implicit none
type(T(REAL32)) x
BLOCK
! integer, parameter :: rk = x%KIND ! Not allowed
integer, parameter :: rk = kind(x%x)
x = 0.0072973525664_rk
write(*,'(g0)') x%x
END BLOCK -1 is too small
12! = 479001600
13 is too big
BLOCK
type(T(REAL64)) x
BLOCK
! integer, parameter :: rk = x%KIND ! Not allowed
integer, parameter :: rk = kind(x%x)
x = 0.0072973525664_rk
write(*,'(g0)') x%x
END BLOCK
END BLOCK
end program blox2
Output with gfortran:
0.729735242E-02
0.72973525663999998E-002
It can be tricky to get a Fortran pointer to a C string because there is no syntax to tell C_F_POINTER what the length of the target of a deferred length pointer should be. BLOCK to the rescue!
program blox3
use ISO_C_BINDING
implicit none
character(len=:,kind=C_CHAR), allocatable, target :: x
type(C_PTR) c_hello
integer(C_INTPTR_T) address
character(kind=C_CHAR), pointer :: nul_address
character(len=:,kind=C_CHAR), pointer :: f_hello
integer i
x = 'Hello, world'//achar(0)
c_hello = C_LOC(x(1:1))
address = transfer(c_hello,address)
i = 0
do
call C_F_POINTER(transfer(address+i,C_NULL_PTR),nul_address)
if(nul_address == C_NULL_CHAR) exit
i = i+1
end do
BLOCK
character(len=i,kind=C_CHAR), pointer :: temp
call C_F_POINTER(c_hello,temp)
f_hello => temp
END BLOCK
write(*,'(i0,1x,a)') len(f_hello), f_hello
end program blox3
Output with gfortran:
12 Hello, world
Not to mention that a named BLOCK construct gives us a label to hang our spaghetti code on:
program blox4
implicit none
integer i
integer j(3)
integer k
j = [-1,12,13]
do i = 1, size(j)
factorial: BLOCK
if(j(i) < 0) then
write(*,'(*(g0))') j(i),' is too small'
EXIT factorial
end if
if(j(i) > 12) then
write(*,'(*(g0))') j(i),' is too big'
EXIT factorial
end if
write(*,'(*(g0))') j(i),'! = ',product([(k,k=1,j(i))])
END BLOCK factorial
end do
end program blox4
Output with gfortran:
-1 is too small
12! = 479001600
13 is too big
The block construct allows you to declare entities such as variables, types, external procedures, etc which are locally known to the block but have no effect to any variables outside of the block.
Example 1:
IF (swapxy) THEN
BLOCK
REAL (KIND (x)) tmp
tmp = x
x = y
y = tmp
END BLOCK
END IF
Here the variable tmp is locally defined to help out with the swap of two variables. Outside of the block, the variable tmp is unknown or back its original form if it was defined outside of the block (see next example).
Example 2:
F = 254E-2
BLOCK
REAL F
F = 39.37
END BLOCK
! F is still equal to 254E-2.
The variable F is redefined locally to the block but has no effect outside of it.
These kinds of blocks are used to make the code more readable and easier to understand as you don't need to look to the entire subprogram to understand what the locally defined entities are. Furthermore, the compiler knows that these entities are locally defined, so it might do some more optimization.

Why do I have to specify implicitly for a double precision return value of a function in Fortran?

I am new to Fortran and I am trying on the common block. My code is simple
program main
implicit double precision (p)
real * 8 :: x, y
common /yvalue/ y
x = 3d0
y = 3d0
print *, power(x)
end program main
function power(x)
implicit none
real * 8 :: power
real * 8 :: x, y
common /yvalue/ y
power = x ** y
end function power
It works but if I comment out the second line, which implicitly declares variables starting with p to be double precision, the compiler complains the following
Error: Return type mismatch of function ‘power’ at (1) (REAL(4)/REAL(8))
I do get the point that the return value power is by default a single precision variable, but why declaring power as double precision in the function is not enough? And why writing real * 8 power in main would not work either?
When a procedure (function or subroutine) that you are trying to invoke in your code lays outside the body of your program and also is not part of any module, it's named an external function (or subroutine).
Fortran is a statically-typed language, so the types of all variables and functions must be known at compile-time. So, if you want to reference an external function in your program, there must be a way for the program to know its return type. You have 3 (bad) options for this, and I'll list them, starting from the worst:
WORST: Rely on an implicit-typing rule that happens to match the return type of the external function with the type associated with its identifier in the caller (as you did in your sample).
Why you shouldn't do that? Because it is cancer. It makes the meaning of the code obscure, you can't know what this name reference to. It may even look just like an array variable in some circumstances, instead of a function. Also, the compiler doesn't check argument conformance in this case, so if you don't have specific compiler options turned on, the code will fail at runtime, or worse, will give wrong results. Moreover, implicit-typing is very very rarely useful these days, most of the time it's an ask for trouble. Always use implicit none!
As you noted, by the default rules of implicit-typing, any variable with a name starting with p will be default real type (in your compiler, it is real(4)). As you declared the function result as real*8, that your compiler interpret as real(8) (see final note), the error arises.
BAD: Declare the function's name and type in the caller's specification area.
You'd do that just like you'd declare a variable, like this:
program main
implicit none
real*8 :: x, y, power
By the way, the attribute external may be applied to external procedures like yours. More than giving some properties to the procedure (can be passed as an actual argument, disambiguation from intrinsic procedures), it would make the origin of the identifier clearer.
program main
implicit none
real*8 :: x, y, power
external :: power
Why you shouldn't do that? There is no argument checking by the compiler either. This severely limits your options for communicating to external functions: the arguments cannot be assumed-shape, assumed-rank, polymorphic, parameterized, coarray, or be declared on the callee side as allocatable, optional, pointer, target, asynchronous, volatile or value; the return type cannot be an array, or pointer, or allocatable; the function cannot be passed as argument, be elemental and, if pure, can't be used in such contexts. And the reason for all this is the lack of an explicit interface.
ACCEPTABLE: Specify an interface for your external function in the caller.
Like this:
program main
implicit none
interface
real*8 function power(y)
real*8 :: y
end function
end interface
This way, the compiler is able to know all details of declaration and all the restrictions I mentioned won't apply. Total freedom and code clarity!
Why you shouldn't do that? Because there is a better way, that is using modules! Well, it's totally ok to do this in contexts were you can't go for modules, e.g. when working with already existent large old code. The downside is that, you have almost the same code in two different places, and they must always match.
Bonus: BETTER: Use modules.
program main
use :: aux_module
implicit none
real*8 :: x, y
common /yvalue/ y
x = 3d0
y = 3d0
print *, power(x)
end
module aux_module
implicit none
contains
function power(x)
real*8 :: power
real*8 :: x, y
common /yvalue/ y
power = x ** y
end
end
Why you should definitely do that? Because with modules, interfaces are automatically and implicitly available (less code duplication, no restrictions); modules can be recompiled separately and updated without breaking code. Also, you can declare shared variables in the scope of the module and avoid using common declarations. An even better version of your code would be:
program main
use aux_module
implicit none
real*8 :: x
x = 3d0
y = 3d0
print *, power(x)
end
module aux_module
implicit none
real*8 :: y
contains
function power(x)
real*8 :: power
real*8 :: x
power = x ** y
end
end
There is even the option to include your functions directly into your program, after contains. This is recommended only if you don't plan to reuse this function in other program units. #IanBush's answer covers this case.
Final note: take a look on this answer to see why the syntax real*8 is non-standard and should be avoided.
As stated in the comments simply declaring the function in not only its own scope but also the scope that it is called will solve your problem. However I also want to discourage you from using common, implicit typing, and the completely non-standard real*8. As such here is a version of your program in a more modern dialect
ian#eris:~/work/stackoverflow$ cat power.f90
Program power_program
Implicit None
Integer, Parameter :: wp = Selected_real_kind( 14, 70 )
Real( wp ) :: x, y
x = 3.0_wp
y = 3.0_wp
! Return type and kind of the function power in scope
! due to the implicit interface
Write( *, '( 3( a, 1x, f0.6, 1x ) )' ) &
'x =', x, 'y = ', y, 'x**y = ', power( x, y )
Contains
Pure Function power( x, y ) Result( r )
Real( wp ) :: r
Real( wp ), Intent( In ) :: x
Real( wp ), Intent( In ) :: y
r = x ** y
End Function power
End Program power_program
ian#eris:~/work/stackoverflow$ gfortran -std=f2003 -Wall -Wextra -O power.f90
ian#eris:~/work/stackoverflow$ ./a.out
x = 3.000000 y = 3.000000 x**y = 27.000000
ian#eris:~/work/stackoverflow$

Eliminating hidden copies in Fortran

I wanted to ask some Fortran gurus about this issues I have with an up to date version of the Cray Compiler. I have several warnings that although they do not affect correctness, they will probably do for performance. The warning is:
This argument produces a copy in to a temporary variable.
Here is one of the situations where I get this warning. Within the same file (fem.f90) and module:
call fem( array_local( i, : ), pcor, arcol, inder, &
^
ftn-1438 crayftn: CAUTION FFEM, File = fem.f90, Line = 676, Column = 31
This argument produces a copy in to a temporary variable.
The routine FFEM from where array_local is called looks like:
--------------------------
subroutine ffem( alow, pcor, arcol, inder, iflag )
integer , intent( in ) :: alow(3), pcor(3)
real, intent( in ) :: inder,arcol
integer, intent( out ) :: iflag
integer:: array_local(5,3)
! within in a loop
call fem( array_local( i, : ), pcor, arcol, inder, &
..........
--------------------------
And here is fem subroutine:
--------------------------
subroutine fem (ac, pc, rc, id, flag )
integer, intent( in ) :: ac(3)
.......
--------------------------
I cannot find the way to get rid of that copy in which will definitely slow down my code. I was wondering, does anyone know why this happen, and how can I fix it?
If array_local must be defined as it is and you cannot define it as (5,3) as brady shows, you can consider an assumed shape dummy argument
subroutine fem (ac, pc, rc, id, flag )
integer, intent( in ) :: ac(:)
array passed there can be non-contiguous and still there is no copy, ac will be non-contiguous (strided) too.
You need explicit interfaces for that. That is best achieved by placing the subroutines in a module.
The feasibility of this change depends on your use of array_local elsewhere, but you could swap the order:
integer:: array_local(3,5)
and then call fem:
call fem( array_local( :, i ), pcor, arcol, inder, &
This will allow the compiler to simply send a reference to the appropriate part of the array_local array since columns are ordered contiguously in memory.

What is wrong with this Fortran program?

I can't tell what is wrong with this free form Fortran program. It does not correctly handle its command line arguments.
It works if I use a static array for the command line argument instead of an allocatable array.
Also, is this a good first Fortran program? Is this the type of problem for which Fortran would be useful? I already know C, C++, and a little bit of D.
module fibonacci
use ISO_FORTRAN_ENV
implicit none
contains
subroutine output_fibonacci(ordinal)
! Declare variables
integer, parameter :: LongInt = selected_int_kind (38)
integer, intent(in) :: ordinal
integer :: count
! integer (kind=LongInt) :: count, compare=2
integer (kind=LongInt), dimension(2,2) :: matrix, initial
matrix=reshape((/ 1, 1, 1, 0 /), shape(matrix))
initial=reshape((/ 1, 0, 0, 1 /), shape(initial))
count = ordinal
! Do actual computations
do while (count > 0)
! If the exponent is odd, then the output matrix
! should be multiplied by the current base
if (mod(count,2) == 1) then
initial = matmul(matrix, initial)
end if
! This is the squaring step
matrix = matmul(matrix, matrix)
count = count/2
end do
write (*,*) initial(1,2)
end subroutine output_fibonacci
end module fibonacci
program main
use, intrinsic :: ISO_FORTRAN_ENV
use fibonacci
implicit none
! The maximum allowed input to the program
integer :: max=200, i, size=20
character, allocatable :: argumen(:)
integer :: error, length, input
allocate(argumen(size))
! write(*,*) argcount
do i=1, command_argument_count()
call get_command_argument(i, argumen, length, error)
read(argumen,*,iostat=error) input
! write(*,*) argument
! write (*,*) input
if (error .ne. 0) then
write(ERROR_UNIT,'(I36.1,A)') input, "is not an integer"
stop (1)
else if (input > max) then
write(ERROR_UNIT,'(A,I36.1,A)') "Input ", input, " is too large"
stop (1)
end if
call output_fibonacci(input)
end do
end program
This line
character, allocatable :: argumen(:)
declares an allocatable array of characters. So the statement
allocate(argumen(size))
makes argumen an array of 20 single-character elements. That's not the usual way of dealing with strings in Fortran and argumen doesn't match (in type or rank) the requirements for the second argument in the call to get_command_argument.
Instead you should write
character(len=:), allocatable :: argumen
to declare argumen to be a character variable of allocatable length. In some contexts you can simply assign to such a variable, e.g.
argumen = 'this is the argument'
without having to previously allocate it explicitly.
With Intel Fortran v14 the call to get_command_argument compiles without warning but on execution the argument argumen isn't automatically allocated and it remains unassigned. I'm honestly not sure if this behaviour is standard-conforming or not. One approach would be to make two calls to get_command_argument, first to get the size of the argument, then to get the argument; like this
do i=1, command_argument_count()
call get_command_argument(i, length=length, status=error)
allocate(character(length)::argumen)
call get_command_argument(i, argumen, status=error)
! do stuff with argument
deallocate(argumen)
end do
Using the name length for the variable to be assigned the value returned by the optional argument called length is legal but a mite confusing. The deallocate statement ensures that argumen can be allocated again for the next argument.
I'll leave you the exercise of declaring, and using, an allocatable array of allocatable-length characters.
Disclaimer: the next two paragraphs contain material which some may find subjective. I will not be entering into any discussion about these parts of this answer.
Is this a good first Fortran program ? It's better than a lot of what I see here on SO. Personally I prefer the consistent use of the modern /= to .ne., < to .lt (etc), I don't use stop if I can avoid it (I usually can), and I'm sure I could find other nits to pick.
Is this the type of problem for which Fortran would be useful? Fortran is useful for all types of problem, though I admit it can be quite challenging using it to write a web server.