Reversing a file in Fortran

The name of the pictureThe name of the pictureThe name of the pictureClash Royale CLAN TAG#URR8PPP





.everyoneloves__top-leaderboard:empty,.everyoneloves__mid-leaderboard:empty margin-bottom:0;







up vote
2
down vote

favorite












This is my first foray into (modern) Fortran in order to learn a bit more about the language, and I'm attempting the following problem: taking the path of an arbitrarily-sized text or binary file given as a command line argument, output to stdout the contents of the file in reverse (i.e. the first byte becomes the last). I would like to do this by reading the file sequentially into memory in chunks in one pass without using any seeks/rewinds etc.



It works (I think), and I'm interested in..



  • better ways of working with arrays of pointers (to arrays), as used here with the dynamically sized array of chunkptrs. From what I've understood, it is necessary to make these additional types (Arrays of Pointers) and access through means of chunks(num_chunks)%ptr%chunk_array. Perhaps there is some better approach?

  • how best to perform error handling (should note I forgot to add checks here after the (de)allocates, I would do this in a similar way with stat and errmsg variables, similar to as in open )

  • improvements related to code layout/organisation and use of subroutines and functions.

Any other comments or ideas also greatly appreciated.



! take a file and output it to stdout in reverse

program main
use :: iso_fortran_env
implicit none

!!! constants
integer, parameter :: CHUNK_SIZE = 1024
integer, parameter :: MIN_CHUNKS = 1
integer, parameter :: IN_FID = 10

!!! type definitions
type chunk
character, allocatable :: chunk_array(:)
endtype chunk

type chunkptr
type(chunk), pointer :: ptr
end type chunkptr

!!! locals
character(len=256) :: path, io_msg
integer :: total_bytes, num_chunks, i, status
type(chunkptr), allocatable :: chunks(:)

!!! begin program
call get_command_argument(1, path, status=status)
if (status /= 0) then
write (error_unit, *) "usage: ./reverse <file>"
call exit(1)
end if

allocate(chunks(MIN_CHUNKS))

! open, slurp file and close
open(IN_FID, file=path, access="stream", iostat=status, iomsg=io_msg, status="old")
if (status /= 0) then
write (error_unit, *) trim(io_msg)
call exit(1)
end if

call slurp_file(IN_FID, num_chunks, total_bytes, chunks)
close(IN_FID)

! output in reverse, and print debug info
call print_reversed(total_bytes, num_chunks, chunks)
write (error_unit, *) "reversed ", total_bytes, "bytes"

! free allocated resources
do i=num_chunks, 1, -1
deallocate(chunks(i)%ptr%chunk_array)
deallocate(chunks(i)%ptr)
end do

deallocate(chunks)


contains
subroutine slurp_file(fid, num_chunks, total, chunks)
integer :: fid, io_status = 0
integer, intent(out) :: total, num_chunks
type(chunkptr), allocatable :: chunks(:)

num_chunks = 0
total = 1

do
num_chunks = num_chunks + 1
call ensure_capacity(num_chunks, chunks)

allocate(chunks(num_chunks)%ptr)
allocate(chunks(num_chunks)%ptr%chunk_array(CHUNK_SIZE))

READ(fid, pos=total, iostat=io_status) chunks(num_chunks)%ptr%chunk_array
inquire(fid, pos=total)

if (io_status == iostat_end) exit
end do

total = total - 1

end subroutine slurp_file


subroutine ensure_capacity(capacity, chunks)
integer :: capacity
type(chunkptr), allocatable, intent(inout) :: chunks(:)
type(chunkptr), allocatable :: tmp(:)

if (capacity > size(chunks)) then
allocate( tmp( 2*size(chunks)) )
tmp(:size(chunks)) = chunks
call move_alloc(tmp, chunks)
end if
end subroutine ensure_capacity


subroutine print_reversed(total_bytes, num_chunks, chunks)
integer :: total_bytes, num_chunks, i, j
type(chunkptr), allocatable :: chunks(:)

! last chunk may not be a multiple of CHUNK_SIZE...
j = modulo(total_bytes, CHUNK_SIZE)

do i = num_chunks, 1, -1
do j=j, 1, -1
call fputc(output_unit, chunks(i)%ptr%chunk_array(j))
end do

! remaining chunks have size CHUNK_SIZE, however
j = CHUNK_SIZE
end do
end subroutine print_reversed

end program main






