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 

Trouble Reading A .CSV file

 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support
View previous topic :: View next topic  
Author Message
JUSTIN



Joined: 22 May 2008
Posts: 2

PostPosted: Wed May 28, 2008 1:40 am    Post subject: Trouble Reading A .CSV file Reply with quote

I am trying to pull data out of a .CSV file, however, i am running into a few problems.

Is there a way to read from a comma delimited format?
I can read the entries of the 43 segments of input in the first record but The complier is not recognizing the end of the record hence it will not read the data in the second through last records. I am quite lost at this point.
Back to top
View user's profile Send private message Send e-mail
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Wed May 28, 2008 3:42 am    Post subject: Reply with quote

There are two suggestions I would make:

1) I successfully read .csv files by reading each record into a character buffer then using my own parsing routine to find each field (segment). the 2 rules I have are:
each field is terminated by a comma ,
text fields, enclosed in "text" can enclose a comma

This has worked well for the .csv files I use
My character buffer is line*1024 , which is the largest record length I require.
You can then read each field, using the appropriate format

2) depending on where you got it, the file you have may not have the normal text file record ending, which is compatible with a fortran read statement.
read (unit,fmt='(a)') line

If this is the case, you can open the file as "transparent" or 1 character fixed length records and search for an end of line terminator, by reading 1 character at a time.

Both these approaches work well for me. Good luck

John
Back to top
View user's profile Send private message
JUSTIN



Joined: 22 May 2008
Posts: 2

PostPosted: Wed May 28, 2008 4:12 am    Post subject: Reply with quote

John,
Thank You for your help.
Sorry to say but I am a beginner at programming and I don't understand what you mean by a character buffer or even what a parsing routine does.
I will study up on it a bit and have a go at it.

I have been reading my textbook for the last two hours and I finaly figured out what is truly going on.

All of the data is enclosed in quotation marks except the numeric date and time. I can give you the first bit of info to illustrate what my hang up is. The data looks like this when I open it up in note pad.

"Order ID","Date","Numeric Time",
9000,6/17/2003 19:52:47,1055879567,
9001,6/17/2003 19:57:17,1055879837,

There are 43 data fields per record and I am reading each record into a DIM=34 array. The first record or line reads in just fine The problem is when the compiler sees the / sign in the date. The / sign tells the compiler to advance to the next record so what is happening is that it is only reading new information into the first two cells of the array each time it reads inside the loop. and I am not getting the information I need out of the file.
Back to top
View user's profile Send private message Send e-mail
IanLambley



Joined: 17 Dec 2006
Posts: 490
Location: Sunderland

PostPosted: Wed May 28, 2008 1:12 pm    Post subject: Reply with quote

Justin,

What John means is that you should read each line into a character variable and take them to bits "by hand". I've being doing it that way since the early 1980s, and I really needed to update some of my routines, so I've just spent the lunch hour writing the following:
Code:

! test of string extraction routines
      character*120 string(4)
      integer*4 istr_len,istat,int_value4
      integer*8 int_value8
      real*4 real_value4
      real*8 real_value8

!test string extraction routine
!note, a double embedded quote is interpreted as a single quotation
      call put_string('"Order ID","Date","Numeric"" Time",',1,istat)
      call set_pos(1)
      print *,'Reading strings'
      do i=1,4
        call string_extract(string(i),istr_len,',',istat)
        print *,istr_len,istat,' ',trim(string(i))
      enddo
      print *,'Quotation removal strings'
      do i=1,4
        call remove_csv_quotes(string(i),'"',istat)
        print *,istat,' ',trim(string(i))
      enddo

!test integer , date, integer extraction
      call put_string('9000,6/17/2003 19:52:47,1055879567',1,istat)
      call set_pos(1)
!extract integer*4
      call integer_extract4(int_value4,',',istat)
      print *,'integer*4 value',int_value4,istat
!extract date/time field
      call string_extract(string(4),istr_len,',',istat)
      print *,'Date time string',istr_len,istat,' ',trim(string(4))
!extract integer*8
      call integer_extract8(int_value8,',',istat)
      print *,'integer*8 value',int_value8,istat
