procedural spaceships

Game development specific discussions.
Post Reply
dafhi
Posts: 1741
Joined: Jun 04, 2005 9:51

procedural spaceships

Post by dafhi »

spaceship generator with real-time scaling & rotation

Part 1/2 .. (part 2 is four posts below)

Code: Select all

/' -- procedural spaceships - 2025 Apr 30 - by Google Gemini 2.5 Pro (thinking) and dafhi

    update:
  thickLine (my new rasterizer)
  design tweaks
    
'/

'#include "rast.bas"

    ' -- boilerplate
    '
    sub _gfx_release( byref im as any ptr )
      if im <> 0 then if imageinfo(im) = 0 then imagedestroy im
      im = 0
    end sub

Type imvars   '' 2025 Apr 12 .. Gemini minified
    As Long     w,h, bypp, pitch, wm, hm, pitchBy
    As Any Ptr  pixels, im
End Type

Sub fill_imvars( Byref i As imvars, im As Any Ptr = 0) '' 2025 Apr 12 .. Gemini minified.  old version released imvars.im before new assignment
    If im = 0 Then
        ScreenInfo i.w, i.h, , i.bypp, i.pitch: i.pixels = screenptr
    Else
        ImageInfo im, i.w, i.h, i.bypp, i.pitch, i.pixels: i.im = im
    End If
    i.wm = i.w - 1: i.hm = i.h - 1: i.pitchBy = i.pitch \ i.bypp
End Sub

Function min overload ( a As Double, b As Double ) As Double: Return Iif( a < b, a, b): End Function
Function max overload ( a As Double, b As Double ) As Double: Return Iif( a > b, a, b): End Function

#define ceil(x) -int(-(x)) ' // Standard integer ceiling //

#Macro Alpha256( ret, back, fore, a256) 'blend colors. alpha max = 256  (2025 Apr 8)
    scope
      dim as long _a = (a256)
      ret=((_
      (fore And &Hff00ff) * _a + _
      (back And &Hff00ff) * (256-_a) + &H800080) And &Hff00ff00 Or (_
      (fore And &H00ff00) * _a + _
      (back And &H00ff00) * (256-_a) + &H008000) And &H00ff0000) Shr 8
    end scope
#EndMacro

function clamp( in As double, hi As double = 1, lo As double = 0) As double
  return min( max(in, lo), hi ) '' 2023 June 12
End Function

#macro sw( _a, _b, _tmp )
    _tmp = _a : _a = _b : _b = _tmp
#endmacro

Const EPSILON As single = 1e-6 ' Small value for float comparisons

 function f_a256( c as ulong ) as long '' 0-255 -> 0-256 for ALpha256
     return ((c shr 24)/255) * 257 - .5
 end function

 function sqr_safe( d as double ) as double '' used for aadot (part of my full framework)
     return sgn(d) * sqr( abs(d))
 end function

Type v2d: As single x, y: End Type

Operator - ( a As v2d, b As v2d ) As v2d: Return Type( a.x - b.x, a.y - b.y ): End Operator
Operator * ( a As v2d, s As single ) As v2d: Return Type( a.x * s, a.y * s ): End Operator
Function dot ( a As v2d, b As v2d ) As single: Return a.x * b.x + a.y * b.y : End Function
Function LenSq ( a As v2d ) As Double: Return a.x * a.x + a.y * a.y : End Function

 function edgeFunction( a as v2d, b as v2d, p as v2d ) as single ' determines which side of a line a point is on
     return (p.x - a.x) * (b.y - a.y) - (p.y - a.y) * (b.x - a.x)
 end function
  ' --- boilerplate END


type t_fij '' New: 2025 Apr 27
    as single         v
    declare property  i as long
    declare property  j as long
end type

property t_fij.i as long: return int(v): end property
property t_fij.j as long: return ceil(v): end property


type v2di '' New: 2025 Apr 27
    as single         x, y
    declare property  ix as long
    declare property  iy as long
    declare property  jx as long
    declare property  jy as long
end type

property v2di.ix as long: return int(x): end property
property v2di.iy as long: return int(y): end property
property v2di.jx as long: return ceil(x): end property
property v2di.jy as long: return ceil(y): end property


Namespace Rast

  Dim Shared As imvars imv ' Shared within the namespace

  ' -- a main function
  '
Sub render_target( _im As Any Ptr = 0 )
    fill_imvars imv, _im
End Sub

  dim as ulong ptr row
  dim as long         scan_x0, scan_x1, alpha_max, final_a, gx0, gy0, gx1, gy1, col
  dim as single       xm5, ym5, xp5, rp5_sq, invert, alpha_sa, edge_iRSq
  dim as single       dySq, dx, dy, rSq, dist_sq, break_sq, coverage, cov0, cov1, cov2

  sub _cliprect( x0 as single, y0 as single, x1 as single, y1 as single )
    gx0 = max( 0, int( x0+.0 )) '' +.5 used previously
    gy0 = max( 0, int( y0+.0 ))
    gx1 = min( imv.wm, int( x1+.0 ))
    gy1 = min( imv.hm, int( y1+.0 ))
  end sub

  sub _aadot_precalcs( x as single, y as single, c as ulong, r as single, edge as single )
      _cliprect x - r, y - r, x + r, y + r
      alpha_sa = min(1, edge*r) * f_a256(c)
      rSq = r^2 : break_sq = rSq * .8 : alpha_max = alpha_sa
      edge_irSq = edge * alpha_sa / rSq
      xm5 = x - .5 : xp5 = x + .5 : ym5 = y - .5 : rp5_sq = (r + .5)^2
  end sub
  
  sub _aadot_dy_and_scanline_ends( y as single, iy as long, rad as single )
      dy = iy-ym5
      dx = sqr_safe( rp5_sq - dy^2 )
      scan_x0 = max( int(xp5 - dx), gx0 ) ' scan segment hugs circle
      scan_x1 = min( int(xm5 + dx), gx1 )
      dySq = dy * dy
      row = cast( ulong ptr, imv.pixels + iy * imv.pitch ) '' pitch = scanline cbytes
  end sub
  
  sub _aadot_scan( x0 as long, x1 as long, _step as long, c as ulong )
        for ix as long = x0 to x1 step _step
    dist_sq = ( (ix - xm5)^2 + dySq )' : if dist_sq < break_sq then exit for
    invert = rSq - dist_sq
    final_a = min( alpha_max, edge_irSq * max(0,invert) )
    alpha256( row[ix], row[ix], c, final_a )
    next
  end sub
  
  sub _aadot_draw( x as single = 0, y as single = 0, c as ulong = -1, rad as single = 5 )
        for iy as long = gy0 to gy1
    _aadot_dy_and_scanline_ends y, iy, rad
    _aadot_scan scan_x0, scan_x1, 1, c
    _aadot_scan scan_x1, scan_x0, -1, c
    next
  end sub

sub aadot( x as single = 0, y as single = 0, c as ulong = -1, rad as single = 5, edge as single = 1 )
    _aadot_precalcs x, y, c, rad, edge
    _aadot_draw x,y,c,rad
end sub

    ' // --- Anti-aliased Triangle --- //
const as double AA_WIDTH_TRI = 1.0
const as double AA_HALF_WIDTH_TRI = AA_WIDTH_TRI * 0.5

