[comp.lang.fortran] Implied do loop in write

moshkovi@eurotunnel.ecn.purdue.edu (Gennady Moshkovich) (04/24/91)

Thanks everybody who sent me a reply on my posting.

Here is summary of what I've got:

1)  Number of replies suggested using of regular implied
    do loop in write statement.
    e.g.

    here line break is insured between separate lines

    do 1 i = 1,n
       write(6,100) (matrix(i,j),j=1,m)
   1 continue
100 format(10i8)

This way, however, is quite obvious, and it was implied in
the original posting that the whanted one is the way to
print _without knowing_ before values of m and n.

2) The way to do it is to use format string which are created
   after the value of m and n are determined.

      character*9 frmt
      data frmt/'(00f10.2/)'/


c   when the value of m and n are determined, you need to change
c   format string as

      write(frmt(2:3),'(i2)')numcol

c   to write matrix:

     do 300 j=1,nrow
	write(6,frmt)(smatr(i,j),i=1,numcol)
300  continue

c  credits to howard@ee.utah.edu
c             Walt Howard


Gene

--
Gennady Moshkovich          
Purdue University
Department of Civil Engineering
moshkovi@ecn.purdue.edu

buckland@cheddar.ucs.ubc.ca (Tony Buckland) (04/24/91)

In article <moshkovi.672431251@eurotunnel.ecn.purdue.edu> moshkovi@eurotunnel.ecn.purdue.edu (Gennady Moshkovich) writes:
>    do 1 i = 1,n
>       write(6,100) (matrix(i,j),j=1,m)
>   1 continue
>100 format(10i8)
>
>This way, however, is quite obvious, and it was implied in
>the original posting that the whanted one is the way to
>print _without knowing_ before values of m and n.

 So what's your problem with this method?  It *does* work
 without the values of m and n being known ahead of time.
 You're supposed to use the code as it was written, you
 know.  You're not supposed to substitute constants in
 the code where variables are shown.

moshkovi@sanandreas.ecn.purdue.edu (Gennady Moshkovich) (04/24/91)

buckland@cheddar.ucs.ubc.ca (Tony Buckland) writes:

>In article <moshkovi.672431251@eurotunnel.ecn.purdue.edu> moshkovi@eurotunnel.ecn.purdue.edu (Gennady Moshkovich) writes:
>>    do 1 i = 1,n
>>       write(6,100) (matrix(i,j),j=1,m)
>>   1 continue
>>100 format(10i8)
             ^^^^
	     THIS IS THE PROBLEM !!
>>
>>This way, however, is quite obvious, and it was implied in
>>the original posting that the whanted one is the way to
>>print _without knowing_ before values of m and n.

> So what's your problem with this method?  It *does* work
> without the values of m and n being known ahead of time.
> You're supposed to use the code as it was written, you
> know.  You're not supposed to substitute constants in
> the code where variables are shown.

Just look at the code, and you will see where the problem is.
You can't print with this code more then _10_ elements in a row.
I can repeat again !!!.  I don't know beforehand how many
elements I have, I can have 3, or I can have 300, but the
output MUST look nice.

Have fun.  Gene

--
Gennady Moshkovich          
Purdue University
Department of Civil Engineering
moshkovi@ecn.purdue.edu

mwette@csi.jpl.nasa.gov (Matt Wette) (04/24/91)

In article <moshkovi.672444244@sanandreas.ecn.purdue.edu>, moshkovi@sanandreas.ecn.purdue.edu (Gennady Moshkovich) writes:
|> buckland@cheddar.ucs.ubc.ca (Tony Buckland) writes:
|> 
|> >In article <moshkovi.672431251@eurotunnel.ecn.purdue.edu> moshkovi@eurotunnel.ecn.purdue.edu (Gennady Moshkovich) writes:
|> >>    do 1 i = 1,n
|> >>       write(6,100) (matrix(i,j),j=1,m)
|> >>   1 continue
|> >>100 format(10i8)
|>              ^^^^
|> 	     THIS IS THE PROBLEM !!

|> Just look at the code, and you will see where the problem is.
|> You can't print with this code more then _10_ elements in a row.
|> I can repeat again !!!.  I don't know beforehand how many
|> elements I have, I can have 3, or I can have 300, but the
|> output MUST look nice.
|> 

      SUBROUTINE MPRINT(M, N, A, NA, OUTUT)