!
! test of real number
      call put_string('25.7,18,455d3',1,istat)
      call set_pos(1)
      call real_extract4(real_value4,',',istat)
      print *,'real*4 value',real_value4,istat
      call real_extract4(real_value4,',',istat)
      print *,'real*4 value',real_value4,istat
      call real_extract8(real_value8,',',istat)
      print *,'real*8 value',real_value8,istat

!now get the date and time ising delimiters of "/", space and ":"
      call put_string(string(4),1,istat)
      call set_pos(1)
      do i=1,6
        call integer_extract4(int_value4,' /:',istat)
        print *,'integer*4 value i',i,int_value4,istat
      enddo

      end




!General read of text data
!=============================================================
!                                                 read_line_in
      subroutine read_line_in(ichan,istat)
! read line of text from input file
      character*2048 line_in
      integer*4 ipos,ilen
      common/read_data_text/line_in
      common/read_data_numb/ipos,ilen
! set extraction pointer to first character
      ipos  = 1
      read(ichan,1000,end=9999)line_in
 1000 format(a)
! determine length of input line
      ilen  = leng(line_in)
! status is successful line read
      istat = 0
      return
!end of file handling
 9999 continue
!nothing read in so set ilen to zero
      ilen  = 0
!end of file detected
      istat = 1
      end



To be continued - see next post


Last edited by IanLambley on Wed May 28, 2008 5:18 pm; edited 2 times in total
Back to top
View user's profile Send private message Send e-mail
IanLambley



Joined: 17 Dec 2006
Posts: 490
Location: Sunderland

PostPosted: Wed May 28, 2008 1:17 pm    Post subject: Reply with quote

Code:

!=============================================================
!                                                   put_string
      subroutine put_string(string,ipos_start,istat)
! read line of text from input file
      character*2048 line_in
      integer*4 ipos,ilen
      common/read_data_text/line_in
      common/read_data_numb/ipos,ilen
      character*(*) string
! insert an user defined string into the buffer ("line_in")
! at the specified start position
      if(ipos_start .gt. 0 .and. ipos_start .le. len(line_in) )then
        line_in(ipos_start:) = string
        ilen  = leng(line_in)
! status is successful string insertion but could have been truncated
        istat = 0
      else
!invalid location for string
        istat = 1
      endif
      end
!=============================================================
!                                                     get_char
      subroutine get_char(chr,istat)
! read a single character from the input line
      character*2048 line_in
      integer*4 ipos,ilen
      common/read_data_text/line_in
      common/read_data_numb/ipos,ilen
      character*1 chr
      integer*4 istat
      if(ipos .gt. ilen)then
!already at end of line
        chr = ' '
        istat = 1
      else
! OK to extract a character and advance pointer for next time
        chr = line_in(ipos:ipos)
        ipos = ipos + 1
      endif
      end
!=============================================================
!                                                      set_pos
      subroutine set_pos(inew)
! set a different extraction position
      character*2048 line_in
      integer*4 ipos,ilen
      common/read_data_text/line_in
      common/read_data_numb/ipos,ilen
      integer*4 inew
      ipos = inew
      end
!=============================================================
!                                                      get_pos
      subroutine get_pos(icurrent)
! find current extraction position
      character*2048 line_in
      integer*4 ipos,ilen
      common/read_data_text/line_in
      common/read_data_numb/ipos,ilen
      integer*4 icurrent
      icurrent = ipos
      end
!=============================================================
!                                               string_extract
      subroutine string_extract(string,istr_len,delims,istat)
! read a character string from the input, terminating at
! specified delimiters
      character*2048 line_in
      integer*4 ipos,ilen
      common/read_data_text/line_in
      common/read_data_numb/ipos,ilen
      character*(*) string,delims
      character*1 chr
      integer*4 i,istr_len,istat,ilen_max
      string = ' '
      istr_len = 0
      ilen_max = len(string)
      istat = 0
      do i=ipos,ilen+1
        call get_char(chr,istat)
        if(istat .eq. 0)then
!not at end of line
          if(index(delims,chr) .ne. 0)then
! terminator found, so exit with what has already been read
            return
          else
! add the character to the string
            if(istr_len .lt. ilen_max)then
              istr_len = istr_len + 1
              string(istr_len:istr_len) = chr
            else
! returning but insufficient space in "string" for full extraction of data
              istat = 2
              return
            endif
          endif
        endif
      enddo
      end


