forums.silverfrost.com Forum Index forums.silverfrost.com
Welcome to the Silverfrost forums
 
 FAQFAQ   SearchSearch   MemberlistMemberlist   UsergroupsUsergroups   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

Record length with formatted write
Goto page 1, 2  Next
 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support
View previous topic :: View next topic  
Author Message
Keith Waters



Joined: 07 Aug 2007
Posts: 29
Location: London or Somerset, UK

PostPosted: Mon Mar 03, 2008 11:19 pm    Post subject: Record length with formatted write Reply with quote

The following program fails with,

Run-time Error, *** Error 69, Invalid record length (see documentation)
004011a0 WX_BUFFER!WX_BUFFER [+00c6]

Code:
! ---------------------------------------------------------------
! MODULE WX_Buffer
!
! This module implements a fixed size string buffer.
!
! As currently implemented the limits of this buffer are as follows.
!
!   Maximum size of buffer   =  1 Mbyte = 1048576 bytes (characters)
!
!

MODULE WX_Buffer

  IMPLICIT NONE
  PRIVATE

  INTEGER(KIND=SELECTED_INT_KIND(9)), &
                      PARAMETER :: long   = SELECTED_INT_KIND(9)

  INTEGER(KIND=long), PARAMETER :: MAX_BUFF_SIZE = 1048576

  TYPE :: buffer_t
    PRIVATE
    INTEGER(KIND=long)           :: size = 0
    CHARACTER(LEN=MAX_BUFF_SIZE) :: str  = ''
  END TYPE

  INTERFACE Buff_Add
    MODULE PROCEDURE Buff_AddStr
  END INTERFACE

  PUBLIC buffer_t,   &
         Buff_Reset, &
         Buff_Add,   &
         Buff_Len,   &
         Buff_toStr

  PUBLIC OPERATOR (.EQUAL.)

CONTAINS

!----------------------------------------------------------------
! Resets the buffer to empty.
!
  SUBROUTINE Buff_Reset (buffer)
    TYPE(buffer_t), INTENT(INOUT) :: buffer

    buffer%size = 0
    buffer%str  = ''
  END SUBROUTINE


!----------------------------------------------------------------
! Adds character string to buffer.  Used for defining generic Buff_Add
! routine.  Sets fOver to true if adding the string would overflow the
! buffer.
!
  SUBROUTINE Buff_AddStr (buffer, s, fOver)            !PRIVATE
    TYPE(buffer_t),   INTENT(INOUT) :: buffer
    CHARACTER(LEN=*), INTENT(IN)    :: s
    LOGICAL,          INTENT(out)   :: fOver

    INTEGER(KIND=long) :: nextSize

    nextSize = buffer%size + LEN(s)
    fOver    = (nextSize > MAX_BUFF_SIZE)
    IF (fOver) THEN
      buffer%size = MAX_BUFF_SIZE
    ELSE
      buffer%str(buffer%size+1: nextSize) = s
      buffer%size = nextSize
    ENDIF

  END SUBROUTINE

!----------------------------------------------------------------
! Returns current contents of buffer as a string.
!
  FUNCTION Buff_toStr (buffer) result(str)
    TYPE(buffer_t), INTENT(IN) :: buffer
    CHARACTER(LEN=buffer%size) :: str

    str = buffer%str(1: buffer%size)

  END FUNCTION

!----------------------------------------------------------------
! Returns current length of buffer.
!
  FUNCTION Buff_Len (buffer)
    INTEGER(KIND=long)         :: Buff_Len
    TYPE(buffer_t), INTENT(IN) :: buffer

    Buff_Len = buffer%size

  END FUNCTION

!----------------------------------------------------------------


