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 

No Saturdays without devilry
Goto page 1, 2  Next
 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> ClearWin+
View previous topic :: View next topic  
Author Message
DanRRight



Joined: 10 Mar 2008
Posts: 2813
Location: South Pole, Antarctica

PostPosted: Sat Nov 27, 2021 2:27 pm    Post subject: No Saturdays without devilry Reply with quote

Code:
MODULE MOD1

    real*8 Wavelength_cm, sigma_WL, FWHM_cm, FWHM_s, Tau_WL
    integer k_Gauss_sigma, k_Gauss_tau
    REAL*8 aIntens_From_a0, a0_tmp1, EnergyInFocalSpot, EnergyInFocalSpotSimple
    integer :: k_Circular_pol_a0_tmp1=0

contains
!...........................

integer function cb_Pulse_dur_FWHM ()

parameter (nnn=2000)
real*8 yyy(0:nnn)
real*8 t0, tleft, tright

real*8 t_ip1, EnergyInFocalSpot, EnergyInFocalSpotSimple, aNormalizFact

if(sigma_wl.lt.1.e-10) goto 999
if(Tau_WL.lt.1.e-10)   goto 998

t0=tau_wl * Wavelength_cm/3e10
tend   = 10*t0  ! range of exponent
tmid   = 5*t0   ! position of top of expeonent

!... tau FWHM

yyy(0) = 0
tleft=0 ; tright =0
FWHM_s = 0
factGauss=2
if(k_Gauss_tau.eq.0) factGauss=1

do i=1,nnn
t = i*10*t0/nnn
yyy(i) = (exp(-(t-tmid)**2/(factGauss*t0**2)) )**2

if(yyy(i-1).le.0.5.and.yyy(i).gt.0.5) tleft=t
if(yyy(i-1).ge.0.5.and.yyy(i).lt.0.5) tright=t
!print*, i,yyy(i)
enddo

!write(*,'(1p,10e10.2)')(yyy(i),i=1,nnn)
FWHM_s = tright-tleft
print*, 'FWHM_s=', FWHM_s
call window_update@(FWHM_s)

!...............................
!... sigma FWHM
!...now t will be distance in cm

t0 = sigma_wl * Wavelength_cm
tend   = 10*t0  ! range of exponent
tmid   = 5*t0   ! position of top of exponent


yyy(0) = 0
tleft=0 ; tright =0

FWHM_cm= 0
factGauss=2.
if(k_Gauss_sigma.eq.0) factGauss=1.

  EnergyInFocalSpot = 0
  aNormalizFact = 0


dr = 10.*t0/nnn

  do i=1,nnn
  t=i*10.*t0/nnn
  yyy(i) = (exp(-(t-tmid)**2/(factGauss*t0**2)) )**2

  if(yyy(i-1).le.0.5.and.yyy(i).gt.0.5) tleft=t
  if(yyy(i-1).ge.0.5.and.yyy(i).lt.0.5) tright=t
  !print*, i,yyy(i)


!...laser energy

  if(t.lt.tmid) then
    t_ip1=(i+1)*10*t0/nnn
    EnergyInFocalSpot= EnergyInFocalSpot + yyy(i) * 3.1415*((t-tmid)**2-(t_ip1-tmid)**2)
    aNormalizFact= aNormalizFact + yyy(i) * dr
  endif


enddo

!write(*,'(1p,10e10.2)')(yyy(i),i=1,nnn)
FWHM_cm = tright-tleft
print*, 'FWHM_cm=', FWHM_cm
call window_update@(FWHM_cm)

aIntens_From_a0 = (a0_tmp1/(8.5e-10*Wavelength_cm*1e4+1.d-50))**2
coefLin = 1
if( k_Circular_pol_a0_tmp1.eq.1) coefLin=2

EnergyInFocalSpot = EnergyInFocalSpot * aIntens_From_a0 * FWHM_s * coefLin
EnergyInFocalSpotSimple = aIntens_From_a0 * FWHM_s * 3.1415*(FWHM_cm/2)**2 

call window_update@(EnergyInFocalSpot )
call window_update@(EnergyInFocalSpotSimple)
call window_update@(aIntens_From_a0 )

