Soft bodys with shape matching

Post your FreeBASIC source, examples, tips and tricks here. Please don’t post code without including an explanation.
Post Reply
h4tt3n
Posts: 698
Joined: Oct 22, 2005 21:12
Location: Denmark

Soft bodys with shape matching

Post by h4tt3n »

Hello folks,

For some time I've been tampering with an algorithm for simulating deformable, soft bodys which have a distinct shape they'll return to when not squeezed. Think wine gums, jellyfish, entrails, that sort of thing :-)
Here's an interactive doodle which shows the algo in action. It's still work in progress, and the code needs a serious cleanup, but it works. I think this could be used in a really cool game, but I'm sort-of stuck and I'd like your input.

If anyone's interested in understanding the physics behind this, I won't mind explaining it in more detail.

PS. you'll need the newest version of GLFW, otherwise just comment out these two function calls near the end of the code:

Code: Select all

glfwopenwindowhint(GLFW_FSAA_SAMPLES, 8)
glfwopenwindowhint(GLFW_WINDOW_NO_RESIZE, GL_TRUE)
Cheers,
Mike

Here's a direct download link

Here's the code sample:

Code: Select all

'******************************************************************************'
'
'		Combined rigid and soft body physics using Shape matching. 
'
'		Version 10d, January 7th 2011
'
'   Created by Michael "h4tt3n" Nissen, micha3l_niss3n@yahoo.dk
'
'		GLFW graphics version. All soft body global data are based on particle state vectors
'
'			- Just two trig calls per update, no sqr() calls
'			- Handles around 20.000 - 25.000 springs in real-time
'			- Conserves energy and linear/angular momentum
'			- Particle to rest position damped linear springs
'			- Particle to particle damped linear springs
'			- Optional area preserving pressure (not needed for mesh based bodies like girders ect.)
'
'		Todo-list:
'
'			- Individual k and d coefficient for each spring.
'			- clean up / simplify angular velocity calculation
'			- same spring struct for both types of springs?
'			- ability to prod soft bodys with mouse
'			- More than one set of rest positions (shape shifting)?
'			- Rest position influenced by external forces?
'
'		(Press esc to quit)
'
'******************************************************************************'

''	includes
#Include Once "GLFW.bi"
#Include Once "vec2.bi"

''	constants
Const As Integer 	FALSE 							= 0							''
Const As Integer 	TRUE  							= Not FALSE			''
Const As float		pi 									= 4*Atn(1)			''	pi
Const As float		dt 									= 0.01					''	timestep
Const As float		Grav_Acc 						= 3200					''	gravity
Const As Integer	Num_Rigid_Bodys			= 8							''	number of bodys
Const As Integer	ScrnWid							= 800						''	screen width
Const As Integer	ScrnHgt         		= 600						''	screen height
Const As float		fr									= 0.5						''	wall friction
Const As float 		Pick_MinDist				= 128						''	mouse pick distance
Const As float 		K_PointSpring_Max		= 0.1						''	particle to rest point spring max value
Const As float 		K_PointSpring_Min		= 0.1						''	particle to rest point spring min value
Const As float 		D_PointSpring_Max		= 0.1						''	particle to rest point damper max value
Const As float 		D_PointSpring_Min		= 0.01					''	particle to rest point damper min value
Const As float 		K_LinearSpring_Max	= 0.4						''	particle to particle spring max value
Const As float 		K_LinearSpring_Min	= 0.04					''	particle to particle spring min value
Const As float 		D_LinearSpring_Max	= 0.1						''	particle to particle damper max value
Const As float 		D_LinearSpring_Min	= 0.01					''	particle to particle damper min value
Const As float 		K_Pressure_Max			= 2.0						''	soft body pressure max value
Const As float 		K_Pressure_Min			= 0.0						''	soft body pressure min value

''	types
Type Rigid_Body_Mass_Type
  As vec2f Init_Psn
  As vec2f Soft_psn
  As vec2f Rest_Psn
  As vec2f vel
  As vec2f Frc
  As vec2f Com_Dst
End Type

Type Rigid_Body_Spring_Type
	As integ a, b
	As integ Rest_Length_Squared
End Type

Type Rigid_Body_Type
	As UByte r, g, b, a
  As Integer Num_Masses, num_springs
  As float Mass, Angle, Angular_Vel, Angular_Acc, Torque, moment_of_inertia, Area, Rest_Area, Angular_Momentum
  As float K_PointSpring, D_PointSpring, K_LinearSpring, D_LinearSpring, K_Pressure
  As vec2f Frc, Vel, Psn, Ang, NrmAng
  As Rigid_Body_Mass_Type Ptr Point_Mass
  As Rigid_Body_Spring_Type Ptr Spring
End Type

Type ScreenType
	
	Declare Function CreateScreen(w As Integer, h As Integer, r As Integer, g As Integer, _
		b As Integer, a As Integer, d As Integer, s As Integer, m As Integer) As Integer
	Declare Function DeleteScreen() As Integer
	
	As Integer wid
	As Integer Hgt
	As Integer Bpp
	
End Type

Type Mouse_Type
	As vec2i Psn, Psn_Old
	As integ Btn, Btn_Old, Whl, Whl_Old
End Type

Type Simulation_Type
	
	Declare Constructor
	Declare Destructor
	
	As ScreenType Scr
	As Mouse_Type Mouse
	As Rigid_Body_Type Ptr Body
	
	As float Temp_Dist, Picked_Rest_Dist
	As integ Pick_State, Picked_Body, Picked_Mass, Prod_State
	
	Declare Sub Run_Simulation()
	Declare Sub Init_Body()
	Declare Sub Kill_Body()
	Declare Sub GetData()
	Declare Sub SetInternalForces()
	Declare Sub SetExternalForces()
	Declare Sub SetPosition()
	Declare Sub SetVelocity()
	Declare Sub Integrate()
	Declare Sub Draw_Bodys()
	