sub drawtriangle_aa( x0 as single, y0 as single, _
                             x1 as single, y1 as single, _
                             x2 as single, y2 as single, _
                             col as ulong = &hFFFFFFFF )

    dim v0 as v2d = type(x0, y0)
    dim v1 as v2d = type(x1, y1)
    dim v2 as v2d = type(x2, y2)

    ' Edge vectors
    dim as single dx01 = v1.x - v0.x, dy01 = v1.y - v0.y
    dim as single dx12 = v2.x - v1.x, dy12 = v2.y - v1.y
    dim as single dx20 = v0.x - v2.x, dy20 = v0.y - v2.y

    ' Inverse lengths (as before)
    dim as single lenSq01 = dx01*dx01 + dy01*dy01
    dim as single lenSq12 = dx12*dx12 + dy12*dy12
    dim as single lenSq20 = dx20*dx20 + dy20*dy20
    dim invLen01 as double = iif(lenSq01 > EPSILON, 1.0 / sqr(lenSq01), 0)
    dim invLen12 as double = iif(lenSq12 > EPSILON, 1.0 / sqr(lenSq12), 0)
    dim invLen20 as double = iif(lenSq20 > EPSILON, 1.0 / sqr(lenSq20), 0)

    ' Bounding box (as before)
    dim minX as single = min(x0, min(x1, x2))
    dim minY as single = min(y0, min(y1, y2))
    dim maxX as single = max(x0, max(x1, x2))
    dim maxY as single = max(y0, max(y1, y2))
    dim startX as long = max(0, int(minX - AA_HALF_WIDTH_TRI))
    dim startY as long = max(0, int(minY - AA_HALF_WIDTH_TRI))
    dim endX   as long = min(imv.wm, ceil(maxX + AA_HALF_WIDTH_TRI))
    dim endY   as long = min(imv.hm, ceil(maxY + AA_HALF_WIDTH_TRI))

    ' Precalculate edge function deltas (rename vars for clarity)
    ' Delta for w0 (edge v1-v2) when moving +1 in X
    dim w0_deltaX as single = dy12 ' v2.y - v1.y
    ' Delta for w0 (edge v1-v2) when moving +1 in Y
    dim w0_deltaY as single = -dx12 ' -(v2.x - v1.x)
    ' Delta for w1 (edge v2-v0) when moving +1 in X
    dim w1_deltaX as single = dy20 ' v0.y - v2.y
    ' Delta for w1 (edge v2-v0) when moving +1 in Y
    dim w1_deltaY as single = -dx20 ' -(v0.x - v2.x)
    ' Delta for w2 (edge v0-v1) when moving +1 in X
    dim w2_deltaX as single = dy01 ' v1.y - v0.y
    ' Delta for w2 (edge v0-v1) when moving +1 in Y
    dim w2_deltaY as single = -dx01 ' -(v1.x - v0.x)

    ' Precalculate for early exit check & coverage
    dim w0_thresh as single = -AA_HALF_WIDTH_TRI / invLen12
    dim w1_thresh as single = -AA_HALF_WIDTH_TRI / invLen20
    dim w2_thresh as single = -AA_HALF_WIDTH_TRI / invLen01
    dim inv_aa_width as double = 1.0 / AA_WIDTH_TRI

    alpha_max = f_a256(col)

    dim p as v2d ' Current pixel center
    p.y = startY + 0.5 ' Y for the first row

    ' Calculate initial w values for the first pixel (startX, startY)
    p.x = startX + 0.5
    dim w0_rowStart as single = edgeFunction(v1, v2, p) - w0_deltaX '' subtract allows w0 w1 w2 advance for concise "if .. continue for"
    dim w1_rowStart as single = edgeFunction(v2, v0, p) - w1_deltaX
    dim w2_rowStart as single = edgeFunction(v0, v1, p) - w2_deltaX

        for y as long = startY to endY
    row = imv.pixels : row += y * imv.pitchBy

    ' Reset w for the start of the scanline
    dim as single w0 = w0_rowStart, w1 = w1_rowStart, w2 = w2_rowStart

    for x as long = startX to endX
        w0 += w0_deltaX: w1 += w1_deltaX: w2 += w2_deltaX
        
        if (w0 < w0_thresh) and (w1 < w1_thresh) and (w2 < w2_thresh) then continue for'' outside

        ' Calculate actual signed distances
        dim as single d0 = w0 * invLen12, d1 = w1 * invLen20, d2 = w2 * invLen01

        ' Calculate coverage (using multiplication instead of division)
        cov0 = clamp(0.5 + d0 * inv_aa_width)
        cov1 = clamp(0.5 + d1 * inv_aa_width)
        cov2 = clamp(0.5 + d2 * inv_aa_width)
        
        coverage = min(cov0, min(cov1, cov2))

        ' Blend pixel if coverage > 0
        if coverage > EPSILON then ' Avoid blending for zero coverage
          dim as long final_a = coverage * alpha_max
          alpha256( row[x], row[x], col, final_a )
        end if

    next x

    ' Increment w_rowStart for the next row (using y delta)
    w0_rowStart += w0_deltaY
    w1_rowStart += w1_deltaY
    w2_rowStart += w2_deltaY
    ' p.y += 1.0 ' Implicitly handled by using wX_rowStart

    next y

end sub

Sub triangle( byval a As V2d, byval b As V2d, byval c As V2d, col As ULong)
    
    ' Sort by Y primarily (ensures a is top, b.y <= c.y)
    If b.y < a.y Then Swap a, b
    If c.y < a.y Then Swap a, c
    If c.y < b.y Then Swap b, c

    ' Example using cross product for proper a b c winding.  (clockwise atm? no comprendo)
     Dim As Double cross_product = (b.x - a.x) * (c.y - a.y) - (b.y - a.y) * (c.x - a.x)
     If cross_product > 0 Then Swap b, c

    drawtriangle_AA( a.x,a.y, b.x,b.y, c.x,c.y, col )
    
End Sub

  ' --- edge-following thickline - 2025 Apr 28 - by dafhi --
    dim as single   cosa, sina, slen, len_inverse, wid_inverse, wid, tmp
    dim as single   cx, cy, halfw_cos, halfw_sin, sL, iSL, xi_ab, xi_ac, xi_cd, xi_bd
    dim as v2di     a,b,c,d
    dim as t_fij    ac, bd

  sub set_corners( byref hi as v2di, byref lo as v2di, x as single, y as single)
      hi = type( x - halfw_sin, y + halfw_cos )
      lo = type( x + halfw_sin, y - halfw_cos )
  end sub

  sub _scan( y as long )
      if sina >= 0 then
          ac.v = max( max( a.x, xi_ab ), xi_ac ) ' end perp
          bd.v = min( min( d.x, xi_cd ), xi_bd ) ' end perp
      else
          bd.v = min( min( b.x, xi_ab ), xi_bd )
          ac.v = max( max( c.x, xi_cd ), xi_ac )
      endif
      row = imv.pixels + y * imv.pitch
      for x as long = max(ac.i, 0) to min(bd.i, imv.wm) '' 2025 Apr 30
          alpha256( row[x], row[x], col, alpha_max )
      next
      xi_ab += iSL
      xi_cd += iSL
      xi_ac -= sL
      xi_bd -= sL
  end sub

