Dimensional Variables - fortran

I'm writing a program for school in FORTRAN. We have to write a program where the user enters a number of grades. With that number of grades, I have to make the program prompt the user that many times to enter the grades. I think I would use a dimensional variable, but I don't know how.
So far I have this, with obvious compiling errors:
INTEGER :: NumGrades
REAL :: GradeAverage
INTEGER :: N
WRITE (*,*) 'Enter Number of grades: '
READ (*,*) NumGrades
N = NumGrades
REAL, Dimension(N) :: Grade
WRITE (*,*) 'Enter the individual grades: '
READ (*,*) Grade
Any help would be greatly appreciated!

Assuming your assignment isn't overdue, you could use allocation. It essentially lets you give an array size after initializing your variables.
INTEGER :: NumGrades
REAL :: GradeAverage !Not exactly sure what this is used for in this snippet
REAL, DIMENSION(:), ALLOCATABLE :: Grade
INTEGER :: i !Used for loop counters
WRITE (*,*) 'Enter Number of grades: '
READ (*,*) NumGrades
allocate(Grade(NumGrades)) !size(Grade) == NumGrades or whatever you inputted
WRITE (*,*) 'Enter the individual grades: '
!DO i = 1, NumGrades
READ(*, *) Grade(i)
!END DO
GradeAverage = sum(Grade) / size(Grade) !Just thought I'd throw this in
The dimension(:) lets the computer know that there is no defined size yet.
Alternatively, you can set the array size to a max integer value if you don't care about memory constraints.
Hope you got this for your assignment!
Edit - Oh yeah, don't forget to deallocate(Grade).

Related

Fortran prompting user and reading polynomial input

I am writing a program to calculate the roots of a polynomial. The user is prompted a polynomial of no greater than fourth order (not a file read). How do I read a polynomial input in Fortran? I thought about using 1D array, each index representing the degree and the number representing the coefficient, but what about the plus and minus signs? I don't want to restrict the user to a polynomial with one mathematical operation.
If you don't care about pretty printing the polynomial without brackets it's not that difficult:
program prompt_read
implicit none
integer, parameter :: wp = kind(1.0d0) ! work precision
!> Polynomial coefficients (maximum degree = 4), only real values allowed
real(wp) :: a(0:4)
!> Polynomial degree
integer :: n
! initialize coefficients to zero
a = 0
write(*,'(A)',advance='no') "Enter polynomial degree (1-4): "
read(*,*) n
! handle erroneous input
if (n > 4 .or. n < 1) then
write(*,'(A)') 'Input error. Try again.'
stop
end if
write(*,'(A)',advance='no') "Enter polynomial coefficients (ascending powers of x): "
read(*,*) a(0:n)
write(*,'(A)') "The polynomial received was " // polystr(a(0:n))
! ... continue with calculation of roots
contains
pure function polystr(coeffs)
real(wp), intent(in) :: coeffs(0:)
character(len=:), allocatable :: polystr
character(32) :: s
integer :: i
write(s,'("(",F0.3,")")') coeffs(0)
polystr = trim(s)
do i = 1, ubound(coeffs,1)
write(s,'("(",F0.3,")")') coeffs(i)
if (i == 1) then
s = trim(s) // '*x'
else if (i > 1) then
s = trim(s) // '*x^' // achar(iachar('0') + i)
end if
polystr = polystr // ' + ' // trim(s)
end do
end function
end program
Example output:
$ gfortran -Wall -o prompt_read prompt_read.f90
$ ./prompt_read
Enter polynomial degree (1-4): 3
Enter polynomial coefficients (ascending powers): 1,-2,3.,-4.2
The polynomial entered is (1.000) + (-2.000)*x + (3.000)*x^2 + (-4.200)*x^3
A few notes/ideas:
use a custom lower bound of 0 to make the array index match the power of the monomial
you can read both space- or comma-delimited input
the polystr function can only handle polynomials up to degree 9
have a look at polyroots-fortran, a collection of existing polynomial root solvers in Fortran
put the body of the program in an "infinite" do-end do loop with a suitable exit condition (for example upon pressing the key q); add a brief help message to explain usage of the program

How to read a file in fortran by using a while loop?