print*,'Energy  J, Norm=',EnergyInFocalSpot , aNormalizFact
print*,'Energy  J, simple estim=I*pi*r_fwhm^2=',EnergyInFocalSpotSimple

goto 1000   

!...errors
998 call sound@(1000,1)
Print*, 'beep: Tau is not set'
goto 1000
999 call sound@(1000,1)
Print*, 'beep: Sigma is not set'

1000 continue


cb_Pulse_dur_FWHM=2
end function

END MODULE MOD1


Last edited by DanRRight on Sun Nov 28, 2021 4:15 am; edited 2 times in total
Back to top
View user's profile Send private message
DanRRight



Joined: 10 Mar 2008
Posts: 2813
Location: South Pole, Antarctica

PostPosted: Sat Nov 27, 2021 2:28 pm    Post subject: Reply with quote

Code:
!-------------------------------------

PROGRAM AAA
use mod1

   k_Gauss_tau  = 0
   k_Gauss_sigma= 0
   Wavelength_cm = 1
   k_Exp2  = 1
   sigma_wl= 1
   FWHM_cm = 0
   FWHM_s  = 0
   Tau_WL  = 1
   a0_tmp1 = 1

        aIntens_From_a0         = 0
        EnergyInFocalSpot       = 0
        EnergyInFocalSpotSimple = 0


        i = winio@('%ww&')    

        i = winio@('%1tl&', 24)    

   i=winio@('%tc[red]Find pulse FWHM in sec from the normalized TAU and SIGMA %tc[black]%ff&')
   i=winio@('Wavelength, cm%ta%rf%ff&',Wavelength_cm)
   i=winio@('Tau in periods %ta%rf&',Tau_WL)
   i=winio@('  %rb[Gauss not exp(-t2/to2)]%ff&',k_Gauss_tau)

   i=winio@('Sigma in WL %ta%rf&',sigma_WL)
   i=winio@('  %rb[Gauss not exp(-t2/to2)]%ff&',k_Gauss_sigma)

   i=winio@('%cn%^tt[Run]%ff %ff&', cb_Pulse_dur_FWHM)

   i=winio@('Duration FWHM, s %ta%rf%ff&',FWHM_s)
   i=winio@('FocalWid FWHM,cm%ta%rf%ff&',FWHM_cm)

   i=winio@('a0 %ta%rf&',a0_tmp1)
   i=winio@('  %rb[Circular polar.]%ff&',k_Circular_pol_a0_tmp1)

   i=winio@('Intensity, W/cm2 %ta%rf%ff&',aIntens_From_a0)
   i=winio@('Energy, J %ta%rf%ff&',EnergyInFocalSpot)
   i=winio@('Energy, J, simple %ta%rf%ff&',EnergyInFocalSpotSimple) !   I*s_FWHM*tau_FWHM

        i = winio@('%1tl', 8)    

end


Just push Run. Why last two numbers (Energy) are not updated ??? They are not equal to zero, as you see they are additionally printed in DOS window.

What do you see?
Back to top
View user's profile Send private message
Kenneth_Smith



Joined: 18 May 2012
Posts: 697
Location: Hamilton, Lanarkshire, Scotland.

PostPosted: Sun Nov 28, 2021 3:29 pm    Post subject: Reply with quote

Definitely some devilry here Dan.

Changing the value returned by the call back to 1 rather than 2 does not help.

Printing the values immediately before the calls to window_update@ returns the expected (non-zero values).

Printing the values after the format window is closed returns their values as zero.

Running the code in the debugger never shows the local values take on any value other than zero.

A simpler example works as expected and does not display the problem.

So all I can really say is I am as puzzled as you are with this one…….. not really of very much help, I am afraid.
Back to top
View user's profile Send private message Visit poster's website
DanRRight



Joined: 10 Mar 2008
Posts: 2813
Location: South Pole, Antarctica

PostPosted: Mon Nov 29, 2021 10:22 am    Post subject: Reply with quote