and the next one


Last edited by IanLambley on Tue Jun 16, 2009 7:43 am; edited 2 times in total
Back to top
View user's profile Send private message Send e-mail
IanLambley



Joined: 17 Dec 2006
Posts: 490
Location: Sunderland

PostPosted: Wed May 28, 2008 1:28 pm    Post subject: Reply with quote

Code:

!=============================================================
!                                             integer_extract8
      subroutine integer_extract8(int_value,delims,istat)
! read an 8-byte integer value from the input, terminating at
! specified delimiters
      character*80 integer_text,integer_right
      character*(*) delims
      integer*8 int_value
      integer*4 istat
! set value to zero for safety
      int_value = 0
      call string_extract(integer_text,istr_len,delims,istat)
      if(istat .gt. 1)then
! there has been insufficient space to extract the integer string
        return
      else
! a string has been found, so right justify it for a read
        integer_right = adjustr(integer_text)
        read(integer_right,1000,err=9999)int_value
 1000   format(i80)
        return
      endif
 9999 continue
!invalid characters in integer string
      istat = 3
      end
!=============================================================
!                                             integer_extract4
      subroutine integer_extract4(int_value,delims,istat)
! read a 4-byte integer value from the input, terminating at
! specified delimiters
      character*80 integer_text,integer_right
      character*(*) delims
      integer*4 istat,int_value
! set value to zero for safety
      int_value = 0
      call string_extract(integer_text,istr_len,delims,istat)
      if(istat .gt. 1)then
! there has been insufficient space to extract the integer string
        return
      else
! a string has been found, so right justify it for a read
        integer_right = adjustr(integer_text)
        read(integer_right,1000,err=9999)int_value
 1000   format(i80)
        return
      endif
 9999 continue
!invalid characters in integer string
      istat = 3
      end
!=============================================================
!                                                real_extract4
      subroutine real_extract4(real_value,delims,istat)
! read a 4-byte real value from the input, terminating at
! specified delimiters
      character*80 real_text,real_right
      character*(*) delims
      real*4 real_value
      integer*4 istat
! set value to zero for safety
      real_value = 0e0
      call string_extract(real_text,istr_len,delims,istat)
      if(istat .gt. 1)then
! there has been insufficient space to extract the integer string
        return
      else
! a string has been found, so right justify it for a read
        real_right = adjustr(real_text)
        read(real_right,1000,err=9999)real_value
!important to shift right and use f80.0 in case no decimal point found in string
 1000   format(f80.0)
        return
      endif
 9999 continue
!invalid characters in real string
      istat = 3
      end
!=============================================================
!                                                real_extract8
      subroutine real_extract8(real_value,delims,istat)
! read a 8-byte real value from the input, terminating at
! specified delimiters
      character*80 real_text,real_right
      character*(*) delims
      real*8 real_value
      integer*4 istat
! set value to zero for safety
      real_value = 0d0
      call string_extract(real_text,istr_len,delims,istat)
      if(istat .gt. 1)then
! there has been insufficient space to extract the integer string
        return
      else
! a string has been found, so right justify it for a read
        real_right = adjustr(real_text)
        read(real_right,1000,err=9999)real_value
!important to shift right and use f80.0 in case no decimal point found in string
 1000   format(f80.0)
        return
      endif
 9999 continue
!invalid characters in real string
      istat = 3
      end

cont'd
Back to top
View user's profile Send private message Send e-mail
IanLambley



Joined: 17 Dec 2006
Posts: 490
Location: Sunderland

PostPosted: Wed May 28, 2008 1:30 pm    Post subject: Reply with quote

and finally

Code:

!=============================================================
!                                            remove_csv_quotes
      subroutine remove_csv_quotes(string,quote_char,istat)
      character*(*) string
      character*2048 output_string
      character*1 quote_char
      integer*4 i,ipos,istat,ilen,in_quote
      istat = 1
      if(string(1:1) .ne. quote_char)then
! return with istat = 1, meaning no quotes removed as first
! character of string does not match specified quote character
        return
      else
        output_string = ' '
        in_quote = 1
        ipos = 0
        ilen = leng(string)
        do i=2,ilen
          if(string(i:i) .eq. quote_char)then