End Type

''	run simulation
Scope: Dim As Simulation_Type Simulation: End Scope

''	constructors & destructors
Constructor Simulation_Type
	Init_Body()
	Scr.CreateScreen(ScrnWid, ScrnHgt, 8, 8, 8, 8, 0, 0, GLFW_window)
	Run_Simulation()
End Constructor

Destructor Simulation_Type
  Scr.DeleteScreen()
	Kill_Body()
End Destructor

''	subs & functions
Sub simulation_type.run_simulation()
	Do
	  Integrate()
	  Draw_Bodys()
	  'GLFWSleep(0.01)
	Loop While (not glfwgetkey(GLFW_key_esc) and glfwgetwindowparam(GLFW_opened))
End Sub

Sub simulation_type.init_body()
	
	''	this function creates a number of soft bodys
	
	Randomize Timer
  
  Body = Callocate(Num_Rigid_Bodys*SizeOf(Rigid_Body_Type))
  
  For i As Integer = 0 To Num_Rigid_Bodys-1
    With Body[i]
	    	
	    .R = 96 + Rnd * 128
	    .G = 96 + Rnd * 128
	    .B = 96 + Rnd * 128
	    
	    .K_PointSpring			= K_PointSpring_Min + (K_PointSpring_Max-K_PointSpring_Min) * Rnd
			.D_PointSpring			= D_PointSpring_Min + (D_PointSpring_Max-D_PointSpring_Min) * Rnd
			.K_LinearSpring			= K_LinearSpring_Min + (K_LinearSpring_Max-K_LinearSpring_Min) * Rnd
			.D_LinearSpring			= D_LinearSpring_Min + (D_LinearSpring_Max-D_LinearSpring_Min) * Rnd
			.K_Pressure					= K_Pressure_Min + (K_Pressure_Max-K_Pressure_Min) * Rnd
	    
	    Dim As float radius = 64 + Rnd * 16
	    
	    .Num_Masses 	= (2*pi*radius)/16
	    .Num_Springs	= .Num_Masses
	    
	    .Point_Mass 	= Callocate(.Num_Masses*SizeOf(Rigid_Body_Mass_Type))
	    .Spring 			= Callocate(.Num_SPrings*SizeOf(Rigid_Body_Spring_Type))
	    
	    .Psn = vec2f(scrnwid\2, scrnhgt\2)
	      
	    .vel.x = (Rnd-Rnd)*300
	    .vel.y = -300-Rnd*300
	    
	    .Angular_vel = (Rnd-Rnd)*16
	    
	    .Angle = Rnd*2*pi
	    .Ang = vec2f(Cos(.Angle), Sin(.Angle))
	    .NrmAng = Normal(.Ang)
	    
	    '' get rigid body mass
	    For i2 As Integer = 0 To .Num_Masses-1
	      With .Point_Mass[i2]
	        Body[i].Mass += 1
	      End With
	    Next
	    
	    Dim As float ecc = 0.5 + Rnd * 0.25
	    
	    ''	particle initial positions
	    For j As Integer = 0 To .Num_Masses-1
	    	Dim As float angle = j * ((2*pi)/.Num_Masses)
	      With .Point_Mass[j]
	      	Dim As float fuzz = (Rnd-Rnd)*6
	      	Dim As Integer r = radius + fuzz
				  .init_Psn.x = Cos(angle)*r
				  .init_Psn.y = Sin(angle)*r*ecc
	      End With
	    Next
	    
			''	get rigid body center of mass position
    	Dim As vec2f com_psn = vec2f(0, 0)
      For j As Integer = 0 To .Num_Masses-1
        com_psn += .Point_Mass[j].init_Psn
      Next
      com_psn /= Body[i].mass
      
      ''	adjust particle initial position
	    For j As Integer = 0 To .Num_Masses-1
				.Point_Mass[j].init_Psn -= com_psn
	    Next
		  
	    ''	set rotated position and soft position
	    For j As Integer = 0 To .Num_Masses-1
	      With .Point_Mass[j]
	      	.Rest_Psn = vec2f(Dot(.Init_Psn, Body[i].Ang), Dot(.Init_Psn, Body[i].NrmAng))
				  .soft_psn = Body[i].Psn+.Rest_psn
				  .vel = Body[i].vel - Body[i].angular_Vel * Normal(.Rest_psn)
	      End With
	    Next
	    
	    ''	set spring pointers
	    For j As Integer = 0 To .Num_Springs-1
	    	Dim As Integer k = (j+1) Mod .Num_Springs
	    	.spring[j].a = j
	    	.spring[j].b = k
	    Next
	    
	    ''	get spring rest length squared
	    For j As Integer = 0 To .Num_Springs-1
	    	Dim As vec2f Lng = .Point_Mass[.Spring[j].b].Rest_Psn-.Point_Mass[.Spring[j].a].Rest_Psn
	    	.spring[j].Rest_Length_Squared = magnitudesquared(Lng)
	    Next
	    
	  	''	get soft body rest area
	  	.Rest_Area = 0
	    For j As Integer = 0 To .Num_Masses-1
	    	Dim As Integer k = (j+1) Mod .Num_Masses
	      .Rest_Area += DotNormal(.Point_Mass[j].soft_psn, .Point_Mass[k].soft_psn)
	    Next
	    .Rest_Area *= 0.5
	    
	    .Area = .Rest_Area
      
    	''	distance to center of mass vector
      For i2 As Integer = 0 To .Num_Masses-1
        With .Point_Mass[i2]
					.Com_Dst = .Soft_Psn-Body[i].psn
        End With
      Next
      
    	''	moment of inertia
    	.Moment_Of_Inertia = 0
      For i2 As Integer = 0 To .Num_Masses-1
        With .Point_Mass[i2]
					Body[i].Moment_Of_Inertia += MagnitudeSquared(.Com_Dst)
        End With
      Next
      
      ''	angular momentum
      .angular_momentum  = 0
      for i2 as integer = 0 to .Num_Masses-1
      	Dim as vec2f Com_Vel = .Point_Mass[i2].Vel - .Vel
        Dim as float ang_vel = DotNormal(.Point_Mass[i2].Com_Dst, Com_Vel)
				.Angular_Momentum += ang_vel
      Next
		
    End With
  Next