sub thickline( x0 as single, y0 as single, x1 as single, y1 as single, _col as ulong = -1, _wid as single = 1, dummy as long = 0 )
    col = _col : wid = _wid
    '_epsilon_dx x0, x1, y0, y1 '' 2025 Apr 28
    if x0 > x1 then sw( x0, x1, tmp) : sw( y0, y1, tmp)
    dx = x1 - x0
    dy = y1 - y0
    slen = sqr(dx*dx + dy*dy)
    len_inverse = 1 / slen
    cosa = dx * len_inverse : halfw_cos = cosa * wid / 2
    sina = dy * len_inverse : halfw_sin = sina * wid / 2
    set_corners a, c, x0, y0
    set_corners b, d, x1, y1
    '_cliprect min(a.ix,c.ix), min(c.iy,d.iy), max(b.ix,d.ix), max(a.iy,b.iy) '' 2025 Apr 30
    sl = dy / dx : iSL = dx / dy
    dim as long iy0 = max( 0, min( c.iy, d.iy )) '' 2025 Apr 30
    if sina >= 0 then
        xi_ab = a.x - iSL * (a.y - iy0)
        xi_cd = d.x + iSL * (iy0+1 - d.y)
        xi_ac = a.x - sL * (iy0+1 - a.y)
        xi_bd = d.x + sL * (d.y - iy0)
    else
        xi_ab = b.x - iSL * (b.y - iy0)
        xi_cd = c.x + iSL * (iy0+1 - c.y)
        xi_bd = b.x - SL * (iy0+1 - b.y)
        xi_ac = c.x + sL * (c.y - iy0)
    endif
    alpha_max = f_a256(col)
    for y as long = iy0 to min( imv.hm, max( a.iy, b.iy )) '' 2025 Apr 30
        _scan y
    next
end sub

End Namespace ' -- Rast

const pi = 4 * atn(1)

Const DEG2RAD As Double = PI / 180.0
 

    function triwave( i as single ) as single
      return abs( i - int(i) - .5 ) - .25 ' by Stonemonkey
    end function

    function _cchsv(h as single, s as single, v as single) as ubyte ' 2024 July 24
      var wave_hgt = s * v
      return 255.499 * (wave_hgt * (clamp(triwave(h)*6+.5)-1) + v)
    end function

function hsv( h as single=0, s as single=1, v as single=1, a as ubyte = 255 ) as ulong ' 2024 May 21
      return rgba( _
    _cchsv( h + 0/3, s,v ), _
    _cchsv( h + 2/3, s,v ), _
    _cchsv( h + 1/3, s,v ), a )
end function

    function ror64( in as ulongint, r as ubyte = 1 ) as ulongint
      return (in shl (64 - r)) or (in shr r)
    end function

    namespace myhash '' dafhi
const as ulongint     Knuth_ADD = 442695040888963407 ' Knuth LCG
const as ulongint     Knuth_MUL = 6364136223846793005
const as ulongint     xorA  = &b0101010101010101010101010101010101010101010101010101010101010101
const as ulongint     xorC  = &b0000000001000000000100000000100000001000000100000100001000100101
dim as ulongint       a, b

sub reset( _a as ulongint, _b as ulongint = 0 )
    a=_a : b=_b
end sub

function v( seed as ulongint = 0 ) as ulongint
    b += a * xorC
    b xor= b shr 31
    a xor= (b xor seed) * xorA
    a xor= a shr 31
    return ror64( a, a shr 58 )
end function

end namespace ' -- myhash

    function float32( i as ulong) as single
      return i / (2^32 + 2^7)
    end function

    ' -- epoch-inspired randomization - 2025 Apr 15  by dafhi
    '
#define rng float32(myhash.v)

type lerp_duo
    declare           constructor( bas_A as single = 0, bas_B as single = 1, vari_A as single = 0, vari_B as single = 0 )
    declare operator  cast as const single
    declare operator  cast as string
    
    as single         ret, bas, bas_v, vari, vari_v, b, v
end type

    sub gen_LD( byref i as lerp_duo )
        i.ret = i.b + rng * i.v
    end sub

    sub epoch_LD( byref i as lerp_duo )
        i.b = i.bas + rng * i.bas_v
        i.v = i.vari + rng * i.vari_v
    end sub
    
constructor lerp_duo( a as single, b as single, va as single, vb as single )
    bas = a : bas_v = b - a : vari = va : vari_v = vb - va
end constructor

operator lerp_duo.cast as const single '' 2025 Apr 15
    return ret 'b + rng * v
end operator

operator lerp_duo.cast as string
    return str(ret)
end operator
    '
    ' --- Part 1 of 2 (procedural spaceships)

Last edited by dafhi on Apr 30, 2025 17:50, edited 8 times in total.
rdc
Posts: 1745
Joined: May 27, 2005 17:22
Location: Texas, USA
Contact:

Re: procedural spaceships

Post by rdc »

Very cool. Some developers use a technique called Wave Function Collapse to build objects within a scene. Townscaper and Caves of Qud use the algorithm for their games. It might be worth looking at.
paul doe
Posts: 1878
Joined: Jul 25, 2017 17:22
Location: Argentina
Contact:

Re: procedural spaceships

Post by paul doe »

Very cool. Can Wave Function Collapse be used in these cases, though? It seems to work well with grids, but could it work here as well?
UEZ
Posts: 1079
Joined: May 05, 2017 19:59
Location: Germany

Re: procedural spaceships

Post by UEZ »

Well done - very nice! :!:
dafhi
Posts: 1741
Joined: Jun 04, 2005 9:51

Re: procedural spaceships

Post by dafhi »

Code: Select all

  ' --- Part 2 of 2 (procedural spaceships continued)
  '
Type hsva_ld
    as lerp_duo h,s,v,a
End Type

    sub gen_hsva_ld( byref i as hsva_ld )
        gen_LD i.h : gen_LD i.s : gen_LD i.v : gen_LD i.a
    end sub

    sub epoch_hsva_ld( byref i as hsva_ld )
        epoch_LD i.h : epoch_LD i.s : epoch_LD i.v : epoch_LD i.a
    end sub

function f_hsva_ld( a as lerp_duo, b as lerp_duo, c as lerp_duo, d as lerp_duo ) as hsva_ld
    static as hsva_ld ret :    ret.h = a : ret.s = b : ret.v = c : ret.a = d
    return ret
end function

Function get_ld_color( Byref c As hsva_ld ) As Ulong
    Return hsv(c.h,c.s,c.v,c.a*255.499)
End Function


    namespace procgen_spaceship '' procedural 2D spaceship concept - 2025 Apr 17 - Gemini 2.5 Pro with minor tweaks by dafhi