!toggle quotation status on and off
            in_quote = 1 - in_quote
          endif
          if(in_quote .eq. 1)then
!within the quotations add character to output string
            ipos = ipos + 1
            output_string(ipos:ipos) = string(i:i)
          endif
        enddo
      endif
!success
      string = output_string
      istat = 0
      end


For reading from a file, replace "call put_string(...)" with something like
ichan=10
open(unit=ichan,file='myfile.txt',status='unknown')
call read_line_in(ichan,istat)

For very long lines, putting recl=2048 in the open statement sometimes helps, but don't quote me on that one!

Regards

Ian
Back to top
View user's profile Send private message Send e-mail
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Fri May 30, 2008 4:36 am    Post subject: Reply with quote

Justin,

To read only the example csv file you gave, the following may help.
If you need to convert the date into days, the function JDATE will also help.

[code:1:f7032696f5]
! Last change: JDC 30 May 2008 1:28 pm
! Program to read a number and date .csv file
!
! "Order ID","Date","Numeric Time",
! 9000,6/17/2003 19:52:47,1055879567,
!
character line*100, fields(5)*40, string*12
integer*4 num_line, iostat, field_val(5), date_time(6), i,j, mc, nf, k, nd, num
!
open (unit=11, file='csv_file.csv')
!
num_line = 0
do
num_line = num_line+1
read (11, fmt='(a)', iostat=iostat) line
if (iostat /= 0) exit
if (num_line == 1) cycle ! ignore headers
!
! Get the fields seperated by a comma
mc = len_trim (line)+1 ! length of active line
nf = 0
fields = ' '
i = 1
do j = 1, mc
if (line(j:j) == ',' .or. j==mc) then
nf = nf+1
fields(nf) = line(i:j-1)
i = j+1
end if
end do
!
! Now get each field
do k = 1,nf
select case (k)
!
case (2) ! date and time field
nd = 0
i = 1
do j = 1,40
if (fields(k)(j:j) == '/' .OR. &
fields(k)(j:j) == ' ' .OR. &
fields(k)(j:j) == ':' ) then
nd = nd+1
string = fields(k)(i:j-1)
read (string, 1001) num
1001 format (bn,i12)
if (iostat/=0) then
write (*,*) 'Unable to read date field',nd,' in line',num_line,' : ',fields(k)
end if
date_time(nd) = num
if (nd == 6) exit
i = j+1
end if
end do

case default ! numeric field
string = fields(k)
read (string, 1001,iostat=iostat) num
if (iostat/=0) then
write (*,*) 'Unable to read field',k,' in line',num_line,' : ',fields(k)
else
field_val(k) = num
end if
end select
end do
!
! Now store the field values recovered
write (*,2001) num_line, field_val(1), date_time(1:6), field_val(3)
2001 format (i6, i8, 2i3,i5,3i3, i12)
end do
!
end

integer*4 FUNCTION jdate (year,month,day)
!
! Converts DAY/MONTH/YEAR to a Julian date transformed to 2000
!
INTEGER*4 day, month, year, yyyy
!
! Test for valid year
if (year > 1800) then
yyyy = year
else if (year > 100) then
yyyy = -1
else if (year > 79) then
yyyy = year + 1900
else if (year > 0 ) then
yyyy = year + 2000
else
yyyy = -1
end if
!
! "Tony T. Warnock" <u091889@lanl.gov>
! 31/10/2002 02:04 AM
!
! jdate = 367*year
! 1 - 7*(year+(month+9)/12)/4
! 1 - 3*((year+(month-9)/7)/100+1)/4
! 1 + 275*month/9+day
! 1 - 730516
!
jdate = 367*yyyy &
- 7*(yyyy+(month+9)/12)/4 &
- 3*((yyyy+(month-9)/7)/
Back to top
View user's profile Send private message
IanLambley



Joined: 17 Dec 2006
Posts: 490
Location: Sunderland

PostPosted: Wed Jun 04, 2008 8:28 pm    Post subject: Reply with quote

Oops!

Deliberate mistakes in "Subroutine string_extract(...)

before do loop insert:

istat=0

DO loop requires

do i=ipos,ilen+1

Ian
PS - Have made the updates
Back to top
View user's profile Send private message Send e-mail
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