End Sub

Sub simulation_type.SetInternalForces()
	
	''	this function sets all internal forces, ie. all forces that
	''	work inside the soft bodys.
	
	''	reset force & torque
  For i As Integer = 0 To Num_Rigid_Bodys-1
    With Body[i]
      .torque = 0
      .frc = vec2f(0, 0)
      For i2 As Integer = 0 To Body[i].Num_Masses-1
				.Point_Mass[i2].frc = vec2f(0, 0)
	    Next
    End With
  Next
  
  ''	damped springs
  For i As Integer = 0 To Num_Rigid_Bodys-1
  	With Body[i]
  		
  		''	set spring and damping value
	    Dim As float Kp = (1 / (dt*dt)) * .K_PointSpring
	    Dim As float Dp = (1 / dt) 		  * .D_PointSpring  	
	    Dim As float Kl = (1 / (dt*dt)) * .K_LinearSpring
	    Dim As float Dl = (1 / dt) 		  * .D_LinearSpring
	    
			''	damped spring between particle and rest position (zero length, so no need to rotate)
			For i2 As Integer = 0 To .Num_Masses-1
			
				Dim As vec2f rest_psn = .psn + .Point_Mass[i2].Rest_psn
				Dim As vec2f diff_psn = .Point_Mass[i2].Soft_Psn - rest_psn
				
				Dim As vec2f rest_vel = .vel - .angular_Vel * Normal(.Point_Mass[i2].Rest_psn)
				Dim As vec2f diff_vel =  .Point_Mass[i2].vel - rest_vel
				
				Dim As vec2f frc = -diff_psn*Kp - diff_Vel*Dp
				
				.Point_Mass[i2].frc += frc
				
			Next
	    
	    ''	damped spring between two particles
	  	For j As Integer = 0 To .Num_Springs-1
				
				Dim As vec2f lng = .Point_Mass[.Spring[j].a].soft_psn - .Point_Mass[.Spring[j].b].soft_psn
				Dim As vec2f rest_lng = .Point_Mass[.Spring[j].a].Rest_psn - .Point_Mass[.Spring[j].b].Rest_psn
				Dim As vec2f diff_lng = lng - rest_lng
				
				Dim As vec2f diff_vel = .Point_Mass[.Spring[j].a].vel - .Point_Mass[.Spring[j].b].vel
				
				Dim As vec2f frc = -.Ang*(diff_lng.x*Kl + diff_Vel.x*Dl) - .NrmAng*(diff_lng.y*Kl + diff_Vel.y*Dl)
				
				frc = vec2f(frc.Dot(.Ang), frc.Dot(.NrmAng))
				
				.Point_Mass[.Spring[j].a].frc += frc
				.Point_Mass[.Spring[j].b].frc -= frc
				
	  	Next
	  	
  	End With
  Next
  
  ''	area preserving pressure force
  For i As Integer = 0 To Num_Rigid_Bodys-1
  	With Body[i]
  		
	  	Dim As float force = -.K_Pressure*(.Area-.Rest_Area)
	  	
	  	For i2 As Integer = 0 To .Num_Springs-1
	  		
				Dim As vec2f dst = .Point_Mass[.Spring[i2].a].soft_psn - .Point_Mass[.Spring[i2].b].soft_psn
				
				''	the force scale factor is a hack, since we don't know the spring's length
				Dim As float Scale = .Spring[i2].Rest_Length_Squared/(.Spring[i2].Rest_Length_Squared+magnitudesquared(dst))
				
				Dim As vec2f frc = force * Normal(dst) * Scale
				
				.Point_Mass[.Spring[i2].a].frc -= frc
				.Point_Mass[.Spring[i2].b].frc -= frc
				
	  	Next
  	End With
  Next
  
  ''	particle <-> virtual body interaction
  For i As Integer = 0 To Num_Rigid_Bodys-1
		With Body[i]
			
			''	apply opposite equal force and torque on virtual body
			For i2 As Integer = 0 To .Num_Masses-1
				.torque -= DotNormal(.Point_Mass[i2].COM_Dst, .Point_Mass[i2].frc)
				.frc -= .Point_Mass[i2].Frc
			Next
			
			''	virtual body angular accelleration
			.angular_acc = .torque / .moment_of_inertia
			
  		''	apply summed force and torque of virtual body "back" on particles
			For i2 As Integer = 0 To .Num_Masses-1
				.Point_Mass[i2].frc += .frc / .mass - .Angular_Acc * normal(.Point_Mass[i2].Com_Dst)
			Next 
			
		End With
  Next
  
End Sub

