Silverfrost Forums

Welcome to our forums

Splash window - how to do it?

19 Oct 2017 11:48 #20506

Hi, I am trying to display a splash image (JPG) for a few seconds before the main application window/menus/etc are built and displayed, and then the splash window should be automagically destroyed.

I tried the following, but it doesn't work the way I want:

! Exibe imagem de abertura
rslt=winio@('%ww[topmost,naked]%im[abertura]%lw',janela_abertura)

! Início
nome_arquivo = ' '
call inicializar()

! destroi tela de abertura
call sleep@(5)
janela_abertura=0
call window_update@(janela_abertura)

! Montagem da interface gráfica
rslt = winio@('%ww%ca[FluxoViz]&')
rslt = winio@('%dr&',le_arquivo_largado)
rslt = winio@('%ft[Arquivo FLX][*.flx]&')
...
rslt = winio@('%`^gr[black,rgb_colours]&',painel%xmax-painel%xmin+1,painel%ymax-painel%ymin+1, &
			id_painel_de_situacao,painel_de_situacao)
...

Any ideas how to solve this problem?

Cheers Rudnei

20 Oct 2017 3:53 #20509

This may be more than you want, but this is how I do mine.

The callback 'button1' returns a -1.

	SUBROUTINE SPLASH_SCREEN (SPLASH_WINDOW,SPLASH_HANDLE,TITLE_LINE,LICENSED_TO,&
                CUSTOMER_NAME,BUILD_DATE_TIME,appfolder,current_dir,sw_version,delay_time)
	USE MSWIN
	INTEGER*4 SPLASH_WINDOW,SPLASH_HANDLE
	CHARACTER*(*) TITLE_LINE,LICENSED_TO,CUSTOMER_NAME,BUILD_DATE_TIME,appfolder,current_dir,sw_version
	INTEGER*4 K
	integer,external:: button1
	real*8:: delay_time
	k = winio@('%ww[no_edge,no_caption,no_maxbox,no_minbox,topmost]&') ! 
	k = winio@('%fn[Times New Roman]%bf%ts&',2.0d0)
	k = winio@('%bg[red]%tc[yellow]&')
	k = winio@('%cn%bm[cjdbitmap]&') ! included as a resource IN THE MAIN
	k = winio@('%ff%ob[invisible]&') ! go past the end of the BMP and start a box which is invisible
	k = winio@('%cn%ws%nl&',TRIM(TITLE_LINE)) ! centered
	k = winio@('%cn(C) Copyright 1985-2016%nl%cnCJD Software%nl&') ! centered
	k = winio@('%cnAll Rights Reserved%nl&') ! centered
	k = winio@('%ts&',1.5d0) ! scale the following font items
	k = winio@('%cn%ws%nl&',trim(licensed_to))  ! centered
	k = winio@('%cn%ws%nl&',trim(customer_name))
	k = winio@('%cn%ws%nl&',trim(build_date_time))
!	k = winio@('%fn[Courier New]%bf&')
	k = winio@('%cnSW %ws Installed: %ws%nl&',trim(sw_version),trim(appfolder))
	k = winio@('%cnRunning in: %ws%nl&',trim(current_dir))
	k = winio@('%cb&') ! close the box
	k = winio@('%hw&',splash_window)
	k = winio@('%lw&',splash_handle) ! return the handle so we can close this in a few seconds
	k = winio@('%dl&',delay_time,button1) ! this closes the window after the delay timer expires
	k = winio@(' ')
	return
	end
20 Oct 2017 3:55 #20510

Rudnei,

Missed hyphen in the code was the reason of crash of rocket in 1962 which in present prices had cost around 1 B dollars.

This time you just missed a dot after number 5. 😃

Yea, even 50 year later Fortran still sucks at this.

Compiler diagnostics with /debug /check also missed that despite this is the best diagnostical compiler. Probably there still exist some tricky compiler switch to catch that error but definitely those two must do that. I'd consider it an error.

This is why we need more users. With critical thinking.

Reproducer:

i=winio@('%ww[topmost,naked]%im[abertura]%es%lw',ilw) 
call sleep@(5.)  ! not sleep@(5)
ilw  = 0 
call window_update@(ilw) 
End

Resources
abertura   image orig.png
20 Oct 2017 4:53 #20517

This is the operative code for my splash screen generator:

       COMMON  /SPLASH/       ICTRL
       COMMON  /Spl_Hnd/      iSplash_Wnd, jSplash_Wnd, NoInc
       ! various things in between
       ICTRL = 1
       NoInc = 255
       Delta_Time = 2.0D0/255.0D0
       IB=WINIO@('%ww[no_border,no_caption,no_maxminbox,topmost,'//     &
     &           'toolwindow,no_frame]&')
       IB=WINIO@('%^bm[SPLASHBMP]&','EXIT')
       IB=WINIO@('%lc%hw&', iSplash_Wnd, jSplash_Wnd) 
       IB=WINIO@('%dl%lw',Delta_Time,KOUNTER,ictrl)

       RETURN
       END