C           
      INTEGER M, N, NA, OUTUT
      DOUBLE PRECISION A(NA,N)
C
C     THIS SUBROUTINE PRINTS A MATRIX IN A REASONABLY NICE WAY.
C
C     31MAY88 M.WETTE, UCSB ECE, SANTA BARBARA, CA 93106
C
      INTEGER I,J,K,BEGC,ENDC
      INTEGER NCOL,NFMT,NC
C
      DATA NCOL, NFMT/ 79, 12/
C
      NC = NCOL / NFMT
C
      IF (N .GT. NC) GOTO 20
         DO 10 I = 1,M
            WRITE(OUTUT, 90001) (A(I,J), J=1,N)
   10    CONTINUE
      GOTO 50
   20 CONTINUE
         DO 40 J = 1,N,NC
            BEGC = J
            ENDC = J + NC - 1
            IF (ENDC .GT. N) ENDC = N
            WRITE(OUTUT,90002) BEGC, ENDC
            DO 30 I = 1,M
               WRITE(OUTUT, 90001) (A(I,K), K=BEGC,ENDC)
   30       CONTINUE
   40    CONTINUE
   50 CONTINUE
      RETURN
C
90001 FORMAT(1X,10(1X,1PE11.4))
90002 FORMAT(1X,9H COLUMNS ,I2,9H THROUGH ,I2)
C
C --- LAST LINE OF MPRINT ---
      END

-- 
 _________________________________________________________________
 Matthew R. Wette           | Jet Propulsion Laboratory, 198-326
 mwette@csi.jpl.nasa.gov    | 4800 Oak Grove Dr, Pasadena,CA 91109
 -----------------------------------------------------------------

jeffe@eniac.seas.upenn.edu (George Jefferson ) (04/24/91)

:
:     character*9 frmt
:     data frmt/'(00f10.2/)'/
:     write(frmt(2:3),'(i2)')numcol
:     do 300 j=1,nrow
:	write(6,frmt)(smatr(i,j),i=1,numcol)
:300  continue
:

IMHO this is cleaner, and will work unless you really
can't guess an upper bound for m and n , in which case how
did you dimension x?

      do i=1,m
         write(*,'(1000f8.3)')(x(i,j),j=1,n)
      end do

Are there compilers which don't allow 'excess' format specifiers?

--
-george            george@mech.seas.upenn.edu

rbr4@uhura.cc.rochester.edu (Roland Roberts) (04/24/91)

In article <moshkovi.672444244@sanandreas.ecn.purdue.edu>
moshkovi@sanandreas.ecn.purdue.edu (Gennady Moshkovich) writes: 
[elided]
>Just look at the code, and you will see where the problem is.
>You can't print with this code more then _10_ elements in a row.
>I can repeat again !!!.  I don't know beforehand how many
>elements I have, I can have 3, or I can have 300, but the
>output MUST look nice.

Depending on what you mean by ``nice,'' there are easier ways that
using a subroutine call.  The technique I have often used (both on IBM
VS Fortran and DEC Fortran) is to take advantage of the format
statement having an implied loop, i.e., the last grouping is repeated
until there is no data.  For example:

       do 1 i = 1,n
         write(6,100) (matrix(i,j),j=1,m)
     1 continue
   100 format(1x,10i8,:/,(11x,10i8,:/))

This results in 10 values per row, with all but the first being
indented by one value to ease in spotting its beginning.  Obviously,
the subroutine method gives greater flexibility in what you get, but
this is the simplest.