Type spaceship_prototype

    '' humans: if you add something, remember to also add to the macro below these properties
    
    ' reduced chance of perfect symmetry for more quirky shapes
    symmetry_chance     As lerp_duo = lerp_duo(0.3, 0.8, -0.2, 0.2)

    ' --- Hull ---
    #if 0 '' original
    hull_length         As lerp_duo = lerp_duo(40, 80, -10, 10)
    hull_width          As lerp_duo = lerp_duo(20, 50, -8, 8)
    hull_color          As hsva_ld  = f_hsva_ld( lerp_duo(0, 1, 0, 1), lerp_duo(0, .25, .0, .2), lerp_duo(.4, .6, -.4, .4), lerp_duo(1,0.7, 0, -.3) )
    hull_taper_front    As lerp_duo = lerp_duo(0.5, 1.0, -0.2, 0.2) ' 1.0 = Rectangular front, 0.0 = Pointed
    hull_taper_rear     As lerp_duo = lerp_duo(0.5, 1.0, -0.2, 0.2) ' 1.0 = Rectangular back, 0.0 = Pointed
    hull_detail_color_offset As hsva_ld = f_hsva_ld( lerp_duo(0,0), lerp_duo(0,-0.1), lerp_duo(-0.1, 0.1), lerp_duo(0,0) ) ' Variation for details
    #else '' cartoony, over the top (Gemini suggestion after "something fun and playful" prompt)
    hull_length         As lerp_duo = lerp_duo(40, 80, -15, 15)
    hull_width          As lerp_duo = lerp_duo(20, 50, -10, 10)
    hull_color          As hsva_ld  = f_hsva_ld( lerp_duo(0, 1, 0, 1), lerp_duo(0.0, 0.1, .0, .3), lerp_duo(.05, 0.65, .0, .35), lerp_duo(1,1, 0, 0) )
    hull_taper_front    As lerp_duo = lerp_duo(0.0, 1.0, -0.3, 0.3)
    hull_taper_rear     As lerp_duo = lerp_duo(0.0, 1.0, -0.3, 0.3)
    hull_detail_color_offset As hsva_ld = f_hsva_ld( lerp_duo(0,0), lerp_duo(-0.1, 0.1), lerp_duo(-0.15, 0.15), lerp_duo(0,0) )
    #endif
    
    ' --- Cockpit ---
    has_cockpit         As lerp_duo = lerp_duo(0.8, 1.0, -0.1, 0.1)
    cockpit_rel_pos_y   As lerp_duo = lerp_duo(0.2, 0.5, -0.15, 0.15)
    cockpit_size        As lerp_duo = lerp_duo(4, 15, -3, 4)
    ' Cockpit glow can still be vibrant
    cockpit_glow_color  As hsva_ld  = f_hsva_ld( lerp_duo(0, 1, 0, 1), lerp_duo(.6, 1.0, .0, .3), lerp_duo(1, 1, 0, 0), lerp_duo(1,1, 0, 0) )

    ' --- Engines ---
    #if 1 '' original
    engine_count        As lerp_duo = lerp_duo(1, 3, -0.5, 0.5) ' 1 to 3 engines (will be rounded)
    engine_size         As lerp_duo = lerp_duo(9, 12, 0, 4)
    engine_spacing      As lerp_duo = lerp_duo(0.5, 1.5, -0.2, 0.3) ' Multiplier relative to engine size
    engine_offset_y     As lerp_duo = lerp_duo(0.0, 0.8, -0.1, 0.2) ' How far behind the hull base the engine sits
    engine_color        as hsva_ld  = f_hsva_ld( lerp_duo(0, 1, 0, 1), lerp_duo(0.1, 0.2, .0, .4), lerp_duo(.08, 0.25, 0, .45), lerp_duo(1,1, 0, -.5) )
    engine_glow_color   As hsva_ld  = f_hsva_ld( lerp_duo(0, 1, 0, 1), lerp_duo(.0, .7, .0, .3), lerp_duo(1, 1), lerp_duo(1,1))
    engine_glow_size    As lerp_duo = lerp_duo(1.0, 1.0, -0.3, 0.5) ' Multiplier for glow radius relative to engine size
    engine_is_exotic    as lerp_duo = lerp_duo(0, .4, .6, -.4)
    
    #else '' cartoony, over the top (Gemini suggestion after "something fun and playful" prompt)
    engine_count        As lerp_duo = lerp_duo(1, 5, -1, 1)
    engine_size         As lerp_duo = lerp_duo(15, 15, -5, 5)
    engine_spacing      As lerp_duo = lerp_duo(0.8, 2.0, -0.3, 0.5)
    engine_offset_y     As lerp_duo = lerp_duo(0.0, 1.0, -0.2, 0.3)
    engine_color        as hsva_ld  = f_hsva_ld( lerp_duo(0, 1, 0, 1), lerp_duo(0.1, 0.2, .0, .4), lerp_duo(.08, 0.25, 0, .45), lerp_duo(1,1, 0, -.5) )
    engine_glow_color   As hsva_ld  = f_hsva_ld( lerp_duo(0, 1, 0, 1), lerp_duo(.7, 1.0, .0, -.35), lerp_duo(1, 1, 0, 0), lerp_duo(1,1, 0, 0) )
    engine_glow_size    As lerp_duo = lerp_duo(1.0, 2.0, -0.5, 1.0)
    engine_is_exotic    as lerp_duo = lerp_duo(0, 1, 1, -1)
    #endif
    
     ' --- Wings ---
    has_wings           As lerp_duo = lerp_duo(0.6, 1.0, -0.2, 0.2) ' Chance of having wings
    #if 1 '' original
    wing_attach_y       As lerp_duo = lerp_duo(-0.2, 0.2, -0.15, 0.15) ' Relative Y attach point (-0.5=rear, 0=center, 0.5=front)
    wing_span           As lerp_duo = lerp_duo(30, 100, -15, 20) ' Total width across wings
    wing_chord_root     As lerp_duo = lerp_duo(15, 40, -5, 10)   ' Width of wing at hull
    wing_chord_tip      As lerp_duo = lerp_duo(5, 25, -4, 8)    ' Width of wing at tip
    wing_sweep          As lerp_duo = lerp_duo(-20, 40, -10, 15) ' Sweep angle in degrees (positive = swept back)
    wing_color          As hsva_ld  = f_hsva_ld( lerp_duo(0, 1, 0, 1), lerp_duo(0, .15, .0, .3), lerp_duo(.3, .5, -.3, .4), lerp_duo(1,0.7, 0, -.3) )
    wing_thickness      As lerp_duo = lerp_duo(1.5, 3.0, -0.5, 1.0) ' Visual thickness for edge/outline
    #else '' cartoony, over the top
    wing_attach_y       As lerp_duo = lerp_duo(-0.4, 0.4, -0.25, 0.25)
    wing_span           As lerp_duo = lerp_duo(40, 150, -20, 30)
    wing_chord_root     As lerp_duo = lerp_duo(15, 50, -10, 15)
    wing_chord_tip      As lerp_duo = lerp_duo(2, 30, -5, 10)
    wing_sweep          As lerp_duo = lerp_duo(-45, 45, -20, 20)
    wing_color          As hsva_ld  = f_hsva_ld( lerp_duo(0, 1, 0, 1), lerp_duo(0.01, 0.24, .0, .4), lerp_duo(.1, 0.5, -.1, .5), lerp_duo(1,1, 0, 0) )
    wing_thickness      As lerp_duo = lerp_duo(0.8, 4.0, -0.3, 1.5)
    #endif
    
    ' --- Lights ---
    light_count         As lerp_duo = lerp_duo(0, 10, -2, 3)
    light_size          As lerp_duo = lerp_duo(1.15, 1.3, 0.0, 0.7) '' 2025 Apr 28
    light_color         As hsva_ld  = f_hsva_ld( lerp_duo(0,1,0,1), lerp_duo(0.6, 1.0, .0, .2), lerp_duo(1, 1, 0, 0), lerp_duo(1,1, 0, 0))
    light_is_blinking   As lerp_duo = lerp_duo(0.6, 0.9, 0.0, 0.1)
    light_blink_freq    As lerp_duo = lerp_duo(0.3, 3.0, -0.2, 1.0)
    light_blink_duty    As lerp_duo = lerp_duo(0.2, 0.8, -0.1, 0.1)
    light_blink_offset  As lerp_duo = lerp_duo(0, 1, 0, 0)

    ' --- Plating/Greebles ---
    has_plating         As lerp_duo = lerp_duo(0.5, 1.0, -0.1, 0.1)
    plating_line_count  As lerp_duo = lerp_duo(5, 25, -5, 10)
    plating_line_thickness As lerp_duo = lerp_duo(0.5, 2.0, -0.2, 0.5)
    plating_color_offset As hsva_ld = f_hsva_ld( lerp_duo(0,0), lerp_duo(-0.1, 0.1), lerp_duo(-0.15, 0.15), lerp_duo(0,0) )

    ' --- Struts ---
    strut_thickness     As lerp_duo = lerp_duo(1.0, 5.0, -0.3, 1.5)
    strut_color_offset  As hsva_ld = f_hsva_ld( lerp_duo(0,0), lerp_duo(-0.1, -0.2), lerp_duo(-0.1, -0.2), lerp_duo(0,0) )

    has_wobbly_antenna As Single ' Probability (0.0 to 1.0)
    antenna_length As Single     ' Length of the antenna
    antenna_thickness As Single  ' Thickness of the line
    antenna_wobble_freq As Single ' How fast it wobbles
    antenna_wobble_amp As Single  ' How far it wobbles (degrees)