Sub simulation_type.SetExternalForces()
	
	''	this function sets all external forces such as mouse interaction and gravity.
	  
	With mouse
		
		''	update mouse state
		.Psn_Old = .Psn: .Whl_Old = .Whl: .Btn_Old = .Btn
		
		.btn = glfwgetmousebutton(GLFW_MOUSE_BUTTON_LEFT)
		glfwgetmousepos(@.Psn.x, @.Psn.y)
		
		''	on mouseklick, find nearest particle
		If .Btn = 1 Then
			If Pick_State = -1 Then
				Temp_Dist = Pick_Mindist*Pick_Mindist
				For i As integ = 0 To Num_Rigid_Bodys-1
					With Body[i]
						For j As integ = 0 To .Num_Masses-1
							Dim As vec2f dst = mouse.psn - .Point_Mass[j].soft_psn
							If Abs(dst.x) > Pick_Mindist Then Continue For
							If Abs(dst.y) > Pick_Mindist Then Continue For
							Dim As float distanceSquared = MagnitudeSquared(dst)
							If distanceSquared > Pick_Mindist*Pick_Mindist Then Continue For
							If distanceSquared > Temp_Dist Then Continue For
	            Temp_Dist = distanceSquared
              Picked_Body = i
              Picked_Mass = j 
						Next
					End With
				Next
		    If Picked_Body > -1 Then Pick_State = 1: Picked_Rest_Dist = Sqr(Temp_Dist)
			End If
		ElseIf .Btn = 2 Then Prod_State = 1
		Else
			Pick_State 	= -1
	  	Picked_Mass = -1
	  	Picked_Body = -1
	  	Prod_State  = -1
		End If
		
	End With
	
	''	set mouse - blob spring force
	If Pick_State = 1 Then
		With Body[Picked_Body].Point_Mass[Picked_Mass]
			Dim As vec2f Dist
			Dim As float Distance, Force
		 	Dist = .Soft_Psn-Mouse.Psn
      Distance = Magnitude(Dist)
      If (Distance-Picked_Rest_Dist) > 0 Then Force =  -(Distance-Picked_Rest_Dist)*(Body[Picked_Body].mass)*32
      .Frc += Force*(Dist/Distance)
		End With
	EndIf
	
	''	gravity
  For i As Integer = 0 To Num_Rigid_Bodys-1
  	With Body[i]
			For i2 As Integer = 0 To .Num_Masses-1
				.Point_Mass[i2].frc += vec2f(0, grav_acc)
			Next 
		End With
  Next
  
End Sub

Sub simulation_type.setvelocity()
	
  For i As Integer = 0 To Num_Rigid_Bodys-1
    With Body[i]
			
			For i2 As Integer = 0 To .Num_Masses-1
				With .Point_Mass[i2]
					.vel += .frc*dt
				End With
			Next
      
    End With
  Next
	
End Sub

Sub simulation_type.setposition()
	
  For i As Integer = 0 To Num_Rigid_Bodys-1
    With Body[i]
    	
      For i2 As Integer = 0 To .Num_Masses-1
        With .Point_Mass[i2]
					.soft_psn += .vel*dt
        End With
      Next
      
    End With
  Next
  
End Sub

Sub simulation_type.integrate()

	SetInternalForces()
	SetExternalForces()
	
	''	set new particle velocity and position
	SetVelocity()
	SetPosition()
	
	''	get soft body data
  For i As Integer = 0 To Num_Rigid_Bodys-1
		With Body[i]
			
			''	soft body state vectors
	    .psn = vec2f(0, 0)
	    .vel = vec2f(0, 0)
      For i2 As Integer = 0 To .Num_Masses-1
        .psn += .Point_Mass[i2].soft_Psn
        .vel += .Point_Mass[i2].vel
      Next
      .psn /= Body[i].mass
      .vel /= Body[i].mass
      
    	''	get virtual body area
    	.Area = 0
      For j As Integer = 0 To .Num_Masses-1
      	Dim As Integer k = (j+1) Mod .Num_Masses
        .Area += DotNormal(.Point_Mass[j].soft_psn, .Point_Mass[k].soft_psn)
      Next
      .Area *= 0.5
      
    	''	particle distance to virtual body center of mass vector
      For i2 As Integer = 0 To .Num_Masses-1
				.Point_Mass[i2].Com_Dst = .Point_Mass[i2].Soft_Psn-.psn
      Next
      
    	''	virtual body moment of inertia scalar
    	.Moment_Of_Inertia = 0
      For i2 As Integer = 0 To .Num_Masses-1
				.Moment_Of_Inertia += MagnitudeSquared(.Point_Mass[i2].Com_Dst)
      Next
      
      ''	virtual body angular momentum scalar
      .angular_momentum  = 0
      for i2 as integer = 0 to .Num_Masses-1
      	Dim as vec2f Com_Vel = .Point_Mass[i2].Vel - .Vel
        Dim as float ang_vel = DotNormal(.Point_Mass[i2].Com_Dst, Com_Vel)
				.Angular_Momentum += ang_vel
      Next
			
			''	virtual body angular velocity
		  .Angular_vel =  .Angular_Momentum/.Moment_Of_Inertia
		  .Angular_vel += .angular_acc*dt
			
			''	virtual body angle
      .Angle += .Angular_Vel*dt
      .Ang = vec2f(Cos(.Angle), Sin(.Angle))
      .NrmAng = Normal(.Ang)
      
      ''	rotate particle rest positions
      For i2 As Integer = 0 To .Num_Masses-1
        .Point_Mass[i2].Rest_Psn = vec2f(Dot(.Point_Mass[i2].Init_Psn, .Ang), Dot(.Point_Mass[i2].Init_Psn, .NrmAng))
      Next
      
		End With
  Next
	
	''	keep particles inside screen
  For i As Integer = 0 To Num_Rigid_Bodys-1
    With Body[i]
			For i2 As Integer = 0 To Body[i].Num_Masses-1
				With .Point_Mass[i2]
					If .soft_psn.x > ScrnWid-1 Then .soft_psn.x = ScrnWid-1: .vel.x = -.vel.x: .vel *= fr: End If
					If .soft_psn.x < 0 Then .soft_psn.x = 0: .vel.x = -.vel.x:  .vel *= fr: End If
					If .soft_psn.y > ScrnHgt-1 Then .soft_psn.y = ScrnHgt-1: .vel.y = -.vel.y: .vel *= fr: End If
					If .soft_psn.y < 0 Then .soft_psn.y = 0: .vel.y = -.vel.y:  .vel *= fr: End If
				End With
			Next
    End With
	Next
	