share|improve this question





















  • Any relation with this question: stackoverflow.com/questions/51328728/… ?
    – albert
    Jul 16 at 16:43










  • Interesting, thanks I hadn't seen this. I think that question is interested in reversing the order of 'blocks' within a text file with a certain structure, whereas I'm just trying to reverse the byte order of any text or binary file. Additionally, the pure Fortran answer given there uses temporary files and I would like to load the file in its entirety into memory - as an exercise to work with dynamic memory allocation.
    – Harry King
    Jul 16 at 18:48
















up vote
2
down vote

favorite












This is my first foray into (modern) Fortran in order to learn a bit more about the language, and I'm attempting the following problem: taking the path of an arbitrarily-sized text or binary file given as a command line argument, output to stdout the contents of the file in reverse (i.e. the first byte becomes the last). I would like to do this by reading the file sequentially into memory in chunks in one pass without using any seeks/rewinds etc.



It works (I think), and I'm interested in..



  • better ways of working with arrays of pointers (to arrays), as used here with the dynamically sized array of chunkptrs. From what I've understood, it is necessary to make these additional types (Arrays of Pointers) and access through means of chunks(num_chunks)%ptr%chunk_array. Perhaps there is some better approach?

  • how best to perform error handling (should note I forgot to add checks here after the (de)allocates, I would do this in a similar way with stat and errmsg variables, similar to as in open )

  • improvements related to code layout/organisation and use of subroutines and functions.

Any other comments or ideas also greatly appreciated.



! take a file and output it to stdout in reverse

program main
use :: iso_fortran_env
implicit none

!!! constants
integer, parameter :: CHUNK_SIZE = 1024
integer, parameter :: MIN_CHUNKS = 1
integer, parameter :: IN_FID = 10

!!! type definitions
type chunk
character, allocatable :: chunk_array(:)
endtype chunk

type chunkptr
type(chunk), pointer :: ptr
end type chunkptr

!!! locals
character(len=256) :: path, io_msg
integer :: total_bytes, num_chunks, i, status
type(chunkptr), allocatable :: chunks(:)

!!! begin program
call get_command_argument(1, path, status=status)
if (status /= 0) then
write (error_unit, *) "usage: ./reverse <file>"
call exit(1)
end if

allocate(chunks(MIN_CHUNKS))

! open, slurp file and close
open(IN_FID, file=path, access="stream", iostat=status, iomsg=io_msg, status="old")
if (status /= 0) then
write (error_unit, *) trim(io_msg)
call exit(1)
end if

call slurp_file(IN_FID, num_chunks, total_bytes, chunks)
close(IN_FID)

! output in reverse, and print debug info
call print_reversed(total_bytes, num_chunks, chunks)
write (error_unit, *) "reversed ", total_bytes, "bytes"

! free allocated resources
do i=num_chunks, 1, -1
deallocate(chunks(i)%ptr%chunk_array)
deallocate(chunks(i)%ptr)
end do

deallocate(chunks)


contains
subroutine slurp_file(fid, num_chunks, total, chunks)
integer :: fid, io_status = 0
integer, intent(out) :: total, num_chunks
type(chunkptr), allocatable :: chunks(:)

num_chunks = 0
total = 1

do
num_chunks = num_chunks + 1
call ensure_capacity(num_chunks, chunks)

allocate(chunks(num_chunks)%ptr)
allocate(chunks(num_chunks)%ptr%chunk_array(CHUNK_SIZE))

READ(fid, pos=total, iostat=io_status) chunks(num_chunks)%ptr%chunk_array
inquire(fid, pos=total)

if (io_status == iostat_end) exit
end do

total = total - 1

end subroutine slurp_file


subroutine ensure_capacity(capacity, chunks)
integer :: capacity
type(chunkptr), allocatable, intent(inout) :: chunks(:)
type(chunkptr), allocatable :: tmp(:)

if (capacity > size(chunks)) then
allocate( tmp( 2*size(chunks)) )
tmp(:size(chunks)) = chunks
call move_alloc(tmp, chunks)
end if
end subroutine ensure_capacity


subroutine print_reversed(total_bytes, num_chunks, chunks)
integer :: total_bytes, num_chunks, i, j
type(chunkptr), allocatable :: chunks(:)

! last chunk may not be a multiple of CHUNK_SIZE...
j = modulo(total_bytes, CHUNK_SIZE)

do i = num_chunks, 1, -1
do j=j, 1, -1
call fputc(output_unit, chunks(i)%ptr%chunk_array(j))
end do

