File: u_rebar.sru
Size: 9151
Date: Mon, 07 Apr 2008 21:32:43 +0200
$PBExportHeader$u_rebar.sru
$PBExportComments$PB friendly MS Rebar
forward
global type u_rebar from u_base
end type
type st_message from statictext within u_rebar
end type
type st_1 from statictext within u_rebar
end type
end forward

global type u_rebar from u_base
integer width = 645
integer height = 104
boolean border = true
event resize pbm_size
st_message st_message
st_1 st_1
end type
global u_rebar u_rebar

type prototypes
FUNCTION boolean InitCommonControlsEx( Ref INITCOMMONCONTROLS LPINITCOMMONCONTROLS) Library "comctl32.dll" alias for "InitCommonControlsEx;Ansi"
SUBROUTINE GetNMHDR( ref NMHDR d, long s, long l ) library 'kernel32.dll' alias for "RtlMoveMemory"
end prototypes

type variables
Private:
long NMHDR_SIZE
long RebarHandle
CONSTANT string REBAR_SVC = "n_svc_rebar"
boolean ib_refresh
end variables

forward prototypes
public function long of_getrebarhandle ()
public subroutine of_insertband (readonly long al_chilhwnd, readonly string as_bandtext, readonly integer ai_minsize, readonly boolean ab_newline, boolean ab_gripper)
public subroutine of_insertband (readonly long al_childhwnd)
public subroutine of_insertband (readonly long al_childhwnd, readonly boolean ab_newline)
public subroutine of_insertband (readonly long al_childhwnd, readonly boolean ab_newline, readonly boolean ab_gripper)
public subroutine of_insertband (readonly long al_childhwnd, readonly string as_bandtext)
public subroutine of_insertband (readonly long al_childhwnd, readonly string as_bandtext, readonly boolean ab_newline)
public subroutine of_insertband (readonly long al_childhwnd, readonly string as_bandtext, readonly boolean ab_newline, readonly boolean ab_gripper)
protected subroutine of_init (ref n_svc_mgr anv_svc)
public subroutine of_refresh ()
public subroutine of_resize (long al_width, long al_height)
public subroutine of_showband (readonly integer ai_index, readonly boolean ab_show)
public subroutine of_minimizeband (readonly integer ai_index, readonly boolean ab_minimize)
public subroutine of_maximizeband (readonly integer ai_index, readonly boolean ab_maximize)
public subroutine of_setbandminimumsize (readonly integer ai_index, readonly long al_width)
public subroutine of_setbandchild (readonly integer ai_index, readonly long al_hwnd)
public function long of_getbandwidth (readonly integer ai_index)
end prototypes

event resize;IF ib_refresh THEN RETURN

IF RebarHandle <> 0 THEN
   newwidth = this.width
   of_Resize(newwidth, newheight)
END IF
end event

public function long of_getrebarhandle ();RETURN RebarHandle
end function

public subroutine of_insertband (readonly long al_chilhwnd, readonly string as_bandtext, readonly integer ai_minsize, readonly boolean ab_newline, boolean ab_gripper);n_svc_mgr lnv_svc
n_svc_rebar lnv_rebar

lnv_svc.of_LoadSvc(lnv_rebar, REBAR_SVC)
lnv_rebar.of_InsertBand(lnv_svc, &
                  RebarHandle, &
                  al_chilhwnd, &
                  as_bandtext, &
                  ai_minsize, &
                  ab_newline, &
                  ab_gripper)
end subroutine

public subroutine of_insertband (readonly long al_childhwnd);of_InsertBand(al_childhwnd, CString.EMPTY, 0, FALSE, TRUE)
end subroutine

public subroutine of_insertband (readonly long al_childhwnd, readonly boolean ab_newline);of_InsertBand(al_childhwnd, CString.EMPTY, 0, ab_newline, TRUE)
end subroutine

public subroutine of_insertband (readonly long al_childhwnd, readonly boolean ab_newline, readonly boolean ab_gripper);of_InsertBand(al_childhwnd, CString.EMPTY, 0, ab_newline, ab_gripper)
end subroutine

public subroutine of_insertband (readonly long al_childhwnd, readonly string as_bandtext);of_InsertBand(al_childhwnd, as_bandtext, 0, FALSE, TRUE)
end subroutine

public subroutine of_insertband (readonly long al_childhwnd, readonly string as_bandtext, readonly boolean ab_newline);of_InsertBand(al_childhwnd, as_bandtext, 0, ab_newline, TRUE)
end subroutine

public subroutine of_insertband (readonly long al_childhwnd, readonly string as_bandtext, readonly boolean ab_newline, readonly boolean ab_gripper);of_InsertBand(al_childhwnd, as_bandtext, 0, ab_newline, ab_gripper)
end subroutine

protected subroutine of_init (ref n_svc_mgr anv_svc);INITCOMMONCONTROLS lICC

// Set the size of the structure (2 longs = 8 bytes)
lICC.dwSize = 2 * 4
lICC.dwICC  = CWin32.ICC_COOL_CLASSES

// Initialise the common controls
InitCommonControlsEx(lICC)

//let's get the size of NHMDR
n_svc_sizeof lnv_size
NMHDR lstr

anv_svc.of_LoadSvc(lnv_size, CSvc.SIZEOF)
NMHDR_SIZE = lnv_size.SizeOf(lstr)
end subroutine

public subroutine of_refresh ();ib_refresh = TRUE
this.SetRedraw(FALSE)
this.width += 4
this.width -= 4
this.SetRedraw(TRUE)
ib_refresh = FALSE
end subroutine

public subroutine of_resize (long al_width, long al_height);n_svc_rebar lnv_rebar
n_svc_mgr lnv_svc
long ll_rebarheight