End Type

    ' macro to create EPOCH & GEN subroutines  by dafhi
    '
#macro mac_subname_EvsG_spaceship( fname, e_vs_g, e_vs_g_rgba )
Sub fname( Byref p As spaceship_prototype )

    ' --- Overall ---
    e_vs_g p.symmetry_chance

    ' --- Hull ---
    e_vs_g p.hull_length
    e_vs_g p.hull_width
    e_vs_g_rgba p.hull_color
    e_vs_g p.hull_taper_front
    e_vs_g p.hull_taper_rear
    e_vs_g_rgba p.hull_detail_color_offset

    ' --- Cockpit ---
    e_vs_g p.has_cockpit
    e_vs_g p.cockpit_rel_pos_y
    e_vs_g p.cockpit_size
    e_vs_g_rgba p.cockpit_glow_color

    ' --- Engines ---
    e_vs_g p.engine_count
    e_vs_g p.engine_size
    e_vs_g p.engine_spacing
    e_vs_g p.engine_offset_y
    e_vs_g_rgba p.engine_color
    e_vs_g_rgba p.engine_glow_color
    e_vs_g p.engine_glow_size
    e_vs_g p.engine_is_exotic

    ' --- Wings ---
    e_vs_g p.has_wings
    e_vs_g p.wing_attach_y
    e_vs_g p.wing_span
    e_vs_g p.wing_chord_root
    e_vs_g p.wing_chord_tip
    e_vs_g p.wing_sweep
    e_vs_g_rgba p.wing_color
    e_vs_g p.wing_thickness

    ' --- Lights ---
    e_vs_g p.light_count
    e_vs_g p.light_size
    e_vs_g_rgba p.light_color
    e_vs_g p.light_is_blinking   ' Blink anim
    e_vs_g p.light_blink_freq
    e_vs_g p.light_blink_duty
    e_vs_g p.light_blink_offset

    ' --- Plating/Greebles ---
    e_vs_g p.has_plating
    e_vs_g p.plating_line_count
    e_vs_g p.plating_line_thickness
    e_vs_g_rgba p.plating_color_offset

    ' --- Struts ---
    e_vs_g p.strut_thickness
    e_vs_g_rgba p.strut_color_offset

    p.has_wobbly_antenna = rng ^ 2 ' Or maybe bias it lower: rng * rng
    p.antenna_length = 5 + rng * 15 ' Adjust range as needed
    p.antenna_thickness = 0.8 + rng * 0.7
    p.antenna_wobble_freq = 2.0 + rng * 4.0 ' Wobbles per second
    p.antenna_wobble_amp = 15 + rng * 30   ' Max wobble angle in degrees

End Sub
#endmacro ' mac_subname_EvsG_spaceship

mac_subname_EvsG_spaceship( epoch_spaceship, epoch_LD, epoch_hsva_ld )
mac_subname_EvsG_spaceship( likeness_spaceship, gen_LD, gen_hsva_ld )

Function get_derived_color( Byref base_color As hsva_ld, Byref offset_color As hsva_ld ) As Ulong '' Gemini 2.5 Pro
    Dim h As Single = clamp(base_color.h + offset_color.h)
    Dim s As Single = clamp(base_color.s + offset_color.s)
    Dim v As Single = clamp(base_color.v + offset_color.v)
    Dim a As Single = clamp(base_color.a + offset_color.a)
    Return hsv(h, s, v, a * 255.499)
End Function

dim as single sin_a, cos_a, scale, cx, cy

    Function transform_local( vx As Single, vy As Single ) As v2d
        Dim rx As Single = (vx * cos_a - vy * sin_a) * scale
        Dim ry As Single = (vx * sin_a + vy * cos_a) * scale ' <<< FIXED: Original code had swapped sin/cos in ry
        Return Type(cx + rx, cy + ry)
    End Function
    
        Using Rast ' Make Rast functions available

    Sub transformed_line(x1 As Single, y1 As Single, x2 As Single, y2 As Single, col As UInteger, thickness As Single = 1.0) '' Gemini 2.5 Pro
        Var v1 = transform_local(x1, y1)
        Var v2 = transform_local(x2, y2)
            thickLine v1.x, v1.y, v2.x, v2.y, col, thickness '' dafhi 2025 Apr 16
    End Sub

    Sub transformed_quad(x1 As Single, y1 As Single, x2 As Single, y2 As Single, x3 As Single, y3 As Single, x4 As Single, y4 As Single, col As UInteger) '' Gemini 2.5 Pro
        Var v1 = transform_local(x1, y1)
        Var v2 = transform_local(x2, y2)
        Var v3 = transform_local(x3, y3)
        Var v4 = transform_local(x4, y4)
        triangle(v1, v2, v3, col)
        triangle(v1, v3, v4, col)
    End Sub

    Sub transformed_dot(x As Single, y As Single, col As UInteger, radius As Single, alpha_mult As Single = 1.0) '' Gemini 2.5 Pro
        Var v = transform_local(x, y)
        aadot(v.x, v.y, col, radius * scale, alpha_mult)
    End Sub
    
    Sub DrawWingShape( ByRef v0 As v2d, ByRef v1 As v2d, ByRef v2 As v2d, ByRef v3 As v2d, _
                       ByVal w_col As Ulong, ByVal w_thick As Single)

        ' Assume triangle takes already-transformed points, and transformed_line takes local points

          ' This assumes transform_local uses the global cx, cy, scale, cos_a, sin_a
          Dim t_v0 As v2d = transform_local(v0.x, v0.y)
          Dim t_v1 As v2d = transform_local(v1.x, v1.y)
          Dim t_v2 As v2d = transform_local(v2.x, v2.y)
          Dim t_v3 As v2d = transform_local(v3.x, v3.y)

        ' Assuming 'triangle' takes pre-transformed vertices
        triangle( t_v0, t_v1, t_v2, w_col )
        triangle( t_v0, t_v2, t_v3, w_col )
        
        Const WING_LE_COL_MOD = &hFFC0C0C0
        Const WING_TIP_COL_MOD = &hFFE0E0E0
        Const WING_TE_COL_MOD = &hFFB0B0B0

        ' Assuming 'transformed_line' takes local coords and transforms internally
        ' If not, you'd call 'Line (t_v1.x, t_v1.y)-(t_v2.x, t_v2.y), ...'
        transformed_line(v1.x, v1.y, v2.x, v2.y, w_col * WING_LE_COL_MOD, w_thick)      ' Leading edge
        transformed_line(v2.x, v2.y, v3.x, v3.y, w_col * WING_TIP_COL_MOD, w_thick*0.8)  ' Tip
        transformed_line(v3.x, v3.y, v0.x, v0.y, w_col * WING_TE_COL_MOD, w_thick)      ' Trailing edge

    End Sub
    
    Function GetHullWidthAtY( ByVal y As Single, _
                              ByVal h_half_wid As Single, _
                              ByVal h_half_len As Single, _
                              ByVal taper_f As Single, _
                              ByVal taper_r As Single ) As Single

        If h_half_len <= 0 Then Return h_half_wid ' Avoid division by zero

        Dim hull_w As Single
        If y > 0 Then ' Front half
            ' Clamp y relative position between 0 and 1 for the front half
            Dim as single rel_y_front = Min(1.0, Max(0.0, y / h_half_len))
            hull_w = h_half_wid * (taper_f + (1.0 - taper_f) * (1.0 - rel_y_front))
        Else ' Rear half (or exactly center)
            ' Clamp y relative position between -1 and 0 for the rear half
            Dim as single rel_y_rear = Min(0.0, Max(-1.0, y / h_half_len))
            hull_w = h_half_wid * (taper_r + (1.0 - taper_r) * (1.0 + rel_y_rear))
        End If
        Return hull_w
    End Function