! remaining chunks have size CHUNK_SIZE, however
j = CHUNK_SIZE
end do
end subroutine print_reversed

end program main






share|improve this question





















  • Any relation with this question: stackoverflow.com/questions/51328728/… ?
    – albert
    Jul 16 at 16:43










  • Interesting, thanks I hadn't seen this. I think that question is interested in reversing the order of 'blocks' within a text file with a certain structure, whereas I'm just trying to reverse the byte order of any text or binary file. Additionally, the pure Fortran answer given there uses temporary files and I would like to load the file in its entirety into memory - as an exercise to work with dynamic memory allocation.
    – Harry King
    Jul 16 at 18:48












up vote
2
down vote

favorite









up vote
2
down vote

favorite











This is my first foray into (modern) Fortran in order to learn a bit more about the language, and I'm attempting the following problem: taking the path of an arbitrarily-sized text or binary file given as a command line argument, output to stdout the contents of the file in reverse (i.e. the first byte becomes the last). I would like to do this by reading the file sequentially into memory in chunks in one pass without using any seeks/rewinds etc.



It works (I think), and I'm interested in..



  • better ways of working with arrays of pointers (to arrays), as used here with the dynamically sized array of chunkptrs. From what I've understood, it is necessary to make these additional types (Arrays of Pointers) and access through means of chunks(num_chunks)%ptr%chunk_array. Perhaps there is some better approach?

  • how best to perform error handling (should note I forgot to add checks here after the (de)allocates, I would do this in a similar way with stat and errmsg variables, similar to as in open )

  • improvements related to code layout/organisation and use of subroutines and functions.

Any other comments or ideas also greatly appreciated.



! take a file and output it to stdout in reverse

program main
use :: iso_fortran_env
implicit none

!!! constants
integer, parameter :: CHUNK_SIZE = 1024
integer, parameter :: MIN_CHUNKS = 1
integer, parameter :: IN_FID = 10

!!! type definitions
type chunk
character, allocatable :: chunk_array(:)
endtype chunk

type chunkptr
type(chunk), pointer :: ptr
end type chunkptr

!!! locals
character(len=256) :: path, io_msg
integer :: total_bytes, num_chunks, i, status
type(chunkptr), allocatable :: chunks(:)

!!! begin program
call get_command_argument(1, path, status=status)
if (status /= 0) then
write (error_unit, *) "usage: ./reverse <file>"
call exit(1)
end if

allocate(chunks(MIN_CHUNKS))

! open, slurp file and close
open(IN_FID, file=path, access="stream", iostat=status, iomsg=io_msg, status="old")
if (status /= 0) then
write (error_unit, *) trim(io_msg)
call exit(1)
end if

call slurp_file(IN_FID, num_chunks, total_bytes, chunks)
close(IN_FID)

! output in reverse, and print debug info
call print_reversed(total_bytes, num_chunks, chunks)
write (error_unit, *) "reversed ", total_bytes, "bytes"

! free allocated resources
do i=num_chunks, 1, -1
deallocate(chunks(i)%ptr%chunk_array)
deallocate(chunks(i)%ptr)
end do

deallocate(chunks)


contains
subroutine slurp_file(fid, num_chunks, total, chunks)
integer :: fid, io_status = 0
integer, intent(out) :: total, num_chunks
type(chunkptr), allocatable :: chunks(:)

num_chunks = 0
total = 1

do
num_chunks = num_chunks + 1
call ensure_capacity(num_chunks, chunks)

allocate(chunks(num_chunks)%ptr)
allocate(chunks(num_chunks)%ptr%chunk_array(CHUNK_SIZE))

READ(fid, pos=total, iostat=io_status) chunks(num_chunks)%ptr%chunk_array
inquire(fid, pos=total)

if (io_status == iostat_end) exit
end do

total = total - 1

end subroutine slurp_file


subroutine ensure_capacity(capacity, chunks)
integer :: capacity
type(chunkptr), allocatable, intent(inout) :: chunks(:)
type(chunkptr), allocatable :: tmp(:)

if (capacity > size(chunks)) then
allocate( tmp( 2*size(chunks)) )
tmp(:size(chunks)) = chunks
call move_alloc(tmp, chunks)
end if
end subroutine ensure_capacity


subroutine print_reversed(total_bytes, num_chunks, chunks)
integer :: total_bytes, num_chunks, i, j
type(chunkptr), allocatable :: chunks(:)

