From: James Van Buskirk on
"Den7" <rrr7rrr(a)gmail.com> wrote in message
news:f3a57bcc-e27e-4a98-8545-cdd5c581c827(a)d9g2000prh.googlegroups.com...

> Thanks for the example. Just report immediate error without looking
> inside to fix that : "attempt to write past end of internal file"

I didn't take into account how perverse the compiler could be in its
implementation of list-directed I/O. If it inserts a large number of
leading spaces or any trailing spaces it will break my example.
Therefore we have to jettison list-directed I/O in favor of minimal
field width output:

C:\gfortran\clf\recursive_io>type recursive_io2.f90
module stuff
implicit none
contains
subroutine write_unit(iunit,x)
integer, intent(in) :: iunit
character(*), intent(in) :: x

write(iunit,'(a)') x
end subroutine write_unit
function compose_i4(x)
integer, intent(in) :: x
character(compose_i4_len(x)) compose_i4

write(compose_i4,'(i0)') x
end function compose_i4
pure function compose_i4_len(x)
integer compose_i4_len
integer, intent(in) :: x
character(range(x)+2) temp

write(temp,'(i0)') x
compose_i4_len = len_trim(temp)
end function compose_i4_len
end module stuff

program test
use stuff
implicit none
integer foo
external foo

open(11,file='11.out')
! open(11,file='12.out') ! BUG!
open(12,file='12.out')
! write(11,*) foo(12)
call write_unit(11,compose_i4(foo(12)))
end program test

integer function foo(i)
implicit none
integer i
character*9 char_I
write(char_i,'(i9)') i
write(12,*,err=1000) char_i
1000 foo=i
end function foo

C:\gfortran\clf\recursive_io>gfortran -Wall
recursive_io2.f90 -orecursive_io2

C:\gfortran\clf\recursive_io>recursive_io2

C:\gfortran\clf\recursive_io>type 11.out
12

C:\gfortran\clf\recursive_io>type 12.out
12

> I did not get though your idea as soon as i see killing it
> write(iunit,'(a)') x

Unfortunate that you didn't proofread before posting. I can't
even guess at what the above paragraph is supposed to mean.

> This compiler does not allow recursive I/O was it real I/O or internal
> file I/O

The whole point of my technique is that no recursive I/O remains.
Try it again with the revised version. Maybe your compiler is one
of those that has problems with complicated specification expressions.
What compiler and version is it?

--
write(*,*) transfer((/17.392111325966148d0,6.5794487871554595D-85, &
6.0134700243160014d-154/),(/'x'/)); end


From: robert.corbett on
On Dec 21, 1:32 pm, "James Van Buskirk" <not_va...(a)comcast.net> wrote:

> I had this problem with recursive I/O when I wrote a code generator
> and posted it to the web so people could test it. It seemed
> illogical to me that f90 allowed the programmer to write recursive
> code but that f95 permitted compilers to implement I/O, even
> internal I/O, via fixed data structures that made all I/O operations
> non-reentrant.

There is no connection between recursive I/O and recursion.
None of the Fortran implementations I have used that support
recursive I/O use recursion in their implementations of
recursive I/O.

Bob Corbett
From: Den7 on
On Dec 21, 5:53 pm, "James Van Buskirk" <not_va...(a)comcast.net> wrote:
> "Den7" <rrr7...(a)gmail.com> wrote in message
>
> news:f3a57bcc-e27e-4a98-8545-cdd5c581c827(a)d9g2000prh.googlegroups.com...
>
> > Thanks for the example. Just report immediate error without looking
> > inside to fix that : "attempt to write past end of internal file"
>
> I didn't take into account how perverse the compiler could be in its
> implementation of list-directed I/O.  If it inserts a large number of
> leading spaces or any trailing spaces it will break my example.
> Therefore we have to jettison list-directed I/O in favor of minimal
> field width output:
>
> C:\gfortran\clf\recursive_io>type recursive_io2.f90
> module stuff
>    implicit none
>    contains
>       subroutine write_unit(iunit,x)
>          integer, intent(in) :: iunit
>          character(*), intent(in) :: x
>
>          write(iunit,'(a)') x
>       end subroutine write_unit
>       function compose_i4(x)
>          integer, intent(in) :: x
>          character(compose_i4_len(x)) compose_i4
>
>          write(compose_i4,'(i0)') x
>       end function compose_i4
>       pure function compose_i4_len(x)
>          integer compose_i4_len
>          integer, intent(in) :: x
>          character(range(x)+2) temp
>
>          write(temp,'(i0)') x
>          compose_i4_len = len_trim(temp)
>       end function compose_i4_len
> end module stuff
>
> program test
>    use stuff
>    implicit none
>           integer foo
>           external foo
>
>           open(11,file='11.out')
> !          open(11,file='12.out') ! BUG!
>           open(12,file='12.out')
> !          write(11,*) foo(12)
>           call write_unit(11,compose_i4(foo(12)))
> end program test
>
> integer function foo(i)
>    implicit none
>    integer i
>           character*9 char_I
>           write(char_i,'(i9)') i
>           write(12,*,err=1000) char_i
> 1000      foo=i
> end function foo
>
> C:\gfortran\clf\recursive_io>gfortran -Wall
> recursive_io2.f90 -orecursive_io2
>
> C:\gfortran\clf\recursive_io>recursive_io2
>
> C:\gfortran\clf\recursive_io>type 11.out
> 12
>
> C:\gfortran\clf\recursive_io>type 12.out
>         12
>
> > I did not get though your idea as soon as i see killing it
> >          write(iunit,'(a)') x
>
> Unfortunate that you didn't proofread before posting.  I can't
> even guess at what the above paragraph is supposed to mean.
>
> > This compiler does not allow recursive I/O was it real I/O or internal
> > file I/O
>
> The whole point of my technique is that no recursive I/O remains.
> Try it again with the revised version.  Maybe your compiler is one
> of those that has problems with complicated specification expressions.
> What compiler and version is it?
>
> --
> write(*,*) transfer((/17.392111325966148d0,6.5794487871554595D-85, &
> 6.0134700243160014d-154/),(/'x'/)); end