On both VS Fortran and DEC Fortran, the `:' says ignore additional
format specifiers if there is no additional data.  I don't know how
widespread this is.

roland

-- 
Roland Roberts,  University of Rochester   BITNET: roberts@uornsrl
  Nuclear Structure Research Lab         INTERNET: rbr4@uhura.cc.rochester.edu
  271 East River Road                        UUCP: rochester!ur-cc!rbr4
  Rochester, NY  14267                       AT&T: (716) 275-8962

tim@ksr.com (Tim Peters) (04/24/91)

In article <moshkovi.672444244@sanandreas.ecn.purdue.edu> moshkovi@sanandreas.ecn.purdue.edu (Gennady Moshkovich) writes:
> ... [stuff deleted] ...
>>>    do 1 i = 1,n
>>>       write(6,100) (matrix(i,j),j=1,m)
>>>   1 continue
>>>100 format(10i8)
>             ^^^^
>	     THIS IS THE PROBLEM !!
> ... [stuff deleted] ...
>Just look at the code, and you will see where the problem is.
>You can't print with this code more then _10_ elements in a row.
>I can repeat again !!!.  I don't know beforehand how many
>elements I have, I can have 3, or I can have 300, but the
>output MUST look nice.

Don't feel bad -- Fortran formats are very powerful but remarkably few
programmers know how to use them.  They're about as obscure as anything
can be <grin/sigh>.

If you've tried the "build the format at runtime" trick you've
discovered it doesn't do what you really want either, so you'll be
motivated to figure out why something like this does <grin>:

      parameter (m=50,n=50)
      integer a(m,n)
      do i = 1, m
         do j = 1, n
            a(i,j) = i + j
         end do
      end do   
      do i = 1, m
         write(6,99) i,(a(i,j),j=1,n)
      end do
 99   format('Row ',i4,': ',9i7/(10x,9i7))
      end

This gives the "nice" output:

Row    1:       2      3      4      5      6      7      8      9     10
               11     12     13     14     15     16     17     18     19
               20     21     22     23     24     25     26     27     28
               29     30     31     32     33     34     35     36     37
               38     39     40     41     42     43     44     45     46
               47     48     49     50     51
Row    2:       3      4      5      6      7      8      9     10     11
               12     13     14     15     16     17     18     19     20
               21     22     23     24     25     26     27     28     29
               30     31     32     33     34     35     36     37     38
               39     40     41     42     43     44     45     46     47
               48     49     50     51     52

... output for 47 rows deleted ...

Row   50:      51     52     53     54     55     56     57     58     59
               60     61     62     63     64     65     66     67     68
               69     70     71     72     73     74     75     76     77
               78     79     80     81     82     83     84     85     86
               87     88     89     90     91     92     93     94     95
               96     97     98     99    100

The tricks here are to study the std to see how a "/" can be used to
force a linefeed (= new "record"), and especially how nested parentheses
in a format can be used to force a *part* of the format to be rescanned
an arbitrary number of times.  The latter trick is the crucial one here,
and allows the format to work the way you want whether the rows happen
to have one or a million elements.

unfortunately-the-rules-are-hard-to-explain-in-a-few-lines-so-your-best-
   bet-really-is-to-study-the-standard-ly y'rs  - tim


Tim Peters   Kendall Square Research Corp
tim@ksr.com,  ksr!tim@harvard.harvard.edu

mac@cis.ksu.edu (Myron A. Calhoun) (04/24/91)

moshkovi@sanandreas.ecn.purdue.edu (Gennady Moshkovich) writes:
>buckland@cheddar.ucs.ubc.ca (Tony Buckland) writes:
>>moshkovi@eurotunnel.ecn.purdue.edu (Gennady Moshkovich) writes:
>>>100 format(10i8)
>             ^^^^
>	     THIS IS THE PROBLEM !!

>Just look at the code, and you will see where the problem is.
>You can't print with this code more then _10_ elements in a row.

And who told you that?  FORTRAN FORMAT processor automatically starts
a new line when it reaches the last closing parentheses.

>I can repeat again !!!.  I don't know beforehand how many
>elements I have, I can have 3, or I can have 300, but the
>output MUST look nice.

You must have some awfully wide printers!  For the 132-column printers
I get to use, 16 8-digit numbers across is all that "look nice".

So just write 100 format(16i8) AND THAT IS ALL YOU'LL EVER NEED
(for 8-digit numbers)!
--Myron.
--
# Myron A. Calhoun, Ph.D. E.E.; Associate Professor   (913) 539-4448 home
#  INTERNET:  mac@cis.ksu.edu (129.130.10.2)                532-6350 work
#      UUCP:  ...rutgers!ksuvax1!harry!mac                  532-7353 fax
# AT&T Mail:  attmail!ksuvax1!mac                   W0PBV @ K0VAY.KS.USA.NA

moshkovi@sanandreas.ecn.purdue.edu (Gennady Moshkovich) (04/25/91)

mac@cis.ksu.edu (Myron A. Calhoun) writes:

>moshkovi@sanandreas.ecn.purdue.edu (Gennady Moshkovich) writes:
>>buckland@cheddar.ucs.ubc.ca (Tony Buckland) writes:
>>>moshkovi@eurotunnel.ecn.purdue.edu (Gennady Moshkovich) writes:
>>>>100 format(10i8)
>>             ^^^^
>>	     THIS IS THE PROBLEM !!

>>Just look at the code, and you will see where the problem is.
>>You can't print with this code more then _10_ elements in a row.

>And who told you that?  FORTRAN FORMAT processor automatically starts
>a new line when it reaches the last closing parentheses.

>>I can repeat again !!!.  I don't know beforehand how many
>>elements I have, I can have 3, or I can have 300, but the
>>output MUST look nice.

>You must have some awfully wide printers!  For the 132-column printers
>I get to use, 16 8-digit numbers across is all that "look nice".

>So just write 100 format(16i8) AND THAT IS ALL YOU'LL EVER NEED
>(for 8-digit numbers)!
>--Myron.

Well, don't whant to start another flame war.  I agree, this
will work.  BUT, BUT, BUT isn't the way of flexible labels
looks much better and flexible. (note, this is not a question)


Gene

--
Gennady Moshkovich          
Purdue University
Department of Civil Engineering
moshkovi@ecn.purdue.edu

buckland@cheddar.ucs.ubc.ca (Tony Buckland) (04/25/91)

In article <moshkovi.672444244@sanandreas.ecn.purdue.edu> moshkovi@sanandreas.ecn.purdue.edu (Gennady Moshkovich) writes:
>buckland@cheddar.ucs.ubc.ca (Tony Buckland) writes:
>>In article <moshkovi.672431251@eurotunnel.ecn.purdue.edu> moshkovi@eurotunnel.ecn.purdue.edu (Gennady Moshkovich) writes:
>>>100 format(10i8)
>	     THIS IS THE PROBLEM !!
>Just look at the code, and you will see where the problem is.
>You can't print with this code more then _10_ elements in a row.

 My apologies, I was concentrating on the DO statement.
 If I were using this technique myself - and in fact I often
 have, I would write the FORMAT so as to use up the maximum
 line length on the intended output device.  If that device
 is a terminal, then 10I8 is a quite reasonable choice.  The
 only way you could get more on one line would be if you knew
 the values were low enough in absolute terms to fit into a
 narrower field than I8.  If they were arbitrary fullword
 integers, I8 wouldn't in fact be safe.  For -2**31, you need
 I11 (7 per terminal line), or I12 if you leave a column blank
 for readability (6 per terminal line).  To do *that*, you
 have to know that your matrix line length is no more than 6,
 or 7, or, in the case of the 10I8 format, 8.

jeyadev@rocksanne.uucp (Surendar Jeyadev) (04/25/91)

In article <13617@ur-cc.UUCP> rbr4@uhura.cc.rochester.edu (Roland Roberts) writes:
>Depending on what you mean by ``nice,'' there are easier ways that
>using a subroutine call.  The technique I have often used (both on IBM
>VS Fortran and DEC Fortran) is to take advantage of the format
>statement having an implied loop, i.e., the last grouping is repeated
>until there is no data.  For example:
>
>       do 1 i = 1,n
>         write(6,100) (matrix(i,j),j=1,m)
>     1 continue
>   100 format(1x,10i8,:/,(11x,10i8,:/))
>
>On both VS Fortran and DEC Fortran, the `:' says ......