Thanks Ken, for trying and confirming. Colleagues of mine say that i ones said "Who does not work on weekends does not work at all". I do not remember that but this is very possible. Because weekends are the most productive days on supercomputers - they are much less crowdy. But last couple decades this compiler punish me for work on Saturdays doing every time unbelievable trickeries Smile. Even if this sometimes shocks me deeply and cause loud swearing and yelling when it's 3-4-5 AM and i am not yet found the bug, I am actually not angry for it for that, it has done great things to me all this time. Smile.
Back to top
View user's profile Send private message
LitusSaxonicum



Joined: 23 Aug 2005
Posts: 2388
Location: Yateley, Hants, UK

PostPosted: Mon Nov 29, 2021 10:54 am    Post subject: Reply with quote

Dan,

I had a go, and sure, those boxes don't update.

It taught me one thing, and that was to stay content with COMMON and traditional program structures and formatting - I found it difficult to follow what you were doing.

Eddie
Back to top
View user's profile Send private message
mecej4



Joined: 31 Oct 2006
Posts: 1885

PostPosted: Mon Nov 29, 2021 11:46 am    Post subject: Reply with quote

Elementary, my dear Watson, I mean Dan!

You have, in the variable declarations in the module,
Code:
REAL*8 aIntens_From_a0, a0_tmp1, EnergyInFocalSpot, EnergyInFocalSpotSimple


Later, in the contained integer function cb_Pulse_dur_FWHM(), you re-declare the last two variables that I just named:
Code:
EnergyInFocalSpot, EnergyInFocalSpotSimple


These local variables make the host module variables with the same names stay out of scope. You calculate and assign values to these local variables. These assignments leave the module variables of the same name unchanged from their zero values. When you display the values of the module variables in the main program using ClearWin, you are displaying just the arbitrarily assigned zero values.

If you had left out the arbitrary initializations-to-zero, the /undef option could have helped you catch the error. The values shown would have been, instead of zero, -2.937E-306 (Z'8080808080808080'). [Aside: Clearwin does not recognize this value as 'Undefined']

You also made the bug harder to find by allowing implicit typing of variables.


Last edited by mecej4 on Mon Nov 29, 2021 7:33 pm; edited 1 time in total
Back to top
View user's profile Send private message
DanRRight



Joined: 10 Mar 2008
Posts: 2813
Location: South Pole, Antarctica

PostPosted: Mon Nov 29, 2021 1:07 pm    Post subject: Reply with quote

Great, Sherlock, i mean, mecej4. Your eagle eye catched this my error i did not intend to make, but made sometime at the middle of the night and then spent time till 6am because i did not believe my eyes i couldn't fix it. But shouldn't compiler to at least warn me about double declaration ????

Eddie, The compiler became so smart, that i less and less bother to write things correctly, i believe compiler will fix me for sure. It is like an old school teacher with the ruler or stick
And i also like COMMON. The structure of program in this case resembles LEGO blocks, where everything is there nearby inside the code, not 1 mile away in the headers of MODULES containing the city dump of all millions of variable declarations. This text i wrote above was not using COMMON, it was using MODULEs but I succeeded to extract if from large code because i just wrote it and remember where its parts were. And if Silverfrost eventually will make COMMON blocks allocatable (like SDBG64 seems already started to do that if i am not wrong?) then i will use them even more. This is because i often reuse the parts of the code for different purposes. With MODULES i gave up to do that. With COMMON you just take all the common blocks copying them into new place and you are done moving the code.


Last edited by DanRRight on Mon Nov 29, 2021 1:25 pm; edited 1 time in total
Back to top
View user's profile Send private message
mecej4



Joined: 31 Oct 2006
Posts: 1885

PostPosted: Mon Nov 29, 2021 1:24 pm    Post subject: Re: Reply with quote

DanRRight wrote:
... But shouldn't compiler to at least warn me ?


Perhaps it should. On the other hand, we often reuse lots of variables such as DO index variables I, J, K, ..., and having such variables in module scope and also local scope would cause so many warnings to be issued that we would start ignoring those warnings or resort to turning warnings off completely.

[Added 6 hours later] I attempted to trap the error caused by the unintended re-declarations, by generating cross-reference listings using the /xref option. That did not help. The compiler lists the two variables as if they are the same. (It even lists a "subroutine MOD1", when there is no such subroutine.) It is only by generating the EXP code listing that we can see that there are two distinct variables pairs. For instance, the module variable MOD1!ENERGYINFOCALSPOT is distinct from the local variable ENERGYINFOCALSPOT in the EXP listing.