I am trying to read a text file using a Fortran code. I have a file with 1999 rows and the number of columns vary with each row. Can someone please tell me how one can code such a problem. This is my code for reading a 4*2 text file but I am using do loops which I can't use in my current case.
PROGRAM myread2
IMPLICIT NONE
INTEGER, DIMENSION(100) :: a, b
INTEGER :: row,col,max_rows,max_cols
OPEN(UNIT=11, file='text.txt')
DO row = 1,4
READ(11,*) a(row), b(row)
END DO
PRINT *, a(1)
PRINT *, a(4)
PRINT*, b(4)
END PROGRAM myread2
The best way of reading a file like this depends on how you want to store the data. I'm going to use a ragged array as it's probably simplest, although other container types may be better suited depending on your requirements.
Fortran doesn't have ragged arrays natively, so first you need to define a type to hold each row. This can be done as
type :: RowData
integer, allocatable :: cols(:)
end type
type(RowData), allocatable :: rows(:)
When this container is filled out, the value in the i'th column of the j'th row will be accessed as
value = rows(j)%cols(i)
We can then write a program to read the file, e.g.
type :: RowData
integer, allocatable :: cols(:)
end type
type(RowData), allocatable :: rows(:)
integer :: no_rows
integer :: i
open(unit=11, file='text.txt')
no_rows = count_lines(11)
allocate(rows(no_rows))
do i=1,no_rows
rows(i)%cols = read_row(11)
enddo
Now we just need to write the functions count_lines, which counts the number of lines in the file, and read_row, which reads a line from the file and returns the contents of that line as an array of integers.
Following this question, count_lines can be written as
! Takes a file unit, and returns the number of lines in the file.
! N.B. the file must be at the start of the file.
function count_lines(file_unit) result(output)
integer, intent(in) :: file_unit
integer :: output
integer :: iostat
output = 0
iostat = 0
do while (iostat==0)
read(file_unit, *, iostat=iostat)
if (iostat==0) then
output = output+1
endif
enddo
rewind(file_unit)
end function
Writing read_row, to parse a line of unknown length from a file, can be done by following this question.

Calling Fortran code from julia, accessing array dynamically allocated in fortran