With latest changes your example works, so i've got the trick you do.

Unfortunately do not see how can i use it to fool the compiler not to
crash,
since i've mentioned already that the crash i get has most probably
different origin then my recursive I/O examples above.
I suspect it crashes because of write somewhere in the code
( i have several Windows screens and I/O streams open) coincides
with another read/write caused by mouse movements. The flood of mouse
position changes causes flood of started
callbacks (with their internal file writes) and they
overlap in time with those which print something into my open windows.

Thanks for the for pure elemental equilibristics though.

Compiler is FTN95 of Silverfrost.
From: Den7 on
On Dec 21, 5:53 pm, "James Van Buskirk" <not_va...(a)comcast.net> wrote:
> "Den7" <rrr7...(a)gmail.com> wrote in message
>
> news:f3a57bcc-e27e-4a98-8545-cdd5c581c827(a)d9g2000prh.googlegroups.com...
>
> > Thanks for the example. Just report immediate error without looking
> > inside to fix that : "attempt to write past end of internal file"
>
> I didn't take into account how perverse the compiler could be in its
> implementation of list-directed I/O.  If it inserts a large number of
> leading spaces or any trailing spaces it will break my example.
> Therefore we have to jettison list-directed I/O in favor of minimal
> field width output:
>
> C:\gfortran\clf\recursive_io>type recursive_io2.f90
> module stuff
>    implicit none
>    contains
>       subroutine write_unit(iunit,x)
>          integer, intent(in) :: iunit
>          character(*), intent(in) :: x
>
>          write(iunit,'(a)') x
>       end subroutine write_unit
>       function compose_i4(x)
>          integer, intent(in) :: x
>          character(compose_i4_len(x)) compose_i4
>
>          write(compose_i4,'(i0)') x
>       end function compose_i4
>       pure function compose_i4_len(x)
>          integer compose_i4_len
>          integer, intent(in) :: x
>          character(range(x)+2) temp
>
>          write(temp,'(i0)') x
>          compose_i4_len = len_trim(temp)
>       end function compose_i4_len
> end module stuff
>
> program test
>    use stuff
>    implicit none
>           integer foo
>           external foo
>
>           open(11,file='11.out')
> !          open(11,file='12.out') ! BUG!
>           open(12,file='12.out')
> !          write(11,*) foo(12)
>           call write_unit(11,compose_i4(foo(12)))
> end program test
>
> integer function foo(i)
>    implicit none
>    integer i
>           character*9 char_I
>           write(char_i,'(i9)') i
>           write(12,*,err=1000) char_i
> 1000      foo=i
> end function foo
>
> C:\gfortran\clf\recursive_io>gfortran -Wall
> recursive_io2.f90 -orecursive_io2
>
> C:\gfortran\clf\recursive_io>recursive_io2
>
> C:\gfortran\clf\recursive_io>type 11.out
> 12
>
> C:\gfortran\clf\recursive_io>type 12.out
>         12
>
> > I did not get though your idea as soon as i see killing it
> >          write(iunit,'(a)') x
>
> Unfortunate that you didn't proofread before posting.  I can't
> even guess at what the above paragraph is supposed to mean.
>
> > This compiler does not allow recursive I/O was it real I/O or internal
> > file I/O
>
> The whole point of my technique is that no recursive I/O remains.
> Try it again with the revised version.  Maybe your compiler is one
> of those that has problems with complicated specification expressions.
> What compiler and version is it?
>
> --
> write(*,*) transfer((/17.392111325966148d0,6.5794487871554595D-85, &
> 6.0134700243160014d-154/),(/'x'/)); end

With latest changes your example works, so i've got the trick you do.

Unfortunately do not see how can i use it to fool the compiler
not to crash, since i've mentioned already that the crash i get has
most probably different origin then my recursive I/O examples above.
I suspect it crashes because of write somewhere in the code
( i have several Windows screens and I/O streams open) coincides
with another read/write caused by mouse movements. The flood of mouse
position changes causes flood of started
callbacks (with their internal file writes) and they
overlap in time with those which print something into my open
windows.

Thanks for the pure elemental equilibristics though.
Compiler is FTN95 of Silverfrost.
From: glen herrmannsfeldt on
robert.corbett(a)sun.com wrote:
(snip)

> There is no connection between recursive I/O and recursion.
> None of the Fortran implementations I have used that support
> recursive I/O use recursion in their implementations of
> recursive I/O.

Well, no, except that both require reentrancy.

I suppose reentrant I/O would be a better term, but it doesn't
seem to be the one people use.

-- glen