End Sub

Sub simulation_type.draw_bodys()
  
	glClear(GL_DEPTH_BUFFER_BIT Or GL_COLOR_BUFFER_BIT)
	
	glLoadIdentity()
	
	''	draw spring between mouse and body
	If Pick_State = 1 Then
		With Body[Picked_Body].Point_Mass[Picked_Mass]
			gllinewidth(2)
			glcolor4ub(255, 255, 32, 255)
			GLbegin(GL_LINES)
      	glvertex2f(.Soft_Psn.X, .Soft_Psn.y)
      	glvertex2f(Mouse.Psn.X, Mouse.Psn.Y)
      GLend()
		End With
	EndIf
	
	If glfwgetkey(GLFW_key_space) Then
		
	  ''	draw soft body rest shape
	  For i As Integer = 0 To Num_Rigid_Bodys-1
	    With Body[i]
	    	
	      ''	draw soft body rest shape
	      glcolor4ub(0, 0, 0, 64)
	      GLbegin(GL_TRIANGLES)
	      For i2 As Integer = 0 To .Num_Springs-1
	      	glvertex2f(.Psn.X, .Psn.Y)
	      	glvertex2f(.Psn.X+.Point_Mass[.spring[i2].b].Rest_Psn.X, .Psn.Y+.Point_Mass[.spring[i2].b].Rest_Psn.Y)
	    		glvertex2f(.Psn.X+.Point_Mass[.spring[i2].a].Rest_Psn.X, .Psn.Y+.Point_Mass[.spring[i2].a].Rest_Psn.Y)
	      Next
	      GLend()
	      
	      ''	draw spring rest positions
	      glcolor4ub(0, 0, 0, 128)
	      gllinewidth(3)
	      GLbegin(GL_LINES)
	      For i2 As Integer = 0 To .Num_Springs-1
	    		glvertex2f(.Psn.X+.Point_Mass[.spring[i2].a].Rest_Psn.X, .Psn.Y+.Point_Mass[.spring[i2].a].Rest_Psn.Y)
	    		glvertex2f(.Psn.X+.Point_Mass[.spring[i2].b].Rest_Psn.X, .Psn.Y+.Point_Mass[.spring[i2].b].Rest_Psn.Y)
	      Next
	      GLend()
	      
	    End With
	  Next
	  
		''	draw center of mass and angle data
	  For i As Integer = 0 To Num_Rigid_Bodys-1
	 	  With Body[i]
				
				GlLineWidth(2)
	      GLbegin(GL_LINES)
	      	glcolor4ub(255, 32, 32, 255)
	    		glvertex2f(.Psn.X, .Psn.Y)
	    		glvertex2f(.Psn.X+.Ang.Y*10, .Psn.Y-.Ang.X*10)
	    		glcolor4ub(32, 255, 32, 255)
	    		glvertex2f(.Psn.X, .Psn.Y)
	    		glvertex2f(.Psn.X-.Ang.Y*10, .Psn.Y+.Ang.X*10)
	    		glcolor4ub(192, 192, 192, 255)
	    		glvertex2f(.Psn.X, .Psn.Y)
	    		glvertex2f(.Psn.X+.Ang.X*10, .Psn.Y+.Ang.Y*10)
	      GLend()
	      
	 	  	glcolor4ub(192, 192, 192, 255)
	      glpointsize(4)
	      GLbegin(GL_POINTS)
					glvertex2f(.Psn.X, .Psn.Y)
				GLend()
				
	    End With
	  Next
	  
  End if
  
  ''	draw soft body current shape
  For i As Integer = 0 To Num_Rigid_Bodys-1
    With Body[i]
    	
      ''	draw soft body current shape
      glcolor4ub(.R, .G, .B, 128)
      GLbegin(GL_TRIANGLES)
      For i2 As Integer = 0 To .Num_Springs-1
      		glvertex2f(.Psn.X, .Psn.Y)
      		glvertex2f(.Point_Mass[.spring[i2].b].Soft_Psn.X, .Point_Mass[.spring[i2].b].Soft_Psn.Y)
      		glvertex2f(.Point_Mass[.spring[i2].a].Soft_Psn.X, .Point_Mass[.spring[i2].a].Soft_Psn.Y)
      Next
      GLend()
      
      ''	draw spring current positions
      glcolor4ub(0, 0, 0, 255)
      gllinewidth(3)
      GLbegin(GL_LINES)
      For i2 As Integer = 0 To .Num_Springs-1
      		glvertex2f(.Point_Mass[.spring[i2].a].Soft_Psn.X, .Point_Mass[.spring[i2].a].Soft_Psn.Y)
      		glvertex2f(.Point_Mass[.spring[i2].b].Soft_Psn.X, .Point_Mass[.spring[i2].b].Soft_Psn.Y)
      Next
      GLend()
      
      ''	draw particle current positions
	    glcolor4ub(0, 0, 0, 255)
	    glpointsize(3)
	    GLbegin(GL_POINTS)
			For i2 As Integer = 0 To .Num_Masses-1
	    	With .Point_Mass[i2]
					glvertex2f(.Soft_Psn.X, .Soft_Psn.Y)
	    	End With
	    Next
			GLend()
      
    End With
  Next
  
	GLflush()
	
	glfwswapbuffers()
  
End Sub

Sub simulation_type.kill_body()
	
	''	free memory
  For i As Integer = 0 To Num_Rigid_Bodys-1
    With body[i]
      DeAllocate(.Point_Mass)
      DeAllocate(.Spring)
    End With
  Next
  DeAllocate(Body)
  