! last chunk may not be a multiple of CHUNK_SIZE...
j = modulo(total_bytes, CHUNK_SIZE)

do i = num_chunks, 1, -1
do j=j, 1, -1
call fputc(output_unit, chunks(i)%ptr%chunk_array(j))
end do

! remaining chunks have size CHUNK_SIZE, however
j = CHUNK_SIZE
end do
end subroutine print_reversed

end program main






share|improve this question













This is my first foray into (modern) Fortran in order to learn a bit more about the language, and I'm attempting the following problem: taking the path of an arbitrarily-sized text or binary file given as a command line argument, output to stdout the contents of the file in reverse (i.e. the first byte becomes the last). I would like to do this by reading the file sequentially into memory in chunks in one pass without using any seeks/rewinds etc.



It works (I think), and I'm interested in..



  • better ways of working with arrays of pointers (to arrays), as used here with the dynamically sized array of chunkptrs. From what I've understood, it is necessary to make these additional types (Arrays of Pointers) and access through means of chunks(num_chunks)%ptr%chunk_array. Perhaps there is some better approach?

  • how best to perform error handling (should note I forgot to add checks here after the (de)allocates, I would do this in a similar way with stat and errmsg variables, similar to as in open )

  • improvements related to code layout/organisation and use of subroutines and functions.

Any other comments or ideas also greatly appreciated.



! take a file and output it to stdout in reverse

program main
use :: iso_fortran_env
implicit none

!!! constants
integer, parameter :: CHUNK_SIZE = 1024
integer, parameter :: MIN_CHUNKS = 1
integer, parameter :: IN_FID = 10

!!! type definitions
type chunk
character, allocatable :: chunk_array(:)
endtype chunk

type chunkptr
type(chunk), pointer :: ptr
end type chunkptr

!!! locals
character(len=256) :: path, io_msg
integer :: total_bytes, num_chunks, i, status
type(chunkptr), allocatable :: chunks(:)

!!! begin program
call get_command_argument(1, path, status=status)
if (status /= 0) then
write (error_unit, *) "usage: ./reverse <file>"
call exit(1)
end if

allocate(chunks(MIN_CHUNKS))

! open, slurp file and close
open(IN_FID, file=path, access="stream", iostat=status, iomsg=io_msg, status="old")
if (status /= 0) then
write (error_unit, *) trim(io_msg)
call exit(1)
end if

call slurp_file(IN_FID, num_chunks, total_bytes, chunks)
close(IN_FID)

! output in reverse, and print debug info
call print_reversed(total_bytes, num_chunks, chunks)
write (error_unit, *) "reversed ", total_bytes, "bytes"

! free allocated resources
do i=num_chunks, 1, -1
deallocate(chunks(i)%ptr%chunk_array)
deallocate(chunks(i)%ptr)
end do

deallocate(chunks)


contains
subroutine slurp_file(fid, num_chunks, total, chunks)
integer :: fid, io_status = 0
integer, intent(out) :: total, num_chunks
type(chunkptr), allocatable :: chunks(:)

num_chunks = 0
total = 1

do
num_chunks = num_chunks + 1
call ensure_capacity(num_chunks, chunks)

allocate(chunks(num_chunks)%ptr)
allocate(chunks(num_chunks)%ptr%chunk_array(CHUNK_SIZE))

READ(fid, pos=total, iostat=io_status) chunks(num_chunks)%ptr%chunk_array
inquire(fid, pos=total)

if (io_status == iostat_end) exit
end do

total = total - 1

end subroutine slurp_file


subroutine ensure_capacity(capacity, chunks)
integer :: capacity
type(chunkptr), allocatable, intent(inout) :: chunks(:)
type(chunkptr), allocatable :: tmp(:)

if (capacity > size(chunks)) then
allocate( tmp( 2*size(chunks)) )
tmp(:size(chunks)) = chunks
call move_alloc(tmp, chunks)
end if
end subroutine ensure_capacity


subroutine print_reversed(total_bytes, num_chunks, chunks)
integer :: total_bytes, num_chunks, i, j
type(chunkptr), allocatable :: chunks(:)

! last chunk may not be a multiple of CHUNK_SIZE...
j = modulo(total_bytes, CHUNK_SIZE)

do i = num_chunks, 1, -1
do j=j, 1, -1
call fputc(output_unit, chunks(i)%ptr%chunk_array(j))
end do

! remaining chunks have size CHUNK_SIZE, however
j = CHUNK_SIZE
end do
end subroutine print_reversed

