I've also seen the bar stop updating. And I have a way around it that worked for me. BTW, in my case, the bar stopped updating, but the underlying code ran to completion.
In my case, if I prevent the updates from occurring too fast (i.e. increase the time between successive calls), the bar works perfectly. I always call the routine, but look at the elapsed time between subsequent calls, and ignore updating the window too quickly.
In my case, I update every second (a convenient value for my application). Also, for my application, I close the status bar window at the end of it usefulness, so I know the code is still running through to the end, regardless of what the bar status actually says.
I have run across other cases where, if you do things too fast, the ClearWin+ functions don't have enough time to 'clean up' from the previous call, and it can cause a crash.
I've included the code I use here. The first call (NCUR=0) initializes the window, and NCUR=-1 to close it. YMMV.
SUBROUTINE STATUS_BAR(text,NMIN,NMAX,NCUR)
INTEGER NMIN,NMAX,NCUR
character*(*) text ! for labelling the status bar
REAL*8 FILL
real*8 fill_last,fill_this
INTEGER*4 WINDOW_HANDLE,RGB@,ICOLOR
INTEGER*4 WINDOW_CLOSURE
COMMON/STATBAR/WINDOW_HANDLE,WINDOW_CLOSURE
C --- PREVIOUSLY NOT DECLARED
INTEGER K
C --- INITIALIZE THE STATUS BAR WHEN NCUR = 0
IF(NCUR.EQ.0) THEN
ICOLOR = RGB@(0,255,0)
FILL = 0.0
WINDOW_HANDLE = 0
WINDOW_CLOSURE = 0
k = winio@('%ca@&',text)
K=WINIO@('%nl%40br[no_border,left_right,percentage]&',
$ FILL,ICOLOR)
K=WINIO@('%hw&',WINDOW_HANDLE)
K=WINIO@('%lw',WINDOW_CLOSURE)
call dclock(fill_last)
ELSE
IF(NCUR .EQ. -1) THEN
WINDOW_CLOSURE = 0
CALL WINDOW_UPDATE@(WINDOW_CLOSURE)
CALL SLEEP1@(1.)
RETURN
ENDIF
C --- NCUR IS >0
call dclock(fill_this)
if(fill_this-fill_last.le.1.d0) return
fill_last = fill_this
FILL=DBLE(NCUR-nmin)/DBLE(NMAX-NMIN)
IF(FILL.GT.1.0D0)FILL = 1.D0
if(fill.lt.0.0d0) fill = 0.0d0
CALL WINDOW_UPDATE@(FILL)
call sleep1@(1./15.)
ENDIF
RETURN
END
The final SLEEP1@ call was added to make sure the window has released all its resources just in case that another Status Bar is immediately created.