lnv_svc.of_LoadSvc(lnv_rebar, REBAR_SVC)

lnv_rebar.of_Resize(RebarHandle, al_width, al_height)
ll_rebarheight = lnv_rebar.of_GetRebarHeight(lnv_svc, RebarHandle, TRUE)
IF ll_rebarheight <> al_height THEN
   this.height = ll_rebarheight
   //update resize attrib
   str_resize lstr
   rect rc
   
   lstr = of_GetResizeAttrib()
   rc = lstr.bounds
   rc.bottom = ll_rebarheight
   lstr.bounds = rc
   of_SetResizeAttrib(lstr)
   
   //fire resize for parent
   parent.TriggerEvent("resize")
END IF
end subroutine

public subroutine of_showband (readonly integer ai_index, readonly boolean ab_show);n_svc_mgr lnv_svc
n_svc_rebar lnv_r

lnv_svc.of_LoadSvc(lnv_r, REBAR_SVC)
lnv_r.of_ShowBand(RebarHandle, ai_index, ab_show)
end subroutine

public subroutine of_minimizeband (readonly integer ai_index, readonly boolean ab_minimize);n_svc_mgr lnv_svc
n_svc_rebar lnv_r

lnv_svc.of_LoadSvc(lnv_r, REBAR_SVC)
lnv_r.of_MinimizeBand(RebarHandle, ai_index, ab_minimize)
end subroutine

public subroutine of_maximizeband (readonly integer ai_index, readonly boolean ab_maximize);n_svc_mgr lnv_svc
n_svc_rebar lnv_r

lnv_svc.of_LoadSvc(lnv_r, REBAR_SVC)
lnv_r.of_MaximizeBand(RebarHandle, ai_index, ab_maximize)
end subroutine

public subroutine of_setbandminimumsize (readonly integer ai_index, readonly long al_width);n_svc_mgr lnv_svc
n_svc_rebar lnv_r

lnv_svc.of_LoadSvc(lnv_r, REBAR_SVC)
lnv_r.of_setbandminimumsize(lnv_svc, RebarHandle, ai_index, al_width)
end subroutine

public subroutine of_setbandchild (readonly integer ai_index, readonly long al_hwnd);n_svc_mgr lnv_svc
n_svc_rebar lnv_r

lnv_svc.of_LoadSvc(lnv_r, REBAR_SVC)
lnv_r.of_SetBandChild(lnv_svc, RebarHandle, ai_index, al_hwnd)
end subroutine

public function long of_getbandwidth (readonly integer ai_index);n_svc_mgr lnv_svc
n_svc_rebar lnv_r

lnv_svc.of_LoadSvc(lnv_r, REBAR_SVC)

RETURN lnv_r.of_GetBandWidth(RebarHandle, ai_index)
end function

on u_rebar.create
int iCurrent
call super::create
this.st_message=create st_message
this.st_1=create st_1
iCurrent=UpperBound(this.Control)
this.Control[iCurrent+1]=this.st_message
this.Control[iCurrent+2]=this.st_1
end on

on u_rebar.destroy
call super::destroy
destroy(this.st_message)
destroy(this.st_1)
end on

event destructor;call super::destructor;n_svc_mgr lnv_svc
n_svc_rebar lnv_rebar

lnv_svc.of_LoadSvc(lnv_rebar, REBAR_SVC)
lnv_rebar.of_Destroy(RebarHandle)
end event

event ke_preopen;call super::ke_preopen;st_1.Visible = FALSE
this.Border = FALSE

n_svc_mgr lnv_svc
n_svc_rebar lnv_rebar
n_svc_resource lnv_res
n_svc_isempty lnv_check
n_svc_sizeof lnv_size
long llh, ll_style, ll_exstyle, ll_himl
powerobject lpo_parent

lnv_svc.of_LoadSvc(lnv_rebar, REBAR_SVC)

//init rebar
of_Init(lnv_svc)

//create the rebar
RebarHandle = lnv_rebar.of_Create(lnv_svc, &
                  this, &
                  this.width, &
                  this.height)

//set notification parent
lnv_rebar.of_SetParent(rebarHandle, st_message)
end event

type st_message from statictext within u_rebar
event notify pbm_notify
boolean visible = false
integer width = 69
integer height = 52
integer textsize = -8
integer weight = 400
fontcharset fontcharset = ansi!
fontpitch fontpitch = variable!
fontfamily fontfamily = swiss!
string facename = "Tahoma"
long textcolor = 33554432
long backcolor = 67108864
boolean focusrectangle = false
end type

event notify;long ll
NMHDR lstr_ret
n_svc_rebar lnv_rebar
n_svc_mgr lnv_svc

IF wparam = 200 THEN
   lnv_svc.of_LoadSvc(lnv_rebar, REBAR_SVC)
   
   GetNMHDR(lstr_ret, lparam, NMHDR_SIZE)
   CHOOSE CASE lstr_ret.code
      CASE /*-833,*/ /*lnv_rebar.RBN_LAYOUTCHANGED, */ -//lnv_rebar.RBN_HEIGHTCHANGE
         of_Resize(parent.width, parent.height)
         parent.SetRedraw(TRUE)
   END CHOOSE
END IF
end event

type st_1 from statictext within u_rebar
integer x = 128
integer y = 16
integer width = 370
integer height = 52
integer textsize = -8
integer weight = 700
fontcharset fontcharset = ansi!
fontpitch fontpitch = variable!
fontfamily fontfamily = swiss!
string facename = "Tahoma"
long textcolor = 33554432
long backcolor = 67108864
string text = "Rebar Control"
boolean focusrectangle = false
end type