end program main








share|improve this question












share|improve this question




share|improve this question








edited Jul 16 at 18:52
























asked Jul 16 at 16:11









Harry King

365




365











  • Any relation with this question: stackoverflow.com/questions/51328728/… ?
    – albert
    Jul 16 at 16:43










  • Interesting, thanks I hadn't seen this. I think that question is interested in reversing the order of 'blocks' within a text file with a certain structure, whereas I'm just trying to reverse the byte order of any text or binary file. Additionally, the pure Fortran answer given there uses temporary files and I would like to load the file in its entirety into memory - as an exercise to work with dynamic memory allocation.
    – Harry King
    Jul 16 at 18:48
















  • Any relation with this question: stackoverflow.com/questions/51328728/… ?
    – albert
    Jul 16 at 16:43










  • Interesting, thanks I hadn't seen this. I think that question is interested in reversing the order of 'blocks' within a text file with a certain structure, whereas I'm just trying to reverse the byte order of any text or binary file. Additionally, the pure Fortran answer given there uses temporary files and I would like to load the file in its entirety into memory - as an exercise to work with dynamic memory allocation.
    – Harry King
    Jul 16 at 18:48















Any relation with this question: stackoverflow.com/questions/51328728/… ?
– albert
Jul 16 at 16:43




Any relation with this question: stackoverflow.com/questions/51328728/… ?
– albert
Jul 16 at 16:43












Interesting, thanks I hadn't seen this. I think that question is interested in reversing the order of 'blocks' within a text file with a certain structure, whereas I'm just trying to reverse the byte order of any text or binary file. Additionally, the pure Fortran answer given there uses temporary files and I would like to load the file in its entirety into memory - as an exercise to work with dynamic memory allocation.
– Harry King
Jul 16 at 18:48




Interesting, thanks I hadn't seen this. I think that question is interested in reversing the order of 'blocks' within a text file with a certain structure, whereas I'm just trying to reverse the byte order of any text or binary file. Additionally, the pure Fortran answer given there uses temporary files and I would like to load the file in its entirety into memory - as an exercise to work with dynamic memory allocation.
– Harry King
Jul 16 at 18:48















active

oldest

votes











Your Answer




StackExchange.ifUsing("editor", function ()
return StackExchange.using("mathjaxEditing", function ()
StackExchange.MarkdownEditor.creationCallbacks.add(function (editor, postfix)
StackExchange.mathjaxEditing.prepareWmdForMathJax(editor, postfix, [["\$", "\$"]]);
);
);
, "mathjax-editing");

StackExchange.ifUsing("editor", function ()
StackExchange.using("externalEditor", function ()
StackExchange.using("snippets", function ()
StackExchange.snippets.init();
);
);
, "code-snippets");

StackExchange.ready(function()
var channelOptions =
tags: "".split(" "),
id: "196"
;
initTagRenderer("".split(" "), "".split(" "), channelOptions);

StackExchange.using("externalEditor", function()
// Have to fire editor after snippets, if snippets enabled
if (StackExchange.settings.snippets.snippetsEnabled)
StackExchange.using("snippets", function()
createEditor();
);

else
createEditor();

);

function createEditor()
StackExchange.prepareEditor(
heartbeatType: 'answer',
convertImagesToLinks: false,
noModals: false,
showLowRepImageUploadWarning: true,
reputationToPostImages: null,
bindNavPrevention: true,
postfix: "",
onDemand: true,
discardSelector: ".discard-answer"
,immediatelyShowMarkdownHelp:true
);



);








 

draft saved


draft discarded


















StackExchange.ready(
function ()
StackExchange.openid.initPostLogin('.new-post-login', 'https%3a%2f%2fcodereview.stackexchange.com%2fquestions%2f199602%2freversing-a-file-in-fortran%23new-answer', 'question_page');

);

Post as a guest



































active

oldest

votes













active

oldest

votes









active

oldest

votes






active

oldest

votes










 

draft saved


draft discarded


























 


draft saved


draft discarded














StackExchange.ready(
function ()
StackExchange.openid.initPostLogin('.new-post-login', 'https%3a%2f%2fcodereview.stackexchange.com%2fquestions%2f199602%2freversing-a-file-in-fortran%23new-answer', 'question_page');

);

Post as a guest













































































Popular posts from this blog

Chat program with C++ and SFML

Function to Return a JSON Like Objects Using VBA Collections and Arrays

Will my employers contract hold up in court?