KOUNTER is an INTEGER FUNCTION that counts down changing the splash opacity so it fades away:

       INTEGER FUNCTION KOUNTER()
C      --------------------------
       COMMON  /SPLASH/       ICTRL
       COMMON  /Spl_Hnd/      iSplash_Wnd, jSplash_Wnd, NoInc
       LOGICAL IA, SetWindowOpacity
       IF (NoInc .GE. 1) THEN
           IA=SetWindowOpacity(jSplash_Wnd, NoInc)
           NoInc = NoInc-1
           KOUNTER=1
           ELSE
           ICTRL = 0
           KOUNTER=0
           ENDIF
       RETURN
       END

and because this predates the incorporation of transparency in Clearwin+, it employs the code posted by another contributor (modified a tiny bit by me):

      logical function SetWindowOpacity(hWnd, alpha) 
C     ----------------------------------------------
!     Set opacity level for a window (call after window creation) - 
!     automatically sets appropriate extended style and sets opacity  
!     from 0 (transparent) to 255 (no transparency). 

      use mswin 
      integer, parameter:: WS_EX_LAYERED = Z'00080000' 
      integer, parameter:: LWA_COLORKEY  = Z'00000001' 
      integer, parameter:: LWA_ALPHA     = Z'00000002' 
      STDCALL SetLayeredWindowAttributes 'SetLayeredWindowAttributes' 
     &         (VAL, VAL, VAL, VAL) : LOGICAL*4 
      integer, intent(in):: hWnd 
      integer, intent(in):: alpha 

      integer:: attrib, i 
    
  ! Get current window attributes to ensure WS_EX_LAYERED extended style is set 
      attrib = GetWindowLong(hWnd, GWL_EXSTYLE) 
      if (IAND(attrib,WS_EX_LAYERED) /= WS_EX_LAYERED) then 
         i = SetWindowLong(hWnd, GWL_EXSTYLE, IOR(attrib,WS_EX_LAYERED)) 
         end if 

  ! Set layered window alpha value 
      SetWindowOpacity = SetLayeredWindowAttributes
     &           (hWnd, 0, CORE1(LOC(alpha)), LWA_ALPHA) 
      end function SetWindowOpacity

The persistence of vision effect makes dark splashes appear to be visible some time after they have actually disappeared.

It is also useful to kill off the splash if the main application window has fully loaded, especially if it loads with a pre-existing 'document', which is done by setting the window handle (ictrl in this case) to zero.

Eddie

20 Oct 2017 7:00 #20518

Eddie I used your nice method in some my 32 bit codes but when converting to 64 bit I got a problem with Windows API function and there was no time to investigate substitution. Have you solved this?

20 Oct 2017 8:08 #20519

Many thanks to all who replied! Cheers Rudnei

21 Oct 2017 12:42 #20521

Dan,

From version 7.00, Paul added opacity setting to Clearwin+ (see the ENH file, item 354 and following) thus:

   INTEGER FUNCTION SET_OPACITY@(Opacity)
   INTEGER opacity

which affect the current drawing surface, and presumably work in 64 bit mode.

The routine affects the current drawing surface, so if your splash screen is the only surface in view, presumably its opacity is set. What I am doing, however, is to build my main application screen 'behind' the splash, and I worked out that I would probably have to combine SELECT_GRAPHICS_OBJECT@ with the splash display handle before using SET_OPACITY@, and for a variety of reasons I didn't modify my code to suit.

One of the reasons being that I don't use 64-bit, having no need, and a second reason being that in maintaining that application for academic use I'm using a pre 64-bit licensed version of FTN95 (v6.10, actually).

In the countdown routine I would expect to replace

           IA=SetWindowOpacity(jSplash_Wnd, NoInc)

with

           IB = SELECT_GRAPHICS_WINDOW@(jSplash_Wnd)
           IA = SET_OPACITY@ (NoInc)

(and dump the custom routine) but I haven't got that far yet. It would avoid the call in the custom opacity setting routine and rely instead on how Paul implemented it.

Eddie

21 Oct 2017 12:55 #20522

In my eagerness, I suggested something that doesn't work, sorry. I suspect that there are limitations in the call to SetLayeredWindowAttributes when used in 64 bit mode.

Eddie

22 Oct 2017 5:03 #20529

Still thanks for tries, Eddie

/* Meantime another way of making splash screen I posted in 64bit section based on OpenGL. It works on all other computers but mine main PC last two days.

Please login to reply.