#define LIGHT_WING_ATTACH_CHANCE 0.4
#define LIGHT_HULL_SIDE_ATTACH_CHANCE 0.7 ' Cumulative with wing chance

Sub draw_spaceship( Byref p As spaceship_prototype, _ '' Gemini 2.5 Pro
                   _cx As single, _cy As single, _
                   _scale As single = 1.0, _
                   angle_deg As single = 0.0, _
                   current_time As Double = 0.0 )

    ' -- Pre-calculate Transformation --
    Dim angle_rad As Single = angle_deg * (3.14159265 / 180.0)
    cos_a = Cos(angle_rad)
    sin_a = Sin(angle_rad)
    cx = _cx : cy = _cy : scale = _scale

    Dim is_symmetric As Boolean = (rng < p.symmetry_chance) ' Generate instance symmetry

    ' Hull dimensions
    Dim as single h_len = p.hull_length, h_half_len = h_len * 0.5
    Dim as single h_wid = p.hull_width, h_half_wid = h_wid * 0.5
    Dim taper_f As Single = p.hull_taper_front ' 1 = square, 0 = point
    Dim taper_r As Single = p.hull_taper_rear  ' 1 = square, 0 = point
    Dim As Ulong hull_col = get_ld_color(p.hull_color), strut_col = get_derived_color(p.hull_color, p.strut_color_offset)
    Dim detail_col_offset As Ulong = get_derived_color(p.hull_color, p.hull_detail_color_offset) ' For generic details
    dim as single strut_thick = p.strut_thickness

    ' -- Draw Components (Back to Front Order) --

    ' 1. Engine Glows
    Dim eng_count As Integer = max(1, min(5, int(p.engine_count + 0.5)))
    Dim eng_size As Single   = p.engine_size
    Dim eng_spacing As Single = p.engine_spacing * eng_size
    Dim eng_offset As Single = p.engine_offset_y * eng_size ' How far back
    Dim eng_glow_rad As Single = (eng_size * 0.6) * p.engine_glow_size
    
    dim as single         exa = p.engine_is_exotic
    dim as long           ex = p.engine_is_exotic > rng
    dim byref as hsva_ld  q = p.engine_glow_color
    dim as single hsv_a = q.a * 255.499
    dim as ulong eng_glow_col  = hsv( q.h, iif(ex, clamp(exa), 1),              1, hsv_a )
    Dim As Ulong eng_glow_core = hsv( q.h, iif(ex,              1,0) , iif(ex,0,1), hsv_a )

    Dim total_engine_width As Single = (eng_count - 1) * eng_spacing
    Dim eng_start_x As Single = -total_engine_width * 0.5
    Dim eng_y As Single = -h_half_len - eng_offset - eng_glow_rad * 0.3 ' Position behind hull rear + offset

    '' drawing order: engine aura, glow center, component (step 6)
    Dim engine_offsets(0 To eng_count - 1) As Single ' Store offsets
    
    For i As Integer = 0 To eng_count - 1
        engine_offsets(i) = eng_start_x + i * eng_spacing
        If Not is_symmetric And eng_count > 1 Then
            engine_offsets(i) += (rng - 0.5) * eng_spacing * 0.6
        End If
    Next

    For i As Integer = 0 To eng_count - 1
        transformed_dot(engine_offsets(i), eng_y, eng_glow_col, eng_glow_rad, 1.0)
    Next
    For i As Integer = 0 To eng_count - 1
        transformed_dot(engine_offsets(i), eng_y, eng_glow_core, eng_glow_rad * 0.7, 1.1)
    Next
    
    ' 2. Wings (if any)
    Dim wings_present As Boolean = (p.has_wings > 0.3)
    Dim w_span As Single, w_att_y As Single ' Declare here for later use (pods)
        Dim hull_w_at_wing_attach As Single
    If wings_present Then
        w_span = p.wing_span
        Dim w_root As Single = p.wing_chord_root
        Dim w_tip As Single  = p.wing_chord_tip
        w_att_y = p.wing_attach_y * h_half_len ' Y attach point relative to hull center
        Dim w_sweep As Single= p.wing_sweep
        Dim w_col As Ulong   = get_ld_color(p.wing_color)
        Dim w_thick As Single = p.wing_thickness

        Dim w_half_span As Single = w_span * 0.5
        Dim w_sweep_rad As Single = w_sweep * (3.14159265 / 180.0)
        Dim w_sweep_offset As Single = Tan(w_sweep_rad) * w_half_span ' Use Tan for offset calculation

        ' Wing points (relative to ship center 0,0)
        Dim root_fwd As Single = w_att_y + w_root * 0.5
        Dim root_aft As Single = w_att_y - w_root * 0.5
        Dim tip_fwd As Single  = w_att_y + w_tip * 0.5 - w_sweep_offset ' Adjusted by sweep
        Dim tip_aft As Single  = w_att_y - w_tip * 0.5 - w_sweep_offset ' Adjusted by sweep

        ' Define attachment width based on hull taper at attach point Y
        ' Interpolate hull half-width at wing attach point Y
        Dim hull_w_at_wing_attach As Single = GetHullWidthAtY(w_att_y, h_half_wid, h_half_len, taper_f, taper_r)
        hull_w_at_wing_attach = Max(hull_w_at_wing_attach, 5.0) ' Ensure minimum attach width

        ' Right Wing Vertices
        Dim wr_v0 As v2d = Type( hull_w_at_wing_attach, root_aft) ' Inner aft
        Dim wr_v1 As v2d = Type( hull_w_at_wing_attach, root_fwd) ' Inner fwd
        Dim wr_v2 As v2d = Type( w_half_span, tip_fwd)      ' Outer fwd
        Dim wr_v3 As v2d = Type( w_half_span, tip_aft)      ' Outer aft
        DrawWingShape(wr_v0, wr_v1, wr_v2, wr_v3, w_col, w_thick) ' Pass transform params

        ' Left Wing Vertices (mirrored X)
        Dim wl_v0 As v2d = Type(-wr_v0.x, wr_v0.y)
        Dim wl_v1 As v2d = Type(-wr_v1.x, wr_v1.y)
        Dim wl_v2 As v2d = Type(-wr_v2.x, wr_v2.y)
        Dim wl_v3 As v2d = Type(-wr_v3.x, wr_v3.y)
        DrawWingShape(wl_v0, wl_v1, wl_v2, wl_v3, w_col, w_thick) ' Pass transform params

    End If

    ' 3. Hull
    Dim h_v0 As v2d = Type(-h_half_wid * taper_r, -h_half_len) ' Rear Left
    Dim h_v1 As v2d = Type( h_half_wid * taper_r, -h_half_len) ' Rear Right
    Dim h_v2 As v2d = Type( h_half_wid,             0)          ' Mid Right
    Dim h_v3 As v2d = Type( h_half_wid * taper_f,  h_half_len) ' Front Right
    Dim h_v4 As v2d = Type(-h_half_wid * taper_f,  h_half_len) ' Front Left
    Dim h_v5 As v2d = Type(-h_half_wid,             0)          ' Mid Left

    transformed_quad(h_v0.x, h_v0.y, h_v1.x, h_v1.y, h_v2.x, h_v2.y, h_v5.x, h_v5.y, hull_col) ' Rear Half
    transformed_quad(h_v5.x, h_v5.y, h_v2.x, h_v2.y, h_v3.x, h_v3.y, h_v4.x, h_v4.y, hull_col) ' Front Half

    ' 6. Engines (Bodies)
    Dim eng_body_col As Ulong = get_ld_color(p.engine_color)'hull_col * &hFF909090 or 255 shl 24
    For i As Integer = 0 To eng_count - 1
        Dim ex As Single = engine_offsets(i)
        var e_half_sz_w = eng_size * 0.5, e_half_sz_l = eng_size * 0.5, _end = e_half_sz_l * .2
        var body_y_center = eng_y + e_half_sz_l * 0.5
        dim as v2d ev0 = Type(ex - e_half_sz_w, body_y_center - _end), _
        ev1 = Type(ex + e_half_sz_w, body_y_center - _end), _
        ev2 = Type(ex + e_half_sz_w, body_y_center + e_half_sz_l), _
        ev3 = Type(ex - e_half_sz_w, body_y_center + e_half_sz_l)
        transformed_quad(ev0.x, ev0.y, ev1.x, ev1.y, ev2.x, ev2.y, ev3.x, ev3.y, eng_body_col)

        ' Draw strut if engine is significantly offset? (Could check eng_offset)
        If Abs(eng_offset) > eng_size * 0.3 Then
             transformed_line(ex, -h_half_len, ex, body_y_center-_end, strut_col, strut_thick * 0.8)
        End If
    Next

    ' 7. Plating Lines / Greebles (on top of hull)
    If p.has_plating > 0.5 Then
        Dim line_count As Integer = max(0, min(30, Int(p.plating_line_count + 0.5)))
        Dim plate_col As Ulong = get_derived_color(p.hull_color, p.plating_color_offset)
        dim as single plate_thick = p.plating_line_thickness
        For i As Integer = 1 To line_count
            ' Simple approach: Random lines across the hull bounds
            Dim as single r_len = rng * h_len
            Dim as single r_wid = rng * h_wid
            Dim as single x1 = (rng - 0.5) * r_wid
            Dim as single y1 = (rng - 0.5) * r_len
            Dim as single x2 = x1 + (rng - 0.5) * h_wid * 0.3 ' Short lines
            Dim as single y2 = y1 + (rng - 0.5) * h_len * 0.3

            ' Clamp lines roughly to hull polygon? (Complex) Or just draw them.
            transformed_line(x1, y1, x2, y2, plate_col, plate_thick)

             ' Add occasional small squares/circles as greebles
             If rng < 0.1 Then
                 Dim as single gx = (rng - 0.5) * h_wid * 0.9
                 Dim as single gy = (rng - 0.5) * h_len * 0.9
                 Dim as single gsize = 1.0 + rng * 2.0
                 If rng < 0.5 then
                    transformed_quad(gx-gsize, gy-gsize, gx+gsize, gy-gsize, gx+gsize, gy+gsize, gx-gsize, gy+gsize, plate_col)
                 Else
                    transformed_dot(gx, gy, plate_col, gsize)
                 End If
             End If
        Next
    End If

    ' 9. Cockpit (if any)
    If p.has_cockpit > 0.4 Then

        Dim cockp_y As Single = p.cockpit_rel_pos_y * h_half_len
        Dim cockp_sz As Single = p.cockpit_size
        @q = @p.cockpit_glow_color
        dim as single hsv_h = (4+rng*3)/12
        Dim cockp_glow_col As Ulong = hsv(hsv_h, q.s, 1, 255)' get_ld_color(p.cockpit_glow_color)

        ' Assume centered X for now
        Dim as single cp_base_x = 0.0
        If Not is_symmetric Then cp_base_x = (rng - 0.5) * h_wid * 0.1 ' Slight offset if asymmetric

