| 
			
				|  | forums.silverfrost.com Welcome to the Silverfrost forums
 
 |  
 
	
		| View previous topic :: View next topic |  
		| Author | Message |  
		| silicondale 
 
 
 Joined: 15 Mar 2007
 Posts: 252
 Location: Matlock, Derbyshire, UK
 
 | 
			
				|  Posted: Wed Jan 15, 2014 7:07 pm    Post subject: Rotated characters invisible when first plotted |   |  
				| 
 |  
				| ... that is, until you pass another window over them to force a repaint. 
 I'm using DRAW_CHARACTERS@. For angle of 0 = horizontal there's no problem, they plot just fine. For any other angle, any part of any character that is outside the positive (upper right) quadrant is invisible. Calling PERFORM_GRAPHICS_UPDATE@ doesn't help. I have to physically move another window over the graphics window and away again to force a repaint and then the invisible parts of characters become visible.
 
 Code snippets:
 
 
 
 
	  | Code: |  
	  | DATA TEXTM /'MIDDLE'/
 ...
 UMID = (UMIN + UMAX)*0.5
 VMID = (VMIN + VMAX)*0.5
 HT = 40.0
 ANGLE = -90.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = -75.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = -60.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = -45.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = -30.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = -15.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 0.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 15.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 30.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 45.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 60.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 75.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 90.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 
 --------------------------------------------
 SUBROUTINE VIG_TEXT (U,V,TEXTM,H,A,IRGB)
 USE MSWIN
 USE CLRWIN
 IMPLICIT DOUBLE PRECISION (A-H,O-Z)
 COMMON /VIG/ IXAX,IYAX,IGO,USIZE,VSIZE,UMIN,UMAX,VMIN,VMAX,
 1             XUSC,YVSC,XMIN,YMIN,XMAX,YMAX
 CHARACTER*(*) TEXTM
 DOUBLE PRECISION U,V,H,A,AA,VV,H
 C
 C  WRITE OUT TEXT STRING
 C  H = HEIGHT IN PIXELS
 C  A = CLOCKWISE ROTATION ANGLE
 C
 CALL SELECT_FONT@('Modern')
 IH = H
 IW = (IH+1)/2
 CALL SIZE_IN_PIXELS@ (IH,IW)
 CALL BOLD_FONT@ (1)
 AA = -A
 CALL ROTATE_FONT@ (AA)
 IU = U
 VV = VSIZE - V
 IV = VV
 CALL DRAW_CHARACTERS@ (TEXTM,IU,IV,IRGB)
 CALL PERFORM_GRAPHICS_UPDATE@ ()
 RETURN
 END
 
 |  
 As originally plotted it looks like this -
 
 
   
 (the little command window, generated elsewhere in the program, was over the bottom right part of the text until I moved it away). I then moved the command window across to the left, like this:
 
   which revealed a little more of the text. I then swiped it over the whole area to reveal all of the text:
 
   
 In fact any other window from the same or a different program will do the job - I just used this little one for convenience.
 
 How can I reveal all of the text without having to obscure the graphics window first? Is there a more powerful version of PERFORM_GRAPHICS_UPDATE@ that actually does perform a full update - or a CW+ function that forces a WM_PAINT ?
 
 ps edit #1.... I have found that a Minimise followed by a Restore will force a repaint of the whole window, making all the text visible. So if no Paint, are there any CW+ functions to do the Minimise and Restore ?
 |  |  
		| Back to top |  |  
		|  |  
		| PaulLaidler Site Admin
 
 
 Joined: 21 Feb 2005
 Posts: 8280
 Location: Salford, UK
 
 | 
			
				|  Posted: Fri Jan 17, 2014 5:24 pm    Post subject: |   |  
				| 
 |  
				| Can you post a sample program for me to try out ? It looks like you are not using GDI+ (e.g. set_smoothing_mode@) so this is an old set of routines that ought to work.
 |  |  
		| Back to top |  |  
		|  |  
		| DanRRight 
 
 
 Joined: 10 Mar 2008
 Posts: 2943
 Location: South Pole, Antarctica
 
 | 
			
				|  Posted: Fri Jan 17, 2014 5:34 pm    Post subject: |   |  
				| 
 |  
				| This is own developers' example with addition of rotated and not rotated text at the end. You can see that usual not rotated text is displayed OK while rotated 90 degrees one not. 
 
 
 
	  | Code: |  
	  | winapp program main
 include <windows.ins>
 !use clrwin
 c_external nARGB@              '__nargb'(VAL,VAL,VAL,VAL):integer
 c_external SET_SMOOTHING_MODE@ '__set_smoothing_mode'(VAL):integer
 integer  cb
 external cb
 
 ix=450;iy=200
 
 !  iw = winio@("%pv%^gr[black,full_mouse_input,box_selection,user_resize,rgb_colours,popup]&",ix,iy,cb)
 !  iw = winio@("%pv%gr[black,full_mouse_input,box_selection,rgb_colours,popup]&",ix,iy,cb)
 iw = winio@('%ww%pv%^gr[gray,user_resize]&',ix,iy,cb)
 iw = winio@("%ac[esc]&",'exit')
 iw = winio@("%lw",ilw)
 
 call draw_line@(5,158,440,188,         RGB@(0,200,0))
 
 
 call select_font@("Arial")
 call size_in_pixels@(16,0)
 call italic_font@(1)
 call bold_font@(1)
 call draw_characters@("No antiAlias Smoothing", 165, 200, RGB@(0,200,0))
 
 call set_line_width@(8)
 call set_line_style@(PS_GEOMETRIC+PS_ENDCAP_SQUARE)
 call draw_line@(5,4,5,108,  nARGB@(255,0,0,255))
 call draw_line@(25,4,25,108,  RGB@(255,0,0))
 call draw_line@(5,10,25,10, nARGB@(255,0,255,0))
 call draw_line@(5,30,25,30, nARGB@(112,0,255,0))
 call draw_line@(5,50,25,50,   RGB@(255,0,255))
 call set_line_style@(PS_GEOMETRIC+PS_ENDCAP_FLAT)
 call set_line_width@(16)
 iw = set_smoothing_mode@(5)        !SmoothingModeAntiAlias8x8
 call draw_line@(50,4,150,104,         RGB@(255,0,0))
 call draw_line@(150,4,50,104,       nARGB@(192,0,0,255))
 call draw_ellipse@(225,60,50,50,            nARGB@(255,0,255,0))
 call draw_filled_ellipse@(225,60,50,50,     nARGB@(192,255,0,0))
 call draw_rectangle@(320,10,420,110,        nARGB@(255,255,0,0))
 call draw_filled_rectangle@(320,10,420,110, nARGB@(192,0,255,0))
 call set_line_width@(1)
 call draw_line@(5,154,440,184,         RGB@(255,0,0))
 
 call select_font@("Arial")
 call size_in_pixels@(16,0)
 call italic_font@(1)
 call bold_font@(1)
 call draw_characters@("AntiAlias Smoothing", 165, 156, RGB@(255,0,0,255))
 
 !        CALL rotate_font@(90.0D0)
 !     call SELECT_FONT@( Fontname1(iFontRTGxaxisR))
 
 iw = set_smoothing_mode@(5)        !SmoothingModeAntiAlias8x8
 call select_font@("Arial")
 call scale_font@(1.9d0)
 call BOLD_FONT@( 1 )
 call ROTATE_FONT@(0.d0)
 call draw_characters@("Not Rotated", 185, 96, RGB@(0,0,255,255))
 call ROTATE_FONT@(90.d0)
 call draw_characters@("Rotated", 185, 96, RGB@(0,0,255,255))
 
 !     call DRAW_POINT@(144,44,RGB@(0,255,255,255))
 !     call set_pixel@(144,54,RGB@(0,255,255,255))
 END
 
 INTEGER FUNCTION cb()
 include <windows.ins>
 call set_line_width@(7)
 call draw_line@ (1,1,450,200,         RGB@(0,0,0))
 call draw_line@ (1,200,450,1,         RGB@(0,0,0))
 call set_line_width@(1)
 cb=1
 end function cb
 |  
 Last edited by DanRRight on Sat Jan 18, 2014 9:43 am; edited 1 time in total
 |  |  
		| Back to top |  |  
		|  |  
		| silicondale 
 
 
 Joined: 15 Mar 2007
 Posts: 252
 Location: Matlock, Derbyshire, UK
 
 | 
			
				|  Posted: Fri Jan 17, 2014 5:53 pm    Post subject: |   |  
				| 
 |  
				| Hi, Paul - thanks for the reply. I've extracted the code into a little test program - and of course it works perfectly. (Also tried Dan's program and that also works just fine). 
 But of course the same coding in the full program still doesn't display all the rotated text - I have to obscure and reveal it, or minimise and restore, in order to see it.
 
 
 
 
	  | Code: |  
	  | PROGRAM TEXTDEMO
 use mswin
 use clrwin
 IMPLICIT DOUBLE PRECISION (A-H,O-Z)
 CHARACTER*8 TEXTM
 C-------------------------------------------------------------
 COMMON /VIG/ IXAX,IYAX,IGO,USIZE,VSIZE,UMIN,UMAX,VMIN,VMAX,
 1             XUSC,YVSC,XMIN,YMIN,XMAX,YMAX
 COMMON /VIGHANDLES/ IGHANDLE,IWHANDLE,ICTRL,ICTRL2
 C-------------------------------------------------------------
 INTEGER CALLBACK
 EXTERNAL CALLBACK
 
 DATA TEXTM /'TEST1234'/
 
 USIZE = 800.0
 VSIZE = 800.0
 UMAX=800.0
 VMAX=800.0
 UMIN=0.0
 VMIN=0.0
 
 NXPIX = USIZE
 NYPIX = VSIZE
 IGHANDLE = 1
 IWHANDLE = 1
 ICTRL = 0
 ix = 20
 iy = 20
 I = WINIO@ ('%ww&')
 I = WINIO@ ('%`^gr[white,rgb_colours,FULL_MOUSE_INPUT]&',
 1    nxpix+1,nypix+1,ighandle,CALLBACK)
 I = WINIO@ ('%sp&', ix, iy)
 I = WINIO@ ('%^bt[OK]&','EXIT')
 I = WINIO@ ('%hw%lw',iwhandle,ictrl)
 call SELECT_GRAPHICS_OBJECT@( IGHANDLE )
 call PERFORM_GRAPHICS_UPDATE@()
 
 UMID = (UMIN + UMAX)*0.5
 VMID = (VMIN + VMAX)*0.5
 
 IRGB = RGB@(0,0,0)
 HT = 40.0
 ANGLE = -90.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = -75.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = -60.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = -45.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = -30.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = -15.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 0.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 15.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 30.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 45.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 60.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 75.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 90.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 STOP
 END
 
 SUBROUTINE VIG_TEXT (U,V,TEXTM,H,A,IRGB)
 USE MSWIN
 USE CLRWIN
 IMPLICIT DOUBLE PRECISION (A-H,O-Z)
 C-------------------------------------------------------------
 COMMON /VIG/ IXAX,IYAX,IGO,USIZE,VSIZE,UMIN,UMAX,VMIN,VMAX,
 1             XUSC,YVSC,XMIN,YMIN,XMAX,YMAX
 COMMON /VIGHANDLES/ IGHANDLE,IWHANDLE,ICTRL,ICTRL2
 C-------------------------------------------------------------
 
 CHARACTER*(*) TEXTM
 DOUBLE PRECISION U,V,H,A,AA,VV,H
 C
 C  WRITE OUT TEXT STRING USING SALFORD TEXT OUTPUT
 C  H = HEIGHT IN PIXELS
 C  A = CLOCKWISE ROTATION ANGLE
 C
 CALL SELECT_FONT@('Modern')
 IH = H
 IW = (IH+1)/2
 CALL SIZE_IN_PIXELS@(IH,IW)
 CALL BOLD_FONT@ (1)
 AA = -A
 CALL ROTATE_FONT@ (AA)
 IU = U
 VV = VSIZE - V
 IV = VV
 
 CALL DRAW_CHARACTERS@ (TEXTM,IU,IV,IRGB)
 
 RETURN
 END
 
 INTEGER FUNCTION CALLBACK ()
 CALLBACK = 2
 END
 
 |  |  |  
		| Back to top |  |  
		|  |  
		| DanRRight 
 
 
 Joined: 10 Mar 2008
 Posts: 2943
 Location: South Pole, Antarctica
 
 | 
			
				|  Posted: Fri Jan 17, 2014 8:54 pm    Post subject: |   |  
				| 
 |  
				| silicondale I'm confused - does my example show rotated font or not? I do not see it rotated 90%. Libraries are from Jan 4
 
 This your example works fine but has no GDI+ font smoothing
 |  |  
		| Back to top |  |  
		|  |  
		| silicondale 
 
 
 Joined: 15 Mar 2007
 Posts: 252
 Location: Matlock, Derbyshire, UK
 
 | 
			
				|  Posted: Fri Jan 17, 2014 10:08 pm    Post subject: |   |  
				| 
 |  
				| Dan - yes, it shows rotated with no problem, though I did have to comment out your set_smoothing_mode@ calls as these came up as an undefined reference, and also had to replace your nARGB@ calls by RGB@. (What on earth is nARGB@ ?) 
 My salflibc libraries are from 14 March 2013.
 
 -Steve
 |  |  
		| Back to top |  |  
		|  |  
		| DanRRight 
 
 
 Joined: 10 Mar 2008
 Posts: 2943
 Location: South Pole, Antarctica
 
 | 
			
				|  Posted: Sat Jan 18, 2014 12:29 am    Post subject: |   |  
				| 
 |  
				| So smoothing does NOT work actually with rotation since  by commenting the line you deleted it  .  Also my speculation is that these older libraries have no such features yet. Or smoothing was not your primary interest in this post? |  |  
		| Back to top |  |  
		|  |  
		| PaulLaidler Site Admin
 
 
 Joined: 21 Feb 2005
 Posts: 8280
 Location: Salford, UK
 
 | 
			
				|  Posted: Sat Jan 18, 2014 8:43 am    Post subject: |   |  
				| 
 |  
				| Steve Despite the fact that your short program works OK, I could still use it to demonstrate how to get a refresh after the smaller windows has been moved over the larger window.
 
 Your sample should use the same window styles for the two windows (%ww %sy %lw) as in the practical application. Then I should be able to add code to force a refresh and you will be able to adapt your application accordingly.
 |  |  
		| Back to top |  |  
		|  |  
		| silicondale 
 
 
 Joined: 15 Mar 2007
 Posts: 252
 Location: Matlock, Derbyshire, UK
 
 | 
			
				|  Posted: Sat Jan 18, 2014 8:55 am    Post subject: |   |  
				| 
 |  
				| Dan - Quite so - smoothing is the least of my concerns. When I get the program working properly, then I can start to think about smoothing! 
 I need to use 90-degree rotated text to annotate the y axis, and it doesn't display until I drag another window over it, or I minimise and restore. When I found it didn't display, I tried other rotation angles and found the problem was more general for any non-zero rotation as shown in the original post.
 
 Odd thing is that the little demo program I wrote, using just the same coding, seems to work perfectly.
 
 If I can do an unconditional re-paint this would fix the problem - though of course still doesn't explain why it happens in the first place. I'd prefer to do it through a CW+ call rather than having to call the Windows WM_PAINT directly (can't be too difficult, but not sure how to do it).
 
 Paul - many thanks. The demo program does use the same windows style as the full program. I think the only possibly significant difference is that the full program writes a coloured background using DRAW_FILLED_RECTANGLE@ before doing any other plotting. The refresh after moving the small window over the large one isn't the problem- it happens automatically. The problem is that I have to do it! An unconditional refresh forced from the program should achieve the same result.
 
 - Steve
 
 ps - edit #1 - just commented out the filled rectangle code and it works perfectly. Then I added back in the filled rectangle code, and it works nearly perfectly (there's one piece of rotated text that doesn't display, and needs a refresh to show it, but other rotated text displays correctly without needing a refresh). Seems to me that maybe it's a memory problem. However, not specific to one computer - just installed and ran on a different computer with exactly the same results.
 
 pps - edit #2. A thought. For the outer filled rectangle, I use
 CALL DRAW_FILLED_RECTANGLE@ (IX1,IY1,IX2,IY2,IRGB) with IX2,IY2 set at the size defined for the %gr that opened the graphics area, but IX1 and IY1 are both zero. Should they actually be set to 1 rather than 0? Would zero arguments possibly result in plotting outside the graphics area with potentially unpredictable memory problems?
 |  |  
		| Back to top |  |  
		|  |  
		| JohnCampbell 
 
 
 Joined: 16 Feb 2006
 Posts: 2621
 Location: Sydney
 
 | 
			
				|  Posted: Mon Jan 20, 2014 12:05 am    Post subject: |   |  
				| 
 |  
				| Steve, 
 I think that the correct values are:
 IX1 = 0
 IX2 = nx-1
 IY1 = 0
 IY2 = ny-1
 However, the values you used might still work.
 There is an option to set limits on the active window for drawing, but I can't recall the name. This might help.
 
 John
 |  |  
		| Back to top |  |  
		|  |  
		| silicondale 
 
 
 Joined: 15 Mar 2007
 Posts: 252
 Location: Matlock, Derbyshire, UK
 
 | 
			
				|  Posted: Mon Jan 20, 2014 11:12 am    Post subject: |   |  
				| 
 |  
				| Thanks, John. However, I tried each variant (lower bound 0 or 1, upper bound n or n-1), but problem remains the same. Some of the rotated text displays, some doesn't, until a forced refresh. |  |  
		| Back to top |  |  
		|  |  
		| JohnCampbell 
 
 
 Joined: 16 Feb 2006
 Posts: 2621
 Location: Sydney
 
 | 
			
				|  Posted: Tue Jan 21, 2014 2:50 am    Post subject: |   |  
				| 
 |  
				| Steve, 
 There is a difference between the full window and the %gr drawing window, depending on what %ww options you use. The following code identifies some of these dimensions.
 
 
 
	  | Code: |  
	  | subroutine set_real_screen_size !
 !    Sets the dimensions for the %gr screen, including menu and border
 !
 INCLUDE 'crtcom.ins'
 include <clearwin.ins>
 include <JDC_menu.ins>
 !
 s_width        = clearwin_info@ ('SCREEN_WIDTH')    ! full screen width
 s_depth        = clearwin_info@ ('SCREEN_DEPTH')    ! full screen depth
 !        if (crt_trace) write (98,9000) s_width, s_depth
 !
 !    %gr graphics window size : account for menu
 w_width        = clearwin_info@ ('GRAPHICS_WIDTH')  ! %gr graphics width
 w_depth        = clearwin_info@ ('GRAPHICS_DEPTH')  ! %gr graphics depth
 !
 !    graphics TEK window : account for border
 nxpix          = w_width - 12
 nypix          = w_depth - 36
 !
 !    real units for tek units to pixel conversion
 X_MAX_WIN      = nxpix - 1
 Y_MAX_WIN      = nypix - 1
 X_MIN_WIN      = 6
 Y_MIN_WIN      = 6
 ASPECT_WIN     = Y_MAX_WIN/X_MAX_WIN
 !
 !    define virtual screen for GRAPHLIB (TEK units)
 X_MAX_TEK      = 1024*4
 Y_MAX_TEK      = X_MAX_TEK*ASPECT_WIN
 !
 !    define home position
 X_POS_WIN      = X_MIN_WIN
 Y_POS_WIN      = Y_MIN_WIN
 !
 !    reset Z buffering status
 direct_colour  = .false.
 z_buffer_limit = -NXPIX           ! z buffering not initialised
 z_colour_limit = -NXPIX
 ZXMIN          = 0                ! z buffering limits
 ZXMAX          = NXPIX
 ZYMIN          = 0
 ZYMAX          = NYPIX
 !
 z_time         = 0
 z_itime        = 0
 !
 !9000  FORMAT ('<FULL_SCREEN>  s_width=',I0,' s_depth=',I0)
 
 end subroutine set_real_screen_size
 
 |  
 for %gr, I use
 
 
 
	  | Code: |  
	  | ! include 'build.ins'
 caption     ='Graphics Suite : FEA MODEL : Build date '//build_stamp
 i = winio@ ('%ca@&', caption)
 !
 i = winio@ ('%ww[no_border]&')
 !
 i = winio@ ('%sc&', plot_setup_func)                  ! call saplot setup function
 i = winio@ ('%pv&')                                   ! allow resize of %gr
 !
 i = winio@ ('%`^gr[grey, user_resize, rgb_colours, full_mouse_input, user_surface]&',  &
 1024, 768,          &   ! screen dimension when not maximised
 ptr_RGB_Address,    &   ! screen address for rgb surface ( not sure of the order ? )
 w_handle,           &   ! ` window handle defined in crtstart
 mouse_back_func)        ! ^ call back function for mouse and resize
 !
 i = winio@ ('%mg&', WM_MOUSEWHEEL, OnMouseWheel)      ! mousewheel response
 !
 call Graphics_Menus
 !
 i = winio@ ('%hw', hwnd)                              ! return the handle of the current window.
 
 |  |  |  
		| Back to top |  |  
		|  |  
		| PaulLaidler Site Admin
 
 
 Joined: 21 Feb 2005
 Posts: 8280
 Location: Salford, UK
 
 | 
			
				|  Posted: Tue Jan 21, 2014 11:28 am    Post subject: |   |  
				| 
 |  
				| This may do the trick. I have added a small command window to illustrate the idea... 
 
 
 
	  | Code: |  
	  | winapp PROGRAM TEXTDEMO
 use mswin
 use clrwin
 IMPLICIT DOUBLE PRECISION (A-H,O-Z)
 CHARACTER*8 TEXTM
 C-------------------------------------------------------------
 COMMON /VIG/ IXAX,IYAX,IGO,USIZE,VSIZE,UMIN,UMAX,VMIN,VMAX,
 1             XUSC,YVSC,XMIN,YMIN,XMAX,YMAX
 COMMON /VIGHANDLES/ IGHANDLE,IWHANDLE,ICTRL,ICTRL2
 C-------------------------------------------------------------
 INTEGER CALLBACK,mv_cb
 EXTERNAL CALLBACK,mv_cb
 
 DATA TEXTM /'TEST1234'/
 
 USIZE = 600.0
 VSIZE = 600.0
 UMAX=600.0
 VMAX=600.0
 UMIN=0.0
 VMIN=0.0
 
 NXPIX = USIZE
 NYPIX = VSIZE
 IGHANDLE = 1
 C     IWHANDLE = 1
 ICTRL = 0
 ix = 20
 iy = 20
 I = WINIO@ ('%ww&')
 I = WINIO@ ('%`^gr[white,rgb_colours,FULL_MOUSE_INPUT]&',
 1    nxpix+1,nypix+1,ighandle,CALLBACK)
 I = WINIO@ ('%sp&', ix, iy)
 I = WINIO@ ('%^bt[OK]&','EXIT')
 I = WINIO@ ('%hw%lw',iwhandle,ictrl)
 call SELECT_GRAPHICS_OBJECT@( IGHANDLE )
 call PERFORM_GRAPHICS_UPDATE@()
 
 UMID = (UMIN + UMAX)*0.5
 VMID = (VMIN + VMAX)*0.5
 
 IRGB = RGB@(0,0,0)
 HT = 40.0
 ANGLE = -90.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = -75.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = -60.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = -45.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = -30.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = -15.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 0.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 15.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 30.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 45.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 60.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 75.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 ANGLE = 90.0
 CALL VIG_TEXT (UMID,VMID,TEXTM,HT,ANGLE,IRGB)
 i = winio@("%mv&",mv_cb)
 i = winio@("OK")
 STOP
 END
 
 SUBROUTINE VIG_TEXT (U,V,TEXTM,H,A,IRGB)
 USE MSWIN
 USE CLRWIN
 IMPLICIT DOUBLE PRECISION (A-H,O-Z)
 C-------------------------------------------------------------
 COMMON /VIG/ IXAX,IYAX,IGO,USIZE,VSIZE,UMIN,UMAX,VMIN,VMAX,
 1             XUSC,YVSC,XMIN,YMIN,XMAX,YMAX
 COMMON /VIGHANDLES/ IGHANDLE,IWHANDLE,ICTRL,ICTRL2
 C-------------------------------------------------------------
 
 CHARACTER*(*) TEXTM
 DOUBLE PRECISION U,V,H,A,AA,VV
 C
 C  WRITE OUT TEXT STRING USING SALFORD TEXT OUTPUT
 C  H = HEIGHT IN PIXELS
 C  A = CLOCKWISE ROTATION ANGLE
 C
 CALL SELECT_FONT@('Modern')
 IH = H
 IW = (IH+1)/2
 CALL SIZE_IN_PIXELS@(IH,IW)
 CALL BOLD_FONT@ (1)
 AA = -A
 CALL ROTATE_FONT@ (AA)
 IU = U
 VV = VSIZE - V
 IV = VV
 
 CALL DRAW_CHARACTERS@ (TEXTM,IU,IV,IRGB)
 
 RETURN
 END
 
 INTEGER FUNCTION CALLBACK ()
 CALLBACK = 2
 END
 
 INTEGER FUNCTION mv_cb ()
 use mswin
 COMMON /VIGHANDLES/ IGHANDLE,IWHANDLE,ICTRL,ICTRL2
 LOGICAL L
 L = InvalidateRect(iwhandle, core4(0), 1)
 mv_cb = 2
 END
 |  |  |  
		| Back to top |  |  
		|  |  
		| silicondale 
 
 
 Joined: 15 Mar 2007
 Posts: 252
 Location: Matlock, Derbyshire, UK
 
 | 
			
				|  Posted: Tue Jan 21, 2014 12:44 pm    Post subject: |   |  
				| 
 |  
				| John - Many thanks. I've already added the no_border option in %ww which makes the graphics look much nicer. 
 Paul - The InvalidateRect call seems to have done the trick. I've added it unconditionally after all the plotting calls, and the rotated text now displays properly without the user having to do anything. Thanks very much! I guess this is a native Windows call rather than CW+ as I can't find any mention in the documentation. Or maybe I'm just not looking in the right place. Anyway, it does fix the problem.
 
 -Steve
 |  |  
		| Back to top |  |  
		|  |  
		|  |  
  
	| 
 
 | 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
 
 |