!!!!!!!!!!!!!!!! Program cdoutput.f90 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! ! ! program cdoutput ! ! ! Purpose: To read in GENPLOT file of pressure and viscous drag ! coefficients and write a new GENPLOT file of the total ! drag coefficient. It also computes the average tototal ! drag coefficient for the last 2000 iterations. ! ! (This is program is intended to be used for simulations ! where either no Global Newton subiterations were specified, or ! 3 Global Newton subiterations were specified. It can be ! easily modified to handle other amounts of subiterations.) ! ! Written by Julianne Dudek ! ! Variables: ! ! cdavg average total drag coefficient ! cdp pressure drag coefficient ! cdv viscous drag coefficent ! cdt total drag coefficient ! xit iteration number ! integer :: icount, ncurv, np1 real, dimension(:), allocatable:: xit, cdp, cdv, cdt real, dimension(:), allocatable:: dum1, dum2 real fac, cdavg character (len=60) :: mtitle, ptitle, xaxtit, yaxtit, ctit, dumc read(5,*) mtitle read(5,*) ptitle read(5,*) xaxtit read(5,*) yaxtit read(5,*) ncurv read(5,*) ctit read(5,*) np1 write(6,*) mtitle write(6,*) ptitle write(6,*) xaxtit write(6,*) yaxtit write(6,*) ncurv write(6,*) ctit write(6,*) np1 allocate( xit(np1) ) allocate( cdp(np1) ) allocate( cdv(np1) ) allocate( cdt(np1) ) allocate( dum1(np1) ) allocate( dum2(np1) ) !-----Read pressure drag coefficient do i = 1, np1 if (i .gt. np1) exit read (5,*) xit(i), cdp(i) end do !------Skip over lift and z-forces do icount = 1, 2 do i = 1, 6 read(5,*) dumc end do do i = 1, np1 read(5,*) dum1(i), dum2(i) end do end do !------Read viscous drag coefficient, compute and write total drag to ! GENPLOT file do i = 1, 6 read(5,*) dumc end do !-------If using Global Newton with 3 subiterations, then divide ! iteration by 3, so iteration count is number from 1 to 10000 by 1's. if (xit(1) .gt. 2) then fac = 3.0 else fac = 1.0 end if cdavg = 0.0 icount = 0.0 do i = 1, np1 read(5,*) xit(i), cdv(i) cdt(i) = cdp(i) + cdv(i) write(6,*) xit(i)/fac, cdt(i) if (xit(i)/fac .gt. 7999.) then cdavg = cdavg + cdt(i) icount = icount + 1 end if end do cdavg = cdavg/real(icount) write(6,*) 'cdavg = ', cdavg deallocate( xit ) deallocate( cdp ) deallocate( cdv ) deallocate( cdt ) deallocate( dum1 ) deallocate( dum2 ) stop end program cdoutput