'        transformed_dot(cp_base_x, cockp_y, cockp_glow_col, cockp_sz * 0.7, 0.8 ) ' Glow
        Dim frame_col As Ulong = hull_col * &hFFA0A0A0
        ' Maybe draw a small trapezoid shape for cockpit instead of dot?
        Dim as single cp_w = cockp_sz
        Dim as single cp_l = cockp_sz * 1.2
        Dim as single cp_taper = 0.6
        Dim as v2d cpv0 = Type(cp_base_x - cp_w*0.5*cp_taper, cockp_y - cp_l*0.5)
        Dim as v2d cpv1 = Type(cp_base_x + cp_w*0.5*cp_taper, cockp_y - cp_l*0.5)
        Dim as v2d cpv2 = Type(cp_base_x + cp_w*0.5, cockp_y + cp_l*0.5)
        Dim as v2d cpv3 = Type(cp_base_x - cp_w*0.5, cockp_y + cp_l*0.5)
        transformed_quad(cpv0.x, cpv0.y, cpv1.x, cpv1.y, cpv2.x, cpv2.y, cpv3.x, cpv3.y, frame_col)
        '@q = @p.hull_color
        transformed_dot(cp_base_x, cockp_y, hsv( hsv_h, .35, (1), 255), cockp_sz * 0.55, 1. ) ' Darker frame/glass

    End If

    '' may become used by other parts
    Dim w_att_y_rel As Single = p.wing_attach_y ' Relative attach point (-0.5 to 0.5)
    Dim w_att_y_abs As Single = w_att_y_rel * h_half_len ' Absolute Y coordinate

    ' 11. Lights (Blinking animation remains as before)
    Dim l_count As Integer = max(0, min(10, int(p.light_count + 0.5)))
    If l_count > 0 Then
        @q = @p.light_color
        'Dim light_base_color_params As hsva_ld = p.light_color
        Dim lights_blink As Boolean = (p.light_is_blinking > 0.5)
        For i As Integer = 1 To l_count
            Dim l_size As Single = p.light_size' + rng * p.light_size_v
            'Dim as single current_light_hue = light_base_color_params.h' + (rng * p.light_hue_v)
            Dim side As Single = Iif(is_symmetric, Iif(i Mod 2 = 0, 1, -1), rng*2-1)
            Dim lx As Single = 0 : Dim ly As Single = 0
            Dim as single r_choice = rng
            If r_choice < LIGHT_WING_ATTACH_CHANCE And wings_present Then ' Wingtip lights (attach to base span tip)
                 Dim base_w_sweep_rad As Single = p.wing_sweep * DEG2RAD
                 Dim base_w_sweep_offset As Single = Tan(base_w_sweep_rad) * (w_span*0.5)
                 Dim tip_y As Single = w_att_y_abs - base_w_sweep_offset
                lx = side * w_span * 0.5 * (0.9 + rng*0.1)
                ly = tip_y + (rng - 0.5) * p.wing_chord_tip
                 ' TODO: If wings are animated, light pos should follow current tip pos
            Elseif r_choice < LIGHT_HULL_SIDE_ATTACH_CHANCE Then ' Hull side lights
                Dim as single hull_y_pos = (rng * h_len) - h_half_len
                Dim hull_w_at_light_y As Single = GetHullWidthAtY(hull_y_pos, h_half_wid, h_half_len, taper_f, taper_r)
                lx = side * hull_w_at_light_y : ly = hull_y_pos
            Else ' Hull front/rear lights
                Dim as long front_back = sgn(rng - 0.5)
                Dim as single taper_val = Iif(front_back > 0, taper_f, taper_r)
                lx = (rng - 0.5) * h_wid * taper_val
                ly = front_back * h_half_len * (0.9 + rng * 0.1)
            End If
            If not is_symmetric then lx *= (0.5 + rng*0.7) : ly += (rng-0.5)*h_len*0.1 End If
            Dim light_alpha_mult As Single = 1.0
            If lights_blink Then
                Dim as single blink_phase_offset = p.light_blink_offset + (i * 0.137)
                blink_phase_offset -= Int(blink_phase_offset)
                Dim blink_cycle_pos As Single = (current_time + blink_phase_offset / p.light_blink_freq) * p.light_blink_freq
                blink_cycle_pos -= Int(blink_cycle_pos)
                If blink_cycle_pos > p.light_blink_duty Then light_alpha_mult = 0.1 End If
            End If
            
            '' added glowy white center - dafhi
            gen_hsva_ld q
            Dim col_o As Ulong = hsv( q.h, q.s, 1, q.a*255.499)
            Dim col_i As Ulong = hsv( q.h, 0, 1, q.a*255.499)
            If light_alpha_mult > 0.05 Then transformed_dot(lx, ly, col_o, l_size, light_alpha_mult) End If
            If light_alpha_mult > 0.05 Then transformed_dot(lx, ly, col_i, l_size*.6, light_alpha_mult) End If
        Next
    End If

    ' 12. Wobbly Antenna (Hilarious Addition)
    If p.has_wobbly_antenna > 0.95 Then ' Adjust probability threshold
        Dim antenna_col As Ulong = hsv( rng, rng, 1 )'detail_col_offset ' Use a derived color
        Dim As Single antenna_base_x, antenna_base_y, base_angle_deg = 90 ' Pointing "up" relative to ship forward

        ' --- Placement Logic ---
        antenna_base_y = h_half_len * (0.6 + rng * 0.3) ' Place on front half
        Dim hull_w_at_base As Single = GetHullWidthAtY(antenna_base_y, h_half_wid, h_half_len, taper_f, taper_r)
        antenna_base_x = (rng - 0.5) * hull_w_at_base * 1.8 ' Can stick out further
        
        ' --- Animation Logic ---
        Dim wobble_rad As Single = Sin(current_time * p.antenna_wobble_freq * 2 * 3.14159) * (p.antenna_wobble_amp * DEG2RAD)
        Dim final_angle_rad As Single = (base_angle_deg * DEG2RAD) + wobble_rad

        ' --- Calculate Tip Position ---
        Dim antenna_tip_x As Single = antenna_base_x + Cos(final_angle_rad) * p.antenna_length
        Dim antenna_tip_y As Single = antenna_base_y + Sin(final_angle_rad) * p.antenna_length ' Sin for Y because 0 rad = right, 90 deg/PI/2 rad = up

        ' --- Draw ---
        transformed_line(antenna_base_x, antenna_base_y, antenna_tip_x, antenna_tip_y, antenna_col, p.antenna_thickness)
        ' Optional: Add a small dot at the tip
        transformed_dot(antenna_tip_x, antenna_tip_y, antenna_col, p.antenna_thickness * 1.5)

    End If