Perhaps, the rules of the language make such errors difficult to detect and report. Local variables can have the same names as host variables, but not the same as those variables that are available from USE association. We do get warnings when our code attempts to violate the second part of that rule.

Another quibble about your code, which may not matter much: you use 3.1415, which is so close to π that it raises a red flag. If that is supposed to be Pi, 3.1416 would be better. If you really need double precision, you can declare:

Code:
real*8, parameter :: Pi = acos(-1d0)


and use the symbolic name Pi instead of the literal constant (four such locations in your code).


Last edited by mecej4 on Mon Nov 29, 2021 6:31 pm; edited 5 times in total
Back to top
View user's profile Send private message
DanRRight



Joined: 10 Mar 2008
Posts: 2813
Location: South Pole, Antarctica

PostPosted: Mon Nov 29, 2021 1:30 pm    Post subject: Reply with quote

Yes, i typically use pi = 4.d0* atan(1d0). Your pi looks even nicer Smile
Thanks again for the fix and discussion.

By the way, are you declaring i,j,k,l,m,n in every subroutine which uses MODULE where they also could be declared?

Compiler started recently check for double declarations inside the subroutines and in COMMON. May be still it is good idea to add this functionality in situations like in my example? Not doing that makes such errors hard to find.
Back to top
View user's profile Send private message
mecej4



Joined: 31 Oct 2006
Posts: 1885

PostPosted: Mon Nov 29, 2021 2:27 pm    Post subject: Reply with quote

It is not a good idea to make variables such as DO loop index variables available through COMMON or to put them into modules. What happens if a subroutine or function that is called inside a DO loop also has access to the DO index variable through COMMON or USE?

What makes COMMON error-prone (esp. in combination with implicit typing) is that it is not just the types or names of the variables contained in the COMMON block that matter. Instead, it is the offsets of the variables w.r.t. the base of the COMMON that are used at run time. Thus, with
Code:
COMMON /BLK/I,J,K,X,Y,Z


if X,Y,Z are implicitly typed REAL in one place and explicitly typed REAL*8 in another, we have a bug right away.

Since common blocks may be reused in different source files within a project, the compiler cannot detect mismatches unless it is being made to compile all the source files with one command. With separate compilation, the linker is the one that has to check blocks for consistency. Unfortunately, the linker can only check the block size, since it may not have any information available in the OBJ files regarding variable names.
Back to top
View user's profile Send private message
DanRRight



Joined: 10 Mar 2008
Posts: 2813
Location: South Pole, Antarctica

PostPosted: Tue Nov 30, 2021 6:38 am    Post subject: Reply with quote

I speculate if COMMON ever will be made allocatable, then its Fortran life will be extended and it will not be considered kind of obsolete. In this case i do not see the reason not to include checking of each variable in COMMON on the declared size and type by adding this information into OBJ files if developers will agree on standard for that. If structure of OBJ files is proprietary then they can do that right away.

Checking at LINK time on total size which FTN95 has is very nice and extremely useful feature. It was added long time ago to 32bit version and now exists with 64bit one too. A bit pity it does not tell which SUBROUTINE size mismatch takes place hence if your files have 100 subroutines then it is a problem for us slow humans.

I was also asking if add the functionality to FTN95 to check for user error like was discussed above in the beginning is worth doing? I do not put ijklmn into the COMMON, i even never declare them as integer, even more i usually do not use IMPLICIT NONE and hence do not have to declare anything besides arrays and TYPEs. So my question about ijklmn was related to this request for adding error checking functionality, particularly how annoying things may turn to IMPLICIT NONE people Smile. If yes, i'd even wanted it to be an error not a warning
Back to top
View user's profile Send private message
mecej4



Joined: 31 Oct 2006
Posts: 1885

PostPosted: Tue Nov 30, 2021 12:45 pm    Post subject: Re: Reply with quote

DanRRight wrote:
... i even never declare them as integer, even more i usually do not use IMPLICIT NONE and hence do not have to declare anything besides arrays and TYPEs