END MODULE


  PROGRAM Buffy

    USE WX_Buffer

    CHARACTER(LEN=2), PARAMETER :: eol = ACHAR(13) // ACHAR(10)

    LOGICAL :: fOver

    TYPE(buffer_t) :: buffer

    DO i = 1, 1000
      CALL Buff_Add (buffer, &
        'If you are out to describe the truth, leave elegance to the tailor.' // eol, fOver)

    END DO

    WRITE (*,'(A)') Buff_toStr(buffer)

  END

! =================================================================

Firstly, I cannot find any reference in the documentation to the record length in formatted output being restricted.

Keith
Back to top
View user's profile Send private message
Keith Waters



Joined: 07 Aug 2007
Posts: 29
Location: London or Somerset, UK

PostPosted: Mon Mar 03, 2008 11:22 pm    Post subject: Reply with quote

Secondly, by my reckoning Buff_toStr(buffer) is 69000 characters long at the point it is written, which makes me suspect the limit is around 32K. Interestingly, the following program appears to run ok.

Code:
  PROGRAM Buffy

    USE WX_Buffer

    CHARACTER(LEN=2), PARAMETER :: eol = ACHAR(13) // ACHAR(10)

    LOGICAL :: fOver

    TYPE(buffer_t) :: buffer

    CHARACTER(LEN=32779) :: s

    DO i = 1, 1000
      CALL Buff_Add (buffer, &
        'If you are out to describe the truth, leave elegance to the tailor.' //

    END DO

    s = Buff_toStr(buffer)
    WRITE (*,'(A)') s

  END


If I now increment the record length by one character to 32780, the program crashes as follows.

Code:
Runtime error from program:c:\k_f90\a7011\v3_1.00\buffy.exe
e to theC:\K_F90\A7011\V3_1.00\buffy.EXE
 tailor.
If you are out to describe the truth, leave elegance to the tailor.
If you are out to describe the truth, leave elegance to the tailor.
If you are out to describe the truth, leave elegance to the tailor.
If you are out to describe the truth, leave}"  gance to theC:\K_F90\A7011\V3_1.00\buffy.EXE
 100f2267 UnitList_destroyAll(<ptr>structÄUnitList) [+0016]
 100e7657 CloseAllFortranUnits [+0024]
 1010f290 CLOSE_UNITS# [+000b]
 101101a8 CLOSETIDY_FTNUNIT# [+000f]
 10030282 do_atexits(void) [+0018]
 1003038a __fortranexit [+000c]
 10110166 DEBUGEXIT# [+0016]
 004011a0 WX_BUFFER!WX_BUFFER [+00f4]

eax=0000006f   ebx=04835184   ecx=04835184
edx=00523189   esi=0060c034   edi=0000006f
ebp=0381fb94   esp=0381fb78   IOPL=3
ds=0023   es=0023   fs=003b
gs=0000   cs=001b   ss=0023
flgs=00010206 [NC EP NZ SN DN NV]

 100f227d  mov      edi,[eax]
 100f227f  mov      [ebp-0x10],edi
 100f2282  push     0xf0f0f0f0


Keith
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7925
Location: Salford, UK

PostPosted: Thu Mar 06, 2008 2:29 pm    Post subject: Reply with quote

As you say, it looks like there is a 32K output buffer limit when using the format descriptor '(A)'. List directed output (*) appears to work.

We will see if the limit can be relaxed.
Back to top
View user's profile Send private message AIM Address
Norm.Campbell



Joined: 31 Aug 2007
Posts: 66

PostPosted: Tue Nov 30, 2010 1:49 am    Post subject: character length limit Reply with quote

Paul

Did you work out a way to relax the limit on something like

parameter ( length_ch = 32000)

character ( LEN = length_ch ) ch_array

which works fine.

But as soon as length_ch > 32K, you get a run-time error

***Error 69, Invalid record length (see documentation)

Unfortunately, I need to read a *.csv file (from a third party) which has 3051 values written as a long string. I can only read the first 2905.

Norm Campbell
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Tue Nov 30, 2010 11:58 pm    Post subject: Reply with quote

Norm,

You could try a character array, which can be handled in a very similar way and has a 2gb size limit, as:
integer*4, parameter :: length_ch = 320000000
character (len=1), dimension (length_ch) :: ch_array
ch_array = ' '

John
Back to top
View user's profile Send private message
Norm.Campbell



Joined: 31 Aug 2007
Posts: 66

PostPosted: Wed Dec 01, 2010 7:28 am    Post subject: character array Reply with quote

Thanks John

Paul, this shifts the problem to elsewhere in my code.

I then need something like

read (ndi, '(32000a1)' ) ch_array

which works fine.

But as soon as I try > '(32768a1)' in the read statement, the read doesn't operate correctly.
Back to top
View user's profile Send private message
Martin



Joined: 09 Sep 2004
Posts: 43

PostPosted: Mon Jan 03, 2011 10:46 pm    Post subject: Reply with quote

Hi guys,

The formatted write problem has now been fixed ready for the next release of FTN95. With the next version you should be able to write character strings of any length.

Martin
Back to top
View user's profile Send private message
Norm.Campbell



Joined: 31 Aug 2007
Posts: 66

PostPosted: Mon Apr 04, 2011 1:16 am    Post subject: character length limit Reply with quote

Hi Martin

You say that "The formatted write problem has now been fixed ready for the next release of FTN95. With the next version you should be able to write character strings of any length."

What version will this be in?

Norm
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7925
Location: Salford, UK

PostPosted: Mon Apr 04, 2011 10:57 am    Post subject: Reply with quote

This refers to the current release which is now 6.10.
This is mentioned in the "News" section of the main Silverfrost website but is yet to appear in the Announcements on this form.
Back to top
View user's profile Send private message AIM Address
Norm.Campbell



Joined: 31 Aug 2007
Posts: 66

PostPosted: Mon Apr 04, 2011 1:39 pm    Post subject: Reply with quote

Thanks for the prompt reply. I'd only just downloaded v6.0, and hadn't realised that v6.1 had been released.

I'm downloading v6.1 now. I'll try reading into and from a character * 64000 array tomorrow.
Back to top
View user's profile Send private message
Norm.Campbell



Joined: 31 Aug 2007
Posts: 66

PostPosted: Tue Apr 05, 2011 10:33 am    Post subject: character array record length Reply with quote

Code with

character *33000 ch_array

and

100 read ( ndi, '(a)', end = 200 ) ch_array

does not work.

I get

Error 69 Invalid record length
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7925
Location: Salford, UK

PostPosted: Tue Apr 05, 2011 11:00 am    Post subject: Reply with quote

I do not experience a problem. Here is my code...

Code:
character(len=33000)::ch_array
character(len=64000)::ndi
ndi = "abc"
read ( ndi, '(a)', end = 200 ) ch_array
print*, ch_array(1:20)
200 continue
end
Back to top
View user's profile Send private message AIM Address
sparge



Joined: 11 Apr 2005
Posts: 371

PostPosted: Tue Apr 05, 2011 12:01 pm    Post subject: Buggy string and salflibc.dll version control Reply with quote

Lest we forget:

http://forums.silverfrost.com/viewtopic.php?t=1832&start=15

Might be worth making sure (particularly in view of very recent new release) that all are singing from the same salflibc.dll version hymn sheet...

Andy
Back to top
View user's profile Send private message Send e-mail
Norm.Campbell



Joined: 31 Aug 2007
Posts: 66

PostPosted: Thu Apr 07, 2011 1:16 am    Post subject: record length Reply with quote

Thanks Paul

Your code:

program test_character_array

character (len=64000) :: ch_array

character (len=64000) :: ndi


ndi = "abc"

read ( ndi, '(a)', end = 200 ) ch_array

write ( 6, '(a)' ) ch_array(1:20)

do ii = 1, 64000

if ( mod ( ii, 32000 ) == 0 ) write ( 6, * ) ii

ch_array ( ii : ii ) = '*'

end do


200 continue


stop
end

compiles under v6.10 and works fine.

I then modified it to

program test_character_array

character*160 file_name

character (len=64000) :: ch_array


do ii = 1, 64000

if ( mod ( ii, 32000 ) == 0 ) write ( 6, * ) ii

ch_array ( ii : ii ) = '*'

end do


c input file

file_name = 'Ryan_Chouest_11_031' //
1 '-D20100731-T102437_Sv_2_records.csv'

ndR = 10

open ( unit = ndR,
1 file = file_name,
2 status = 'unknown' )

rewind ndR


read ( ndR, '(a)', end = 200 ) ch_array

write ( 6, '(a)' ) ch_array(1:20)

read ( ndR, '(a)', end = 200 ) ch_array

write ( 6, '(a)' ) ch_array(1:20)


200 continue


stop
end

I get the Error 69 invalid record length message at line 31, which is the "read ( ndR, '(a)', end = 200 ) ch_array" line.

How do I send you the small test data file?
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7925
Location: Salford, UK

PostPosted: Thu Apr 07, 2011 10:08 am    Post subject: Reply with quote

This is something different and I will refer it to our IO expert.
Back to top
View user's profile Send private message AIM Address
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support All times are GMT + 1 Hour
Goto page 1, 2  Next
Page 1 of 2

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


Powered by phpBB © 2001, 2005 phpBB Group