End Sub

end namespace ' -- procgen_spaceship



#include "fbgfx.bi" ' For multikey

var scr_w = 960
var scr_h = 720
screenres scr_w, scr_h, 32

var tile_w = 300 ' Increased size for better detail
var tile_h = 225

    using rast '' Rast namespace for drawing functions

dim as any ptr im = imagecreate(tile_w, tile_h)
render_target im

    using procgen_spaceship
dim as spaceship_prototype ship_template '' Gemini 2.5 Pro

'' standard-ish game loop
dim as double likeness_trigger
dim as single global_ship_scale = 0.9 ' Base scale for ships in tiles
dim as single global_ship_angle = 0.0  ' Base angle for ships in tiles
dim as boolean needs_redraw = true ' Start with a redraw needed
dim as double t0 = timer, demo_time = 100
dim as double frame_count = 0
dim as double current_time, last_frame_time, tp, dt2, fps
dim as ulongint current_epoch_seed
randomize

' --- Main Loop ---
do
    tp = current_time
    current_time = timer - t0
    var dt = current_time - tp

    if multikey(&h01) then exit do ' Exit on Escape key
  
    if current_time >= likeness_trigger then
        current_epoch_seed = rnd * culngint(-1) '' hash logistics by dafhi
        myhash.reset current_epoch_seed
        epoch_spaceship ship_template '' Apply new epoch to the template.  i use my rng #define for the ship
        likeness_trigger += 3.5
        global_ship_scale = tile_w / 280
    end if

     global_ship_angle += 10 * (dt)
     if global_ship_angle >= 360 then global_ship_angle -= 360

        dim as integer step_x = tile_w + 1
        dim as integer step_y = tile_h + 1
        
        '' draw_spaceship generates individuals via custom rng
        myhash.reset current_epoch_seed

            screenlock
  
            for iy as long = 0 to scr_h - step_y step step_y
        var lx = clng(tile_w * .1)
        var ly = clng(tile_h * .1) + iy
        
        for ix as long = 0 to scr_w - step_x step step_x

        '' clear
        Line im, (0,0)-(rast.imv.wm, rast.imv.hm), RGBA(20, 20, 30, 255), bf ' Opaque Dark space blue

        '' rng stream.  writes to lerp_duo.ret, cast as single each lerp_duo instance (ship color etc)
        likeness_spaceship ship_template

        draw_spaceship ship_template, tile_w/2, tile_h/2, global_ship_scale, global_ship_angle, current_time
        Line im, (0,0)-(rast.imv.wm, rast.imv.hm), Rgb(100,100,120), b

        put (lx+ix,ly), im, pset
  
        next ix
        next iy

        Locate 2,2: Print "epoch-inspired Procedural Spaceships [ESC to Exit]"
        Locate 5,2: Print Using "Global Scale: #.##"; global_ship_scale
        locate 7,2: Print Using "FPS: ##.#"; fps
        locate 6,2: Print Using "Demo Time: ##.#"; demo_time - current_time
        screenunlock

        ' --- Calculate FPS ---
        if current_time - last_frame_time >= 1.0 then
          dt2 = dt
          dt = timer - t0 - current_time
          fps = 2 / (dt + dt2)
          last_frame_time = current_time
        endif
        if current_time > demo_time then exit do

    Sleep 5, 1 ' Sleep briefly to yield CPU, 1 allows event processing (Gemini comment)

loop

_gfx_release im
sleep
Last edited by dafhi on Apr 30, 2025 18:07, edited 9 times in total.
rdc
Posts: 1745
Joined: May 27, 2005 17:22
Location: Texas, USA
Contact:

Re: procedural spaceships

Post by rdc »

paul doe wrote: Apr 16, 2025 13:15 Very cool. Can Wave Function Collapse be used in these cases, though? It seems to work well with grids, but could it work here as well?
Your algorithm is working fine, so there isn't any pressing need to change it. However, Wave Function Collapse works with any object you are trying to create from a set of other objects. It is widely used in generating maps, but Townscaper employs it to build houses, similarly to how you are creating a spaceship. In your case, you would generate the pieces of the ship and then use WFC to create the actual ships in different configurations. You can think of it as a rule-based system. The base part could be A, for example. What pieces connect to part A? All the pieces that connect to part A form a set of potential connections you can make. This is analogous to the wave function in quantum mechanics, where a particle can exist in a set of different states simultaneously, called a superposition of states. Your base part is in a superposition of states, where all the pieces that can connect to the base are possible choices. Once you make a choice, all those possibilities "collapse" into a single state. If you connect part C to A, you then have another set of possibilities to choose from since you now include C in the mix, and the process repeats. What is nice about this algorithm is that you don't encounter the problem of mismatched parts, since the algorithm only matches compatible pieces. There is a possibility of running out of valid connections, but I don't see that as a problem in your use case. In your case, it probably isn't an improvement, but if you wanted to use digital art for the ship's components, then this might work for you. Just something to keep in mind.
jdebord
Posts: 554
Joined: May 27, 2005 6:20
Location: Limoges, France
Contact:

Re: procedural spaceships

Post by jdebord »

FreePascal programs for Wave Function Collapse :

https://github.com/PascalCorpsman/mini_ ... rlap_model

https://github.com/PascalCorpsman/mini_ ... Tile_model

Could be adapted to FreeBASIC.
Post Reply