Well, to each his/her own, but note that practicing promiscuous typing may cause Acquired Implicit Double-precision Syndrome.

In your short program above, you have the variables
Code:
COEFLIN, DR, T, FACTGAUSS, TMID, TEND

implicitly typed REAL, yet you are using them in expressions that get evaluated and their values put into explicitly typed REAL*8 variables. If you take such liberties with your huge supercomputer code, and your supervisor comes to know, ... ?

Try compiling the code with /imp, and re-evaluate your choices.
Back to top
View user's profile Send private message
LitusSaxonicum



Joined: 23 Aug 2005
Posts: 2388
Location: Yateley, Hants, UK

PostPosted: Tue Nov 30, 2021 12:48 pm    Post subject: Reply with quote

Mecej4,

A great piece of detective work, but as Sherlock (I'm on first name terms) said to Inspector Gregory (with whom I'm not) that he found something because he knew it was there, or words to the same effect. (The Silver Blaze, if you want to look).

I certainly don't know the scoping rules with Modules, nor do I need them, as I never use them. I took one look a number of years ago, and it seemed to ride roughshod over custom and practice up to the point they were introduced. Dan, if he uses Modules, needs to know those rules.*

The downsides to COMMON that you cite also don't bother me, for at least 2 reasons: firstly, I don't use them in the way that you say causes problems, and secondly, it's somewhere that I would look when examining code written by someone else (or even by me, as to err is human, and divinity doesn't come into it).

Now who was the genius who once said that you can write Fortran in any language? (Don't tell me, it was a rhetorical question). It turns out that the Fortran Committee intends us to write all the other computer languages in Fortran!

Eddie

Hint for Dan: If you search the Fortran standard using the search terms 'Bell, book and candle' you may well be directed to 'Modules'. Apparently, this link is not available on Saturdays.
Back to top
View user's profile Send private message
DanRRight



Joined: 10 Mar 2008
Posts: 2813
Location: South Pole, Antarctica

PostPosted: Tue Nov 30, 2021 1:26 pm    Post subject: Reply with quote

Mecej4,
Things are that i am the supervisor Smile and for me there exist advantages for all these BYTE, integer*2, real/integer*4, real/integer*8 and real*10 which i miss a bit with 64bits. The only i do not like to use are integer*2 but have to since FTN95 has some legacy code with them - they are extremely error-prone.

Always using REAL*8 cost me if i alone generate several PB of data per year and usually very hesitant to delete most of it at least for several years. When memory will be cheap, caches large, the real*8 will become default for all compilers

When i was young my boss ones told me that the only he wanted to hear from me was some number was large or not. His words:"I do not like to hear about all these numerical problems and accuracies, because the only what we need to know is if the idea will work or not, and for that we need just to know the gain number is >1". And that is 1 bit accuracy most of supervisors brain operates. My real*4 brain is not yet that bad in comparison

Eddie,
I am still learning tricks of modules despite using them for the last 20 years, trying to like them. Currently we have no alternatives as the allocatables are a must and COMMON do not work with them. I reached the state when i do not like or hate MODULES. This is first time i got kick into the butt from modules specifically funny that all tough problems happened freaking always for me on Saturday. Hopefully Silverfrost will offer some fixes to this problem which i guess in some cases could be way more severe for the user
Back to top
View user's profile Send private message
mecej4



Joined: 31 Oct 2006
Posts: 1885

PostPosted: Tue Nov 30, 2021 4:22 pm    Post subject: Re: Reply with quote

DanRRight wrote:
Mecej4,
Things are that i am the supervisor :)


In that case, my condolences. Your situation reminded me of General Braxton Bragg (after whom Fort Bragg is named). This is from the Wikipedia article about him:

Bragg was a company commander at a frontier post where he also served as quartermaster. He submitted a requisition for supplies for his company, then as quartermaster declined to fill it. As company commander, he resubmitted the requisition, giving additional reasons for his requirements, but as the quartermaster he denied the request again. Realizing that he was at a personal impasse, he referred the matter to the post commandant, who exclaimed, "My God, Mr. Bragg, you have quarreled with every officer in the army, and now you are quarreling with yourself!"
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> ClearWin+ 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