End Sub

Function ScreenType.CreateScreen(w As Integer, h As Integer, r As Integer, g As Integer, _
	b As Integer, a As Integer, d As Integer, s As Integer, m As Integer) As Integer
	
	''	this function creates an GLFW opengl screen
	
	If glfwinit() Then
		
		Dim As GLFWvidmode glfwvm
		glfwGetDesktopMode(@glfwvm)
		
		If w = 0 Or h = 0 Then 
			w = glfwvm.width
			h = glfwvm.height
			m = GLFW_FULLSCREEN
		End If
		
		glfwopenwindowhint(GLFW_FSAA_SAMPLES, 8)
		glfwopenwindowhint(GLFW_WINDOW_NO_RESIZE, GL_TRUE)
		
		If glfwopenwindow(w, h, r, g, b, a, d, s, m) Then
			glfwsetwindowpos(glfwvm.width\2 - w\2, glfwvm.height\2 - h\2)
			glfwsetwindowtitle("Mike's shape matching softbody. Press left mouse to pick up objects. Hold down space to see rest shape.")
			glfwswapinterval(1)
			glfwEnable(GLFW_MOUSE_CURSOR)
			
			glmatrixmode(GL_PROJECTION)  
			glloadidentity()
			glviewport(0, 0, w, h)
			glortho(0, w, h, 0, 0, 32)
			glmatrixmode(GL_MODELVIEW)
			glloadidentity()
			glenable(GL_CLEAR)
			glClearColor(0.5, 0.5, 0.5, 1.0)
			glenable(GL_BLEND)
			glblendfunc(GL_SRC_ALPHA, GL_ONE_MINUS_SRC_ALPHA)
			Return TRUE
		End If
		glfwterminate()
	End If
	Return FALSE
End Function

Function ScreenType.DeleteScreen() As Integer
	glfwclosewindow()
	glfwterminate()
	Return TRUE
End Function
...and here's the vec2 vector library:

Code: Select all

''*******************************************************************************
''		
''		Freebasic 2d floating point and integer vector library
''		version 0.5b, june 2010, Michael "h4tt3n" Nissen, jernmager@yahoo.dk
''		Integer vectors have been added for screen and mouse operations.   
''		
''		function syntax:
''		
''   	(return type) (function name) (argument type (, ...))
''		
''	 	floating point vector function list:
''		
''   	vector absolute          	(vector)          - absolute value
''   	vector normal            	(vector)          - normal vector
''   	vector normalised        	(vector)          - normalised vector
''		vector normalisednormal		(vector)					-	normalised normal vector
''   	scalar magnitude         	(vector)          - magnitude
''   	scalar magnitudesquared		(vector)          - magnitude squared
''   	scalar distance          	(vector, vector)  - vector distance
''   	scalar distancesquared   	(vector, vector)  - vector distance squared
''   	scalar dot               	(vector, vector)  - dot product
''   	scalar dotnormal         	(vector, vector)  - normal dot product
''   	vector project           	(vector, vector)	-	vector projection
''		vector component					(vector, vector)	-	vector component
''		vector randomise					(scalar)					-	randomise in range +/- value
''		vector reciprocal					(vector)					- reciprocal value of components
''
''		integer vector function list:
''		
''		
''	 	function useage, member and non-member style:
''
''		vector_a.function(vector_b),	function(vector_a, vector_b)
''
''		functions 
''		
''*******************************************************************************

Type float As Double
Type integ As Integer

''  2d float vector structure
Type vec2f
	
  ''  variables
  As float x, y
	
  ''  constructor declarations
	Declare Constructor ()
  Declare Constructor (ByVal x As float, ByVal y As float)
	
  ''  compound arithmetic member operator declarations
  Declare Operator += (ByRef rhs As vec2f)
  Declare Operator -= (ByRef rhs As vec2f)
  Declare Operator *= (ByRef rhs As vec2f)
  Declare Operator *= (ByRef rhs As float)
  Declare Operator /= (ByRef rhs As float)
  Declare Operator Let (ByRef rhs As vec2f)
	
	''  member function declarations
  'Declare Function absolute() As vec2f
  Declare Function normal() As vec2f 
  Declare Function normalised() As vec2f
  Declare Function normalisednormal() As vec2f
  Declare Function magnitude() As float
  Declare Function magnitudesquared() As float
  Declare Function distance(ByRef rhs As vec2f) As float
  Declare Function distancesquared(ByRef rhs As vec2f) As float
  Declare Function dot(ByRef rhs As vec2f) As float
  Declare Function dotnormal(ByRef rhs As vec2f) As float
  Declare Function project(ByRef rhs As vec2f) As vec2f
  Declare Function component(ByRef rhs As vec2f) As vec2f
  Declare Function randomise(ByVal rhs As float) As vec2f
  Declare Function reciprocal(ByVal rhs As vec2f) As vec2f
  
End Type

''  vec2f unary arithmetic non-member operator declarations
Declare Operator - (ByRef rhs As vec2f) As  vec2f

''  vec2f binary arithmetic non-member operator declarations
Declare Operator + (ByVal lhs As vec2f, ByRef rhs As vec2f) As vec2f
Declare Operator - (ByVal lhs As vec2f, ByRef rhs As vec2f) As vec2f
Declare Operator * (ByVal lhs As float, ByRef rhs As vec2f) As vec2f
Declare Operator * (ByVal lhs As vec2f, ByVal rhs As float) As vec2f
Declare Operator / (ByVal lhs As vec2f, ByVal rhs As float) As vec2f

