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 

Compiler crash attempting substring of character function

 
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 4:44 pm    Post subject: Compiler crash attempting substring of character function Reply with quote

FTN95 crashes when attempting to compile the following code, the offending statement being, WRITE (*,*) Buff_toStr(buffer)(1:32768).

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

    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.', fOver)

    END DO

    WRITE (*,*) Buff_toStr(buffer)(1:32768)

  END

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



Keith


Last edited by Keith Waters on Mon Mar 03, 2008 4:46 pm; edited 1 time in total
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 4:45 pm    Post subject: Reply with quote

Code:
Runtime error from program:c:\program files\silverfrost\ftn95\ftn95.exe
Access Violation
The instruction at address 00522b96 attempted to read from location 00000218

 00522b26 determine_index_register(<ptr>structÄscoped_entity,enumÄlogical) [+0070]
 00522dfb memory_reference(structÄtree_ptr,enumÄop_type) [+0167]
 0051d0e2 code_generator(<ref>structÄtree_ptr) [+46b3]
 004760a1 do_function_rec(<ptr>structÄtree_record) [+03f1]
 0051d0e2 code_generator(<ref>structÄtree_ptr) [+46b3] [recur=  1]
 00479f25 do_function_top(<ptr>structÄtree_record) [+126f]
 0051d0e2 code_generator(<ref>structÄtree_ptr) [+46b3]
 00416981 end_function(int) [+10f0]

eax=00000210   ebx=04a5033c   ecx=00000000
edx=00000000   esi=00000001   edi=04a50140
ebp=0383ef08   esp=0383eedc   IOPL=2
ds=0023   es=0023   fs=003b
gs=0000   cs=001b   ss=0023
flgs=00210246 [NC EP ZR SN DN NV]

 00522b96  mov      ecx,[eax+0x8]
 00522b99  mov      [ebp-0x14],ecx
 00522b9c  mov      edi,[ebx+0x58]
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


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

PostPosted: Wed Mar 05, 2008 6:05 pm    Post subject: Reply with quote

Thank you for the bug report.
The compiler ought to report a programming error on the line:

WRITE (*,*) Buff_toStr(buffer)(1:32768)

You cannot take a substring of a function returning a character variable.

The compiler has missed the error and then tried to produce executable code.
Back to top
View user's profile Send private message AIM Address
PaulLaidler
Site Admin


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

PostPosted: Sat Apr 05, 2008 4:19 pm    Post subject: Reply with quote

FTN95 now reports this as an error.
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
Page 1 of 1

 
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