If one is using VAX Fortran, why not use

       do 1 i = 1,n
         write(6,'(<m>(3x,i8)') (matrix(i,j),j=1,m)
     1 continue

I have found the <repeat_count> useful. VAX and Sun Fortran allow
a variable to be used, but you have to enclose it in angled brackets.

--
Surendar Jeyadev     Internet: jeyadev.wbst128@xerox.com

Most books say that the sun is a star. But, somehow, it knows how to
change back to a sun in the morning.  (5th grader)

rbe@yrloc.ipsa.reuter.COM (Robert Bernecky) (04/25/91)

I have been observing this thread with some amusement. Fortran 90
(91, 9x?) picked up a number of circa 1970 ideas from APL, but missed
a lot of the newer (and older) concepts of the language. For a more
detailed tirade, see "Fortran 90 Arrays" in the January 1991 SIGPLAN
Notices.

However, the way to display the value of MATRIX in APL, assuming you don't
know up front how big it is, is:

      MATRIX

If you DO know how big it is, you can use this alternate form:
      MATRIX

(SOrry, folks, but I couldn't resist)  8~}

Bob


Robert Bernecky      rbe@yrloc.ipsa.reuter.com  bernecky@itrchq.itrc.on.ca 
Snake Island Research Inc  (416) 368-6944   FAX: (416) 360-4694 
18 Fifth Street, Ward's Island
Toronto, Ontario M5J 2B9 
Canada

jlg@cochiti.lanl.gov (Jim Giles) (04/26/91)

In article <moshkovi.672444244@sanandreas.ecn.purdue.edu>, moshkovi@sanandreas.ecn.purdue.edu (Gennady Moshkovich) writes:
|> [...]
|> Just look at the code, and you will see where the problem is.
|> You can't print with this code more then _10_ elements in a row.
|> I can repeat again !!!.  I don't know beforehand how many
|> elements I have, I can have 3, or I can have 300, but the
|> output MUST look nice.

Why not use the following:

      do 10 i=1,n
         write(6,100) (matrix(i,j),j=1,m)
 10   continue
      ...
100   format('0 row:',i9,(t16,8i8))

This program will produce the following output:

 row:        1   1234567 2345678 3456789 ...
                 8765432 1232244 ...
                 ...
                 1223343 ...

 row:        2   ...

In other words, each row will be printed out (using as many lines
as required), then a blank line and the start of the next row.
Further, the elements of each row will be printed 8 per line
starting in column 16 (the last line will only contain mod(m,8)
elements).  The only dependence on the sizes of n and m is the
format specifier for row number (i9) - which limits you to a
billion rows.  Pick a smaller or larger field depending on the
maximum characteristics of your program (a billion rows is a lot,
you may want to make the field smaller so that there's not so
much space after the colon).

J. Giles

khb@chiba.Eng.Sun.COM (Keith Bierman fpgroup) (04/26/91)

In article <1991Apr25.160306.8065@yrloc.ipsa.reuter.COM> rbe@yrloc.ipsa.reuter.COM (Robert Bernecky) writes:

>...I have been observing this thread with some amusement. Fortran 90
   (91, 9x?) picked up a number of circa 1970 ideas from APL, but missed
   a lot of the newer (and older) concepts of the language. For a more
   detailed tirade, see "Fortran 90 Arrays" in the January 1991 SIGPLAN
   Notices.

To the best of my knowledge this is quite wrong (as was the tirade in
the Notices). X3J3 was not particularly interested in replicating APL.
No attempt was made to do so. 
--
----------------------------------------------------------------
Keith H. Bierman    keith.bierman@Sun.COM| khb@chiba.Eng.Sun.COM
SMI 2550 Garcia 12-33			 | (415 336 2648)   
    Mountain View, CA 94043

greg@monu6.cc.monash.edu.au (Greg Coldicutt) (04/30/91)

In article <788@rocksanne.WRC.XEROX.COM> jeyadev@sita.UUCP (Surendar Jeyadev) writes:
>In article <13617@ur-cc.UUCP> rbr4@uhura.cc.rochester.edu (Roland Roberts) writes:
>> i.e., the last grouping is repeated
>>until there is no data.  For example:
>>
>>       do 1 i = 1,n
>>         write(6,100) (matrix(i,j),j=1,m)
>>     1 continue
>>   100 format(1x,10i8,:/,(11x,10i8,:/))
>>
>>On both VS Fortran and DEC Fortran, the `:' says ......
>
>If one is using VAX Fortran, why not use
>
>       do 1 i = 1,n
>         write(6,'(<m>(3x,i8)') (matrix(i,j),j=1,m)
>     1 continue
>
>I have found the <repeat_count> useful. VAX and Sun Fortran allow
>a variable to be used, but you have to enclose it in angled brackets.
>
My initial response was the "why not use" wasn't serious, but, since it
may have been:

Apart from the fact that the (11x,10i8:  implies 90 columns of output
(compared with 80 columns for 1x,10i8:), which may exceed the screen width,
the earlier suggestion is standard and portable.
The VAX and Sun option is an unnecessary non-standard, less portable, less
flexible alternative (eg it can readily exceed screen and printer width, and
will require hardware wrap-around to work, and it does not indent subsequent
lines of long rows to avoid ambiguity such as is it two rows of 8, or
1 long row of 16 numbers?).

I've spent hundreds of hours "converting" programs with non-standard Fortran
code that could easily have been written using standard code.  Why include
non-standard code unless there is a demonstrable need?