''  vec2f non-member function declarations
'Declare Function absolute (ByRef lhs As vec2f) As vec2f
Declare Function normal (ByRef lhs As vec2f) As vec2f
Declare Function normalised (ByRef lhs As vec2f) As vec2f
Declare Function normalisednormal(ByRef lhs As vec2f) As vec2f
Declare Function magnitude (ByRef lhs As vec2f) As float
Declare Function magnitudesquared (ByRef lhs As vec2f) As float
Declare Function distance (ByVal lhs As vec2f, ByRef rhs As vec2f) As float
Declare Function distancesquared (ByVal lhs As vec2f, ByRef rhs As vec2f) As float
Declare Function dot (ByVal lhs As vec2f, ByRef rhs As vec2f) As float
Declare Function dotnormal (ByVal lhs As vec2f, ByRef rhs As vec2f) As float
Declare Function project (ByVal lhs As vec2f, ByRef rhs As vec2f) As vec2f
Declare Function component(ByVal lhs As vec2f, ByRef rhs As vec2f) As vec2f
Declare Function trigonometry(ByRef lhs As float) As vec2f
Declare Function randomise(ByVal lhs As float) As vec2f

''  vec2f constructors
Constructor vec2f(): this.x = 0.0: this.y = 0.0: End Constructor
Constructor vec2f(ByVal x As float, ByVal y As float): this.x = x: this.y = y: End Constructor

''  vec2f compound arithmetic member operators
Operator vec2f.+= (ByRef rhs As  vec2f): x += rhs.x: y += rhs.y: End Operator
Operator vec2f.-= (ByRef rhs As  vec2f): x -= rhs.x: y -= rhs.y: End Operator
Operator vec2f.*= (ByRef rhs As  vec2f): x *= rhs.x: y *= rhs.y: End Operator
Operator vec2f.*= (ByRef rhs As  float): x *= rhs: y *= rhs: End Operator
Operator vec2f./= (ByRef rhs As  float): x /= rhs: y /= rhs: End Operator
Operator vec2f.let (ByRef rhs As  vec2f): x = rhs.x: y = rhs.y: End Operator

''  vec2f member functions
'Function vec2f.absolute() As vec2f: Return vec2f(Abs(x), Abs(y)): End Function
Function vec2f.normal() As vec2f: Return vec2f(y, -x): End Function 
Function vec2f.normalised() As vec2f: If this.x <> 0 And this.y <> 0 Then Return This/magnitude(): Else Return vec2f(0, 0): End if: End Function
Function vec2f.normalisednormal() As vec2f: Return this.normal()/magnitude(): End Function
Function vec2f.magnitude() As float: Return Sqr(magnitudesquared()): End Function
Function vec2f.magnitudesquared() As float: Return this.dot(This): End Function
Function vec2f.distance(ByRef rhs As vec2f) As float: Return Sqr(distancesquared(rhs)): End Function
'Function vec2f.distancesquared(ByRef rhs As vec2f) As float: Return (x-rhs.x)*(x-rhs.x)+(y-rhs.y)*(y-rhs.y): End Function
Function vec2f.distancesquared(ByRef rhs As vec2f) As float: Dim As vec2f d = This-rhs: Return d.dot(d): End Function
Function vec2f.dot(ByRef rhs As vec2f) As float: Return (x*rhs.x+y*rhs.y): End Function
Function vec2f.dotnormal(ByRef rhs As vec2f) As float: Return this.dot(rhs.normal()): End Function
Function vec2f.project(ByRef rhs As vec2f) As vec2f: Return (dot(rhs)/magnitudesquared())*rhs: End Function
Function vec2f.component(ByRef rhs As vec2f) As vec2f: Return (dot(rhs)/rhs.magnitudesquared)*rhs: End Function
Function vec2f.randomise(ByVal rhs As float) As vec2f: Return vec2f((Rnd-Rnd)*rhs, (Rnd-Rnd)*rhs): End Function
Function vec2f.reciprocal(ByVal rhs As vec2f) As vec2f: Return vec2f(0, 0): End Function

''  vec2f unary arithmetic non-member operators
Operator - (ByRef rhs As vec2f) As vec2f: Return vec2f(-rhs.x, -rhs.y): End Operator

''  vec2f binary arithmetic non-member operators
Operator + (ByVal lhs As vec2f, ByRef rhs As vec2f) As vec2f: Return vec2f(lhs.x+rhs.x, lhs.y+rhs.y): End Operator
Operator - (ByVal lhs As vec2f, ByRef rhs As vec2f) As vec2f: Return vec2f(lhs.x-rhs.x, lhs.y-rhs.y): End Operator
Operator * (ByVal lhs As float, ByRef rhs As vec2f) As vec2f: Return vec2f(lhs*rhs.x, lhs*rhs.y): End Operator
Operator * (ByVal lhs As vec2f, ByVal rhs As float) As vec2f: Return vec2f(lhs.x*rhs, lhs.y*rhs): End Operator
Operator / (ByVal lhs As vec2f, ByVal rhs As float) As vec2f: Return vec2f(lhs.x/rhs, lhs.y/rhs): End Operator