I need to call some fortran code that dynamically allocates arrays similar to this basic example. (unlike this example in the code I'm working with the size of the array is not known at the beginning of the function)
subroutine getIdentity(n,I)
integer, intent(in) :: n
integer, allocatable,dimension(:,:), intent(out) :: I
integer :: j,k
write(*,*) "creating " ,n, "x", n, "identity matrix"
allocate(I(n,n))
do j=1,n
do k=1,n
if(k==j) then
I(j,k) = 1
else
I(j,k) = 0
end if
end do
end do
end subroutine getIdentity
When I call this with this julia code:
I = zeros(Int32,1,1)
n = Ref{Int32}(3)
ccall((:__myModule_MOD_getidentity,"./test.so"), Cvoid ,
(Ref{Int32},Ref{Int32}), n,I)
println(I)
When I look at I in julia it is just garbage, not the Identity matrix I would expect. What would be the correct way to do this?

Fortran code returns 0 for every calculation in the loop

Can anyone help me to find where I am going wrong about writing this code
program time_period
! This program calculates time period of an SHM given length of the chord
implicit none
integer, parameter:: length=10
real, parameter :: g=9.81, pi=3.1415926535897932384
integer, dimension(1:length)::chordlength
integer :: l
real :: time
do l= 1,length
time = 2*pi*(chordlength(l)/(g))**.5
print *, l, time
enddo
end program
Result:
1 0.00000000E+00
2 0.00000000E+00
3 0.00000000E+00
4 0.00000000E+00
5 0.00000000E+00
6 0.00000000E+00
7 0.00000000E+00
8 0.00000000E+00
9 0.00000000E+00
10 0.00000000E+00
If the chord lengths you're interested are the integer values 1,2,...,10 you hardly need an array to store them. Further, if what you are interested in are the SHM period lengths for each of those 10 chord lengths, it strikes me that you should have an array like this:
real, dimension(length) :: shm_periods
which you would then populate, perhaps like this:
do l= 1,length
shm_periods(l) = 2*pi*(l/g)**.5
print *, l, shm_periods(l)
enddo
Next, you could learn about Fortran's array syntax and write only one statement to assign values to shm_periods.
#High Performance Mark
i worked it the following way
program time_period
! This program calculates time period of an SHM given length of the chord
implicit none
integer, parameter:: length=10
real, parameter :: g=9.81, pi=3.1415926535897932384
integer, dimension(1:length)::chordlength
integer :: l
real, dimension(1:length) :: timeperiod
do l= 1,length
print *, 'Enter ChordLength', l
read *, chordlength(l)
timeperiod(l) = 2*pi*(chordlength(l)/g)**.5
enddo
do l=1,length
print *, l, timeperiod(l)
enddo
end program
its giving me results but asking to type the chord lengths...appreciate your help
The code below does not answer your question (since you already did that). But it does address some issues with the design of the code.
As a next step, lets say you want to use a) a function for the calculation, b) have some standard length values to display the period and c) input a custom length for calculation.
Fortran allows for the declaration of elemental functions which can operate on single values or arrays just the same (with no need for a loop). See the example below:
elemental function CalcTimePeriod(chord_length) result(period)
! Calculate the SHM time period from the chord length
real, parameter :: g=9.80665, pi=3.1415926535897932384
real, intent(in) :: chord_length
real :: period
period = 2*pi*sqrt(chord_length/g)
end function
So I am posting the code below in hopes that you can learn something new with modern Fortran.
program SHM_CalcTime
implicit none
! Variables
integer, parameter :: n = 10
real, dimension(n) :: gen_lengths, periods
real :: input_length
integer :: i
! Example calculation from generated array of chord lengths
! fill an array of lengths using the formula len = 1.0 + (i-1)/2
gen_lengths = [ (1.0+real(i-1)/2, i=1, n) ]
! calculate the time periods for ALL the lengths in the array
periods = CalcTimePeriod(gen_lengths)
write (*, '(1x,a14,1x,a18)') 'length', 'period'
do i=1,n
write (*, '(1x,g18.4,1x,g18.6)') gen_lengths(i), periods(i)
end do
input_length = 1.0
do while( input_length>0 )
write (*,*) 'Enter chord length (0 to exit):'
read (*,*) input_length
if(input_length<=0.0) then
exit
end if
write (*, '(1x,g18.4,1x,g18.6)') input_length, CalcTimePeriod(input_length)
end do
contains
elemental function CalcTimePeriod(chord_length) result(period)
! Calculate the SHM time period from the chord length
real, parameter :: g=9.80665, pi=3.1415926535897932384
real, intent(in) :: chord_length
real :: period
period = 2*pi*sqrt(chord_length/g)
end function
end program SHM_CalcTime
On a final note, see that programs can have internal functions declared after a contains statement, with no need for an explicit interface declaration as you would with older Fortran variants.

Dynamic array allocation in fortran90