''  vec2f non-member functions
'Function absolute (ByRef lhs As vec2f) As vec2f: Return lhs.absolute(): End Function
Function normal (ByRef lhs As vec2f) As vec2f: Return lhs.normal(): End Function
Function normalised (ByRef lhs As vec2f) As vec2f: Return lhs.normalised(): End Function
Function normalisednormal(ByRef lhs As vec2f) As vec2f: Return lhs.normalisednormal(): End Function
Function magnitude (ByRef lhs As vec2f) As float: Return lhs.magnitude(): End Function
Function magnitudesquared (ByRef lhs As vec2f) As float: Return lhs.magnitudesquared(): End Function
Function distance (ByVal lhs As vec2f, ByRef rhs As vec2f) As float: Return lhs.distance(rhs): End Function
Function distancesquared (ByVal lhs As vec2f, ByRef rhs As vec2f) As float: Return lhs.distancesquared(rhs): End Function
Function dot (ByVal lhs As vec2f, ByRef rhs As vec2f) As float: Return lhs.dot(rhs): End Function
Function dotnormal (ByVal lhs As vec2f, ByRef rhs As vec2f) As float: Return lhs.dotnormal(rhs): End Function
Function project (ByVal lhs As vec2f, ByRef rhs As vec2f) As vec2f: Return lhs.project(rhs): End Function
Function component(ByVal lhs As vec2f, ByRef rhs As vec2f) As vec2f: Return lhs.component(rhs): End Function
Function trigonometry(ByRef lhs As float) As vec2f: Return vec2f(Cos(lhs), Sin(lhs)): End Function
Function randomise(ByVal lhs As float) As vec2f: Return vec2f((Rnd-Rnd)*lhs, (Rnd-Rnd)*lhs): End Function

''  2d integer vector structure
Type vec2i
	
  ''  variables
  As integ x, y
	
  ''  constructor declarations
	Declare Constructor ()
  Declare Constructor (ByVal x As integ, ByVal y As integ)
	
  ''  compound arithmetic member operator declarations
  Declare Operator += (ByRef rhs As vec2i)
  Declare Operator -= (ByRef rhs As vec2i)
  Declare Operator *= (ByRef rhs As vec2i)
  Declare Operator *= (ByRef rhs As integ)
  Declare Operator \= (ByRef rhs As integ)
  Declare Operator Let (ByRef rhs As vec2i)
  
End Type

''  vec2i unary arithmetic non-member operator declarations
Declare Operator - (ByRef rhs As vec2i) As  vec2i

''  vec2i binary arithmetic non-member operator declarations
Declare Operator + (ByVal lhs As vec2i, ByRef rhs As vec2i) As vec2i
Declare Operator - (ByVal lhs As vec2i, ByRef rhs As vec2i) As vec2i
Declare Operator * (ByVal lhs As float, ByRef rhs As vec2i) As vec2i
Declare Operator * (ByVal lhs As vec2i, ByVal rhs As float) As vec2i
Declare Operator \ (ByVal lhs As vec2i, ByVal rhs As float) As vec2i

''  vec2i constructors
Constructor vec2i(): this.x = 0: this.y = 0: End Constructor
Constructor vec2i(ByVal x As integ, ByVal y As integ): this.x = x: this.y = y: End Constructor

''  vec2i compound arithmetic member operators
Operator vec2i.+= (ByRef rhs As  vec2i): x += rhs.x: y += rhs.y: End Operator
Operator vec2i.-= (ByRef rhs As  vec2i): x -= rhs.x: y -= rhs.y: End Operator
Operator vec2i.*= (ByRef rhs As  vec2i): x *= rhs.x: y *= rhs.y: End Operator
Operator vec2i.*= (ByRef rhs As  integ): x *= rhs: y *= rhs: End Operator
Operator vec2i.\= (ByRef rhs As  integ): x \= rhs: y \= rhs: End Operator
Operator vec2i.let (ByRef rhs As  vec2i): x = rhs.x: y = rhs.y: End Operator

''  vec2i unary arithmetic non-member operators
Operator - (ByRef rhs As vec2i) As vec2i: Return vec2i(-rhs.x, -rhs.y): End Operator

''  vec2i binary arithmetic non-member operators
Operator + (ByVal lhs As vec2i, ByRef rhs As vec2i) As vec2i: Return vec2i(lhs.x+rhs.x, lhs.y+rhs.y): End Operator
Operator - (ByVal lhs As vec2i, ByRef rhs As vec2i) As vec2i: Return vec2i(lhs.x-rhs.x, lhs.y-rhs.y): End Operator
Operator * (ByVal lhs As integ, ByRef rhs As vec2i) As vec2i: Return vec2i(lhs*rhs.x, lhs*rhs.y): End Operator
Operator * (ByVal lhs As vec2i, ByVal rhs As integ) As vec2i: Return vec2i(lhs.x*rhs, lhs.y*rhs): End Operator
Operator \ (ByVal lhs As vec2i, ByVal rhs As integ) As vec2i: Return vec2i(lhs.x\rhs, lhs.y\rhs): End Operator

''  combined binary arithmetic non-member operator declarations
Declare Operator + (ByVal lhs As vec2f, ByRef rhs As vec2i) As vec2f
Declare Operator + (ByVal lhs As vec2i, ByRef rhs As vec2f) As vec2f
Declare Operator - (ByVal lhs As vec2f, ByRef rhs As vec2i) As vec2f
Declare Operator - (ByVal lhs As vec2i, ByRef rhs As vec2f) As vec2f

''  combined non-member function declarations

''  combined binary arithmetic non-member operators
Operator + (ByVal lhs As vec2f, ByRef rhs As vec2i) As vec2f: Return vec2f(lhs.x+rhs.x, lhs.y+rhs.y): End Operator
Operator + (ByVal lhs As vec2i, ByRef rhs As vec2f) As vec2f: Return vec2f(lhs.x+rhs.x, lhs.y+rhs.y): End Operator
Operator - (ByVal lhs As vec2f, ByRef rhs As vec2i) As vec2f: Return vec2f(lhs.x-rhs.x, lhs.y-rhs.y): End Operator
Operator - (ByVal lhs As vec2i, ByRef rhs As vec2f) As vec2f: Return vec2f(lhs.x-rhs.x, lhs.y-rhs.y): End Operator

''  combined non-member functions

duke4e
Posts: 717
Joined: Dec 04, 2005 0:16
Location: Varazdin, Croatia, Europe
Contact:

Post by duke4e »

Looks really fun
Post Reply