I am writing a generic subroutine in fortran90 that will read in a column of data (real values). The subroutine should first check to see that the file exists and can be opened, then it determines the number of elements (Array_Size) in the column by reading the number of lines until end of file. Next the subroutine rewinds the file back to the beginning and reads in the data points and assigns each to an array (Column1(n)) and also determines the largest element in the array (Max_Value). The hope is that this subroutine can be written to be completely generic and not require any prior knowledge of the number of data points in the file, which is why the number of elements is first determined so the array, "Column1", can be dynamically allocated to contain "Array_Size" number of data points. Once the array is passed to the main program, it is transferred to another array and the initial dynamically allocated array is deallocated so that the routine can be repeated for multiple other input files, although this example only reads in one data file.
As written below, the program compiles just fine on the Intel fortran compiler; however, when it runs it gives me a severe (174): SIGSEV fault. I place the write(,) statements before and after the allocate statement in the subroutine and it prints the first statement "Program works here", but not the second, which indicates that the problem is occurring at the ALLOCATE (Column1(Array_Size)) statement, between the two write(,) statements. I re-compiled it with -C flag and ran the executable, which fails again and states severe (408): "Attempt to fetch from allocatable variable MISC_ARRAY when it is not allocated". The variable MISC_ARRAY is the dummy variable in the main program, which seems to indicate that the compiler wants the array allocated in the main program and not in the subprogram. If I statically allocate the array, the program works just fine. In order to make the program generic and not require any knowledge of the size of each file, it needs to be dynamically allocated and this should happen in the subprogram, not the main program. Is there a way to accomplish this that I am not seeing?
PROGRAM MAIN
IMPLICIT NONE
! - variable Definitions for MAIN program
INTEGER :: n
! - Variable Definitions for EXPENSE READER Subprograms
REAL, DIMENSION(:), ALLOCATABLE :: Misc_Array,MISC_DATA
INTEGER :: Size_Misc
REAL :: Peak_Misc_Value
! REAL :: Misc_Array(365)
CHARACTER(LEN=13) :: File_Name
File_Name = "Misc.txt"
CALL One_Column(File_Name,Size_Misc,Peak_Misc_Value,Misc_Array)
ALLOCATE (MISC_DATA(Size_Misc))
DO n = 1,Size_Misc ! Transfers array data
MISC_DATA(n) = Misc_Array(n)
END DO
DEALLOCATE (Misc_Array)
END PROGRAM MAIN
SUBROUTINE One_Column(File_Name,Array_Size,Max_Value,Column1)
IMPLICIT NONE
REAL, DIMENSION(:), ALLOCATABLE,INTENT(OUT) :: Column1
! REAL :: Column1(365)
REAL, INTENT(OUT) :: Max_Value
CHARACTER,INTENT(IN) :: File_Name*13
INTEGER, INTENT(OUT) :: Array_Size
INTEGER :: Open_Status,Input_Status,n
! Open the file and check to ensure it is properly opened
OPEN(UNIT=100,FILE = File_Name,STATUS = 'old',ACTION = 'READ', &
IOSTAT = Open_Status)
IF(Open_Status > 0) THEN
WRITE(*,'(A,A)') "**** Cannot Open ",File_Name
STOP
RETURN
END IF
! Determine the size of the file
Array_Size = 0
DO 300
READ(100,*,IOSTAT = Input_Status)
IF(Input_Status < 0) EXIT
Array_Size = Array_Size + 1
300 CONTINUE
REWIND(100)
WRITE(*,*) "Program works here"
ALLOCATE (Column1(Array_Size))
WRITE(*,*) "Program stops working here"
Max_Value = 0.0
DO n = 1,Array_Size
READ(100,*) Column1(n)
IF(Column1(n) .GT. Max_Value) Max_Value = Column1(n)
END DO
END SUBROUTINE One_Column
This is an educated guess: I think that the subroutine One_Column ought to have an explicit interface. As written the source code has 2 compilation units, a program (called main) and an external subroutine (called One_Column).
At compile-time the compiler can't figure out the correct way to call the subroutine from the program. In good-old (emphasis on old) Fortran style it takes a leap of faith and leaves it to the linker to find a subroutine with the right name and crosses its fingers (as it were) and hopes that the actual arguments match the dummy arguments at run-time. This approach won't work on subroutines returning allocated data structures.
For a simple fix move end program to the end of the source file, in the line vacated enter the keyword contains. The compiler will then take care of creating the necessary interface.
For a more scalable fix, put the subroutine into a module and use-associate it.
I think it is important to show the corrected code so that future users can read the question and also see the solution. I broke the subroutine into a series of smaller functions and one subroutine to keep the data as local as possible and implemented it into a module. The main program and module are attached. The main program includes a call to the functions twice, just to show that it can be used modularly to open multiple files.
PROGRAM MAIN
!
! - Author: Jonathan A. Webb
! - Date: December 11, 2014
! - Purpose: This code calls subprograms in module READ_COLUMNAR_FILE
! to determine the number of elements in an input file, the
! largest element in the input file and reads in the column of
! data as an allocatable array
!***************************************************************************
!***************************************************************************
!********************* **********************
!********************* VARIABLE DEFINITIONS **********************
!********************* **********************
!***************************************************************************
!***************************************************************************
USE READ_COLUMNAR_FILE
IMPLICIT NONE
CHARACTER(LEN=13) :: File_Name
INTEGER :: Size_Misc,Size_Bar,Unit_Number
REAL :: Peak_Misc_Value,Peak_Bar_Value
REAL, DIMENSION(:), ALLOCATABLE :: Misc_Array,Bar_Array
!***************************************************************************
!***************************************************************************
!********************* **********************
!********************* FILE READER BLOCK **********************
!********************* **********************
!***************************************************************************
!***************************************************************************
! - This section reads in data from all of the columnar input decks.
! User defines the input file name and number
File_Name = "Misc.txt"; Unit_Number = 100
! Determines the number of rows in the file
Size_Misc = File_Length(File_Name,Unit_Number)
! Yields the allocatable array and the largest element in the array
CALL Read_File(File_Name,Unit_Number,Misc_Array,Peak_Misc_Value)
File_Name = "Bar.txt"; Unit_Number = 100
Size_Bar = File_Length(File_Name,Unit_Number)
CALL Read_File(File_Name,Unit_Number,Bar_Array,Peak_Bar_Value)
END PROGRAM MAIN
MODULE READ_COLUMNAR_FILE
!***********************************************************************************
!***********************************************************************************
! ***
! Author: Jonathan A. Webb ***
! Purpose: Compilation of subprograms required to read in multi-column ***
! data files ***
! Drafted: December 11, 2014 ***
! ***
!***********************************************************************************
!***********************************************************************************
!
!-----------------------------------
! Public functions and subroutines for this module
!-----------------------------------
PUBLIC :: Read_File
PUBLIC :: File_Length
!-----------------------------------
! Private functions and subroutines for this module
!-----------------------------------
PRIVATE :: Check_File
!===============================================================================
CONTAINS
!===============================================================================
SUBROUTINE Check_File(Unit_Number,Open_Status,File_Name)
INTEGER,INTENT(IN) :: Unit_Number
CHARACTER(LEN=13), INTENT(IN) :: File_Name
INTEGER,INTENT(OUT) :: Open_Status
! Check to see if the file exists
OPEN(UNIT=Unit_Number,FILE = File_Name,STATUS='old',ACTION='read', &
IOSTAT = Open_Status)
IF(Open_Status .GT. 0) THEN
WRITE(*,*) "**** Cannot Open ", File_Name," ****"
STOP
RETURN
END IF
END SUBROUTINE Check_File
!===============================================================================
FUNCTION File_Length(File_Name,Unit_Number)
INTEGER :: File_Length
INTEGER, INTENT(IN) :: Unit_Number
CHARACTER(LEN=13),INTENT(IN) :: File_Name
INTEGER :: Open_Status,Input_Status
! Calls subroutine to check on status of file
CALL Check_File(Unit_Number,Open_Status,File_Name)
IF(Open_Status .GT. 0)THEN
WRITE(*,*) "**** Cannot Read", File_Name," ****"
STOP
RETURN
END IF
! Determine File Size
File_Length = 0
DO 300
READ(Unit_Number,*,IOSTAT = Input_Status)
IF(Input_Status .LT. 0) EXIT
File_Length = File_Length + 1
300 CONTINUE
CLOSE(Unit_Number)
END FUNCTION File_Length
!===============================================================================
SUBROUTINE Read_File(File_Name,Unit_Number,Column1,Max_Value)
INTEGER, INTENT(IN) :: Unit_Number
REAL, DIMENSION(:), ALLOCATABLE,INTENT(OUT) :: Column1
CHARACTER(LEN=13),INTENT(IN) :: File_Name
REAL, INTENT(OUT) :: Max_Value
INTEGER :: Array_Size,n
! Determines the array size and allocates the array
Array_Size = File_Length(File_Name,Unit_Number)
ALLOCATE (Column1(Array_Size))
! - Reads in columnar array and determines the element with
! the largest value
Max_Value = 0.0
OPEN(UNIT= Unit_Number,File = File_Name)
DO n = 1,Array_Size
READ(Unit_Number,*) Column1(n)
IF(Column1(n) .GT. Max_Value) Max_Value = Column1(n)
END DO
CLOSE(Unit_Number)
END SUBROUTINE Read_File
!===============================================================================
END MODULE READ_COLUMNAR_FILE