Wrote r4. Not a full game, but we have an engine showcase in haskell
This commit is contained in:
parent
f1d42f37b9
commit
b1c5fca4b1
@ -5,7 +5,15 @@
|
||||
{-# LANGUAGE NamedFieldPuns #-}
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
|
||||
module Allie (justFuckingDoSomething) where
|
||||
module Allie (WlKeyboardKeyState, LucyFace, LucyFaceFixedSize, AliceGenericMeshHand, AliceShinyMeshHand,
|
||||
AliceGenericMeshInstance(..), AliceShinyMeshInstance(..), AlicePointLight(..), alicePipeline0PointLightMaxCount,
|
||||
Callbacks(..), aliceMainloop, newAlice, aliceSetSkyColor, aliceNewLucyFace,
|
||||
aliceLucyFaceOfSize, lucyFaceAddGlyphs, aliceClearText, aliceAddText,
|
||||
aliceAddGenericMeshHand, aliceGenericMeshResizeInstanceArr, aliceGenericMeshSetInst,
|
||||
aliceAddShinyMeshHand, aliceShinyMeshResizeInstanceArr, aliceShinyMeshSetInst, aliceGetCamBack,
|
||||
aliceGetCamPos, aliceSetCamPos, aliceSetPointLightCount, aliceSetPointLight,
|
||||
aliceIsPressed
|
||||
) where
|
||||
|
||||
import Geom
|
||||
|
||||
@ -19,32 +27,59 @@ import qualified Data.Text
|
||||
import Data.Text.Encoding (encodeUtf8)
|
||||
import Data.ByteString (useAsCStringLen)
|
||||
|
||||
--import Geom
|
||||
|
||||
type Alice = Ptr Word8
|
||||
|
||||
foreign import ccall "Alice_new" newAlice :: IO Alice
|
||||
-- Ready
|
||||
foreign import ccall "allie_alice_new" newAlice :: IO Alice
|
||||
|
||||
data AliceAnotherFrameCap s = AliceAnotherFrameCap Alice
|
||||
data WlKeyboardKeyState = WlKeyboardKeyStateReleased | WlKeyboardKeyStatePressed | WlKeyboardKeyStateRepeated
|
||||
|
||||
foreign import ccall "wrapper" allieMkAliceOnWaylandKeyboardKey :: (Alice -> IO ()) -> IO (FunPtr (Alice -> IO ()))
|
||||
foreign import ccall "wrapper" allieMkAliceOnAnotherFrame :: (Alice -> IO ()) -> IO (FunPtr (Alice -> IO ()))
|
||||
-- data AliceAnotherFrameCap s = AliceAnotherFrameCap Alice
|
||||
|
||||
foreign import ccall "wrapper" allieMkAliceOnWaylandKeyboardKey ::
|
||||
(Ptr () -> Word32 -> Word32 -> IO ()) -> IO (FunPtr (Ptr () -> Word32 -> Word32 -> IO ()))
|
||||
foreign import ccall "wrapper" allieMkAliceOnAnotherFrame ::
|
||||
(Ptr () -> Float -> IO ()) -> IO (FunPtr (Ptr () -> Float -> IO ()))
|
||||
|
||||
-- All of that is inside Alice. They hold pointers to Alice
|
||||
type LucyFontFace = Ptr Word8
|
||||
-- Actually stores a pointer to rb-tree node in LucyFontFace tree. Must not be deleted by without caution
|
||||
type LucyFontFaceFixedSize = Ptr Word8
|
||||
type LucyFace = Ptr Word8
|
||||
-- Actually stores a pointer to rb-tree node in LucyFace tree. Must not be deleted by without caution
|
||||
type LucyFaceFixedSize = Ptr Word8
|
||||
|
||||
type AliceGenericMeshHand = Ptr Word8
|
||||
|
||||
type AliceShinyMeshHand = Ptr Word8
|
||||
|
||||
data AliceGenericMeshInstance = AliceGenericMeshInstance Mat4
|
||||
|
||||
instance Storable AliceGenericMeshInstance where
|
||||
sizeOf _ = sizeOf (undefined :: Mat4)
|
||||
alignment _ = 4
|
||||
peek _ = error "Please don't"
|
||||
poke ptr (AliceGenericMeshInstance modelT) = poke (castPtr ptr :: Ptr Mat4) modelT
|
||||
|
||||
-- model_t color_off color_on
|
||||
data AliceShinyMeshInstance = AliceShinyMeshInstance Mat4 Vec3 Vec3
|
||||
|
||||
instance Storable AliceShinyMeshInstance where
|
||||
sizeOf _ = sizeOf (undefined :: Mat4)
|
||||
alignment _ = 4
|
||||
peek _ = error "Don't do that, please"
|
||||
poke ptr (AliceShinyMeshInstance modelT colorOff colorOn) = do
|
||||
poke (castPtr ptr :: Ptr Mat4) modelT
|
||||
poke (castPtr (ptr `plusPtr` (sizeOf (undefined :: Mat4)) ) :: Ptr Vec3) colorOff
|
||||
poke (castPtr (ptr `plusPtr` (sizeOf (undefined :: Mat4)) `plusPtr` (sizeOf (undefined :: Vec3))) :: Ptr Vec3) colorOn
|
||||
|
||||
-- pos color
|
||||
data AlicePointLight = AlicePointLight Vec3 Vec3
|
||||
|
||||
alicePipeline0PointLightMaxCount :: Int
|
||||
alicePipeline0PointLightMaxCount = 120
|
||||
|
||||
data Callbacks = Callbacks {
|
||||
onWaylandKeyboardKey :: (Alice -> IO ()),
|
||||
onAnotherFrame :: (forall s. AliceAnotherFrameCap s -> IO ())
|
||||
onWaylandKeyboardKey :: (Word32 -> Word32 -> IO ()),
|
||||
onAnotherFrame :: (Float -> IO ())
|
||||
-- onAnotherFrame :: (forall s. AliceAnotherFrameCap s -> IO ())
|
||||
}
|
||||
|
||||
instance Storable Callbacks where
|
||||
@ -52,49 +87,121 @@ instance Storable Callbacks where
|
||||
alignment _ = 8
|
||||
peek _ = error "Зачем тебе?"
|
||||
poke ptr Callbacks{..} = do
|
||||
poke (castPtr ptr) =<< allieMkAliceOnWaylandKeyboardKey onWaylandKeyboardKey
|
||||
poke (castPtr ptr `plusPtr` 8) =<< allieMkAliceOnAnotherFrame onAnotherFramePrepared where
|
||||
onAnotherFramePrepared = (\alice -> onAnotherFrame (AliceAnotherFrameCap alice))
|
||||
poke (castPtr ptr) =<< allieMkAliceOnWaylandKeyboardKey (\_ -> onWaylandKeyboardKey)
|
||||
poke (castPtr ptr `plusPtr` 8) =<< allieMkAliceOnAnotherFrame (\_ -> onAnotherFrame)
|
||||
|
||||
foreign import ccall "Alice_mainloop" allieAliceMainloop :: Alice -> Ptr Callbacks -> IO ()
|
||||
foreign import ccall "allie_alice_mainloop" allieAliceMainloop :: Alice -> Ptr Callbacks -> IO ()
|
||||
|
||||
aliceMainloop :: Alice -> Callbacks -> IO ()
|
||||
aliceMainloop alice cb = alloca $ \ptr -> do
|
||||
poke ptr cb
|
||||
allieAliceMainloop alice ptr
|
||||
|
||||
-- These are only correct in another_frame_callback, actually
|
||||
foreign import ccall "Alice_clear_screen_text" allieAliceClearScreenText :: Alice -> IO ()
|
||||
--aliceClearScreenTextLabel :: AliceAnotherFrameCap s -> IO ()
|
||||
--aliceClearScreenTextLabel (AliceAnotherFrameCap alice) = allieAliceClearScreenText alice
|
||||
|
||||
aliceClearScreenTextLabel :: AliceAnotherFrameCap s -> IO ()
|
||||
aliceClearScreenTextLabel (AliceAnotherFrameCap alice) = allieAliceClearScreenText alice
|
||||
--aliceAddScreenTextLabel :: AliceAnotherFrameCap s -> String -> IO ()
|
||||
--aliceAddScreenTextLabel (AliceAnotherFrameCap alice) str = useAsCStringLen
|
||||
-- (encodeUtf8 $ Data.Text.pack $ str) $ \(cstr, len) ->
|
||||
-- allieAliceAddScreenTextLabel alice (castPtr cstr) (fromIntegral len)
|
||||
|
||||
foreign import ccall "allie_Alice_add_screen_text_label" allieAliceAddScreenTextLabel :: Alice -> Ptr Word8 -> Word64 -> IO ()
|
||||
|
||||
aliceAddScreenTextLabel :: AliceAnotherFrameCap s -> String -> IO ()
|
||||
aliceAddScreenTextLabel (AliceAnotherFrameCap alice) str = useAsCStringLen (encodeUtf8 $ Data.Text.pack $ str) $ \(cstr, len) -> allieAliceAddScreenTextLabel alice (castPtr cstr) (fromIntegral len)
|
||||
|
||||
my2onAnotherFrame :: p -> IO ()
|
||||
my2onAnotherFrame alicePerm = putStrLn "ahahhahah"
|
||||
|
||||
--allieRunAlice :: Callbacks ->
|
||||
|
||||
-- Function to run the main loop with callbacks
|
||||
justFuckingDoSomething :: IO ()
|
||||
justFuckingDoSomething = do
|
||||
alice <- newAlice
|
||||
state <- newIORef 67
|
||||
-- Create the Callbacks structure.
|
||||
let callbacks = Callbacks myonKeyboardKey my2onAnotherFrame where
|
||||
myonKeyboardKey _ = do
|
||||
old <- readIORef state
|
||||
writeIORef state (old + 1)
|
||||
putStrLn ("Doing" ++ show old ++ "this!")
|
||||
myonAnotherFrame alicePerm = do
|
||||
cur <- readIORef state
|
||||
aliceClearScreenTextLabel alicePerm
|
||||
aliceAddScreenTextLabel alicePerm ("Current value is = " ++ show cur)
|
||||
|
||||
useAsUtf8StringLen :: String -> (Ptr Word8 -> Word64 -> IO a) -> IO a
|
||||
useAsUtf8StringLen str cb = useAsCStringLen (encodeUtf8 $ Data.Text.pack $ str) $ \(cstr, len) -> cb (castPtr cstr) (fromIntegral len)
|
||||
|
||||
-- Allocate space for the struct, poke it, and pass to C.
|
||||
aliceMainloop alice callbacks
|
||||
foreign import ccall "allie_alice_set_sky_color" allieAliceSetSkyColor :: Alice -> Float -> Float -> Float -> Float -> IO ()
|
||||
|
||||
aliceSetSkyColor :: Alice -> Vec4 -> IO ()
|
||||
aliceSetSkyColor alice (Vec4 x y z w) = allieAliceSetSkyColor alice x y z w
|
||||
|
||||
foreign import ccall "allie_alice_new_lucy_face" allieAliceNewLucyFace :: Alice -> Ptr Word8 -> Word64 -> IO LucyFace
|
||||
|
||||
aliceNewLucyFace :: Alice -> String -> IO LucyFace
|
||||
aliceNewLucyFace alice str = useAsUtf8StringLen str $ \dt len -> allieAliceNewLucyFace alice dt len
|
||||
|
||||
-- Maps one to one. Fine
|
||||
foreign import ccall "allie_alice_lucy_face_of_size" aliceLucyFaceOfSize :: LucyFace -> Word32 -> IO LucyFaceFixedSize
|
||||
|
||||
-- Mapsone to one. Good. Too bad right now this only works with one range at a time
|
||||
-- (which means one range per image)
|
||||
foreign import ccall "allie_lucy_face_add_glyphs" lucyFaceAddGlyphs :: LucyFaceFixedSize -> Word32 -> Word32 -> IO ()
|
||||
|
||||
-- Maps one to one
|
||||
foreign import ccall "allie_alice_clear_text" aliceClearText :: Alice -> IO ()
|
||||
|
||||
foreign import ccall "allie_alice_add_text" allieAliceAddText :: Alice -> LucyFaceFixedSize -> Float -> Float -> Float -> Float ->
|
||||
Ptr Word8 -> Word64 -> Int32 -> Int32 -> IO ()
|
||||
|
||||
aliceAddText :: Alice -> LucyFaceFixedSize -> Vec4 -> String -> Int32 -> Int32 -> IO ()
|
||||
aliceAddText alice ffs (Vec4 cx cy cz cw) str startPosX startPosY = useAsUtf8StringLen str $ \dt len ->
|
||||
allieAliceAddText alice ffs cx cy cz cw dt len startPosX startPosY
|
||||
|
||||
foreign import ccall "allie_alice_add_generic_mesh_hand" allieAliceAddGenericMeshHand :: Alice ->
|
||||
Ptr Word8 -> Word64 -> Ptr Word8 -> Word64 -> Ptr Word8 -> Word64 -> Ptr Word8 -> Word64 -> IO AliceGenericMeshHand
|
||||
|
||||
-- Path to mesh topology file, path to diffuse texture, path to normal texture, path to specular texture
|
||||
aliceAddGenericMeshHand :: Alice -> String -> String -> String -> String -> IO AliceGenericMeshHand
|
||||
aliceAddGenericMeshHand alice p1 p2 p3 p4 = useAsUtf8StringLen p1 $ \d1 l1 ->
|
||||
(useAsUtf8StringLen p2 $ \d2 l2 -> (useAsUtf8StringLen p3 $ \d3 l3 -> (useAsUtf8StringLen p4 $ \d4 l4 ->
|
||||
allieAliceAddGenericMeshHand alice d1 l1 d2 l2 d3 l3 d4 l4)))
|
||||
|
||||
|
||||
foreign import ccall "allie_alice_add_shiny_mesh_hand" allie_alice_add_shiny_mesh_hand :: Alice -> Ptr Word8 -> Word64 -> IO AliceShinyMeshHand
|
||||
|
||||
aliceAddShinyMeshHand :: Alice -> String -> IO AliceShinyMeshHand
|
||||
aliceAddShinyMeshHand alice p = useAsUtf8StringLen p $ \dt len -> allie_alice_add_shiny_mesh_hand alice dt len
|
||||
|
||||
-- Maps well
|
||||
foreign import ccall "allie_alice_generic_mesh_resize_instance_arr" aliceGenericMeshResizeInstanceArr :: Alice -> AliceGenericMeshHand -> Word64 -> IO ()
|
||||
|
||||
foreign import ccall "allie_alice_shiny_mesh_resize_instance_arr" aliceShinyMeshResizeInstanceArr :: Alice -> AliceShinyMeshHand -> Word64 -> IO ()
|
||||
|
||||
foreign import ccall "allie_alice_generic_mesh_set_inst" allieAliceGenericMeshSetInst :: AliceGenericMeshHand -> Word64 -> Ptr AliceGenericMeshInstance -> IO ()
|
||||
|
||||
aliceGenericMeshSetInst :: AliceGenericMeshHand -> Word64 -> AliceGenericMeshInstance -> IO ()
|
||||
aliceGenericMeshSetInst mesh index obj = alloca $ \ptr -> do
|
||||
poke ptr obj
|
||||
allieAliceGenericMeshSetInst mesh index ptr
|
||||
|
||||
foreign import ccall "allie_alice_shiny_mesh_set_inst" allie_alice_shiny_mesh_set_inst :: AliceShinyMeshHand -> Word64 -> Ptr AliceShinyMeshInstance -> IO ()
|
||||
|
||||
aliceShinyMeshSetInst :: AliceShinyMeshHand -> Word64 -> AliceShinyMeshInstance -> IO ()
|
||||
aliceShinyMeshSetInst mesh index obj = alloca $ \ptr -> do
|
||||
poke ptr obj
|
||||
allie_alice_shiny_mesh_set_inst mesh index ptr
|
||||
|
||||
|
||||
foreign import ccall "allie_alice_get_cam_back" allie_alice_get_cam_back :: Alice -> Ptr Vec3 -> IO ()
|
||||
|
||||
aliceGetCamBack :: Alice -> IO Vec3
|
||||
aliceGetCamBack alice = alloca $ \ptr -> do
|
||||
allie_alice_get_cam_back alice ptr
|
||||
peek ptr
|
||||
|
||||
-- todo: add right and up
|
||||
|
||||
foreign import ccall "allie_alice_get_cam_pos" allie_alice_get_cam_pos :: Alice -> Ptr Vec3 -> IO ()
|
||||
|
||||
aliceGetCamPos :: Alice -> IO Vec3
|
||||
aliceGetCamPos alice = alloca $ \ptr -> do
|
||||
allie_alice_get_cam_pos alice ptr
|
||||
peek ptr
|
||||
|
||||
foreign import ccall "allie_alice_set_cam_pos" allie_alice_set_cam_pos :: Alice -> Float -> Float -> Float -> IO ()
|
||||
|
||||
aliceSetCamPos :: Alice -> Vec3 -> IO ()
|
||||
aliceSetCamPos alice (Vec3 x y z) = allie_alice_set_cam_pos alice x y z
|
||||
|
||||
-- Maps well
|
||||
foreign import ccall "allie_alice_set_point_light_count" aliceSetPointLightCount :: Alice -> Int -> IO ()
|
||||
|
||||
foreign import ccall "allie_alice_set_point_light" allie_alice_set_point_light :: Alice -> Int
|
||||
-> Float -> Float -> Float -> Float -> Float -> Float -> IO ()
|
||||
|
||||
aliceSetPointLight :: Alice -> Int -> AlicePointLight -> IO ()
|
||||
aliceSetPointLight alice index (AlicePointLight (Vec3 px py pz) (Vec3 cx cy cz)) =
|
||||
allie_alice_set_point_light alice index px py pz cx cy cz
|
||||
|
||||
foreign import ccall "alice_is_pressed" aliceIsPressed :: Alice -> Word32 -> IO Bool
|
||||
@ -1,4 +1,7 @@
|
||||
module Geom(Vec2(..), Vec3(..), Vec4(..), Mat4(..), Addable(..), Multipliable(..)) where
|
||||
module Geom(Vec2(..), Vec3(..), Vec4(..), Mat4(..), Addable(..), Multipliable(..), mat4Transit) where
|
||||
|
||||
import Foreign.Storable(Storable(..))
|
||||
import Foreign.Ptr (Ptr, castPtr, plusPtr)
|
||||
|
||||
data Vec2 = Vec2 !Float !Float
|
||||
deriving (Eq, Show)
|
||||
@ -42,3 +45,71 @@ data Mat4 = Mat4 !Vec4 !Vec4 !Vec4 !Vec4
|
||||
|
||||
mat4Transit :: Vec3 -> Mat4
|
||||
mat4Transit (Vec3 x y z) = Mat4 (Vec4 1 0 0 0) (Vec4 0 1 0 0) (Vec4 0 0 1 0) (Vec4 x y z 1)
|
||||
|
||||
|
||||
|
||||
instance Storable Vec2 where
|
||||
sizeOf _ = 2 * sizeOf (undefined :: Float)
|
||||
alignment _ = 4
|
||||
peek ptr = do
|
||||
let fptr = castPtr ptr :: Ptr Float
|
||||
x <- peek fptr
|
||||
y <- peek (fptr `plusPtr` sizeOf (undefined :: Float))
|
||||
return $ Vec2 x y
|
||||
poke ptr (Vec2 x y) = do
|
||||
let fptr = castPtr ptr :: Ptr Float
|
||||
poke fptr x
|
||||
poke (fptr `plusPtr` sizeOf (undefined :: Float)) y
|
||||
|
||||
instance Storable Vec3 where
|
||||
sizeOf _ = 3 * sizeOf (undefined :: Float)
|
||||
alignment _ = 4
|
||||
peek ptr = do
|
||||
let fptr = castPtr ptr :: Ptr Float
|
||||
let floatSize = sizeOf (undefined :: Float)
|
||||
x <- peek fptr
|
||||
y <- peek (fptr `plusPtr` floatSize)
|
||||
z <- peek (fptr `plusPtr` (2 * floatSize))
|
||||
return $ Vec3 x y z
|
||||
poke ptr (Vec3 x y z) = do
|
||||
let fptr = castPtr ptr :: Ptr Float
|
||||
let floatSize = sizeOf (undefined :: Float)
|
||||
poke fptr x
|
||||
poke (fptr `plusPtr` floatSize) y
|
||||
poke (fptr `plusPtr` (2 * floatSize)) z
|
||||
|
||||
instance Storable Vec4 where
|
||||
sizeOf _ = 4 * sizeOf (undefined :: Float)
|
||||
alignment _ = 4
|
||||
peek ptr = do
|
||||
let fptr = castPtr ptr :: Ptr Float
|
||||
let floatSize = sizeOf (undefined :: Float)
|
||||
x <- peek fptr
|
||||
y <- peek (fptr `plusPtr` floatSize)
|
||||
z <- peek (fptr `plusPtr` (2 * floatSize))
|
||||
w <- peek (fptr `plusPtr` (3 * floatSize))
|
||||
return $ Vec4 x y z w
|
||||
poke ptr (Vec4 x y z w) = do
|
||||
let fptr = castPtr ptr :: Ptr Float
|
||||
let floatSize = sizeOf (undefined :: Float)
|
||||
poke fptr x
|
||||
poke (fptr `plusPtr` floatSize) y
|
||||
poke (fptr `plusPtr` (2 * floatSize)) z
|
||||
poke (fptr `plusPtr` (3 * floatSize)) w
|
||||
|
||||
instance Storable Mat4 where
|
||||
sizeOf _ = 4 * sizeOf (undefined :: Vec4)
|
||||
alignment _ = 4
|
||||
peek ptr = do
|
||||
let vec4Size = sizeOf (undefined :: Vec4)
|
||||
v1 <- peek (castPtr ptr)
|
||||
v2 <- peek (ptr `plusPtr` vec4Size)
|
||||
v3 <- peek (ptr `plusPtr` (2 * vec4Size))
|
||||
v4 <- peek (ptr `plusPtr` (3 * vec4Size))
|
||||
return $ Mat4 v1 v2 v3 v4
|
||||
poke ptr (Mat4 v1 v2 v3 v4) = do
|
||||
let vec4Size = sizeOf (undefined :: Vec4)
|
||||
poke (castPtr ptr) v1
|
||||
poke (ptr `plusPtr` vec4Size) v2
|
||||
poke (ptr `plusPtr` (2 * vec4Size)) v3
|
||||
poke (ptr `plusPtr` (3 * vec4Size)) v4
|
||||
@ -667,15 +667,16 @@ typedef struct {
|
||||
} UsedVulkanQueues;
|
||||
|
||||
|
||||
void alice_default_callback_on_wl_keyboard_key(){}
|
||||
void alice_default_callback_on_wl_keyboard_key(void* d, U32 keysym, U32 key_action){}
|
||||
|
||||
void alice_default_callback_on_another_frame(){}
|
||||
void alice_default_callback_on_another_frame(void* d, float fl){}
|
||||
|
||||
typedef struct Alice Alice;
|
||||
|
||||
typedef struct{
|
||||
void (*on_wl_keyboard_key)(Alice*);
|
||||
void (*on_another_frame)(Alice*);
|
||||
/* guest data, keysym, key action (wl_keyboard_key_state) */
|
||||
void (*on_wl_keyboard_key)(void*, U32, U32);
|
||||
void (*on_another_frame)(void*, float);
|
||||
} AliceCallbacks;
|
||||
|
||||
void AliceCallbacks_set_default(AliceCallbacks* self){
|
||||
@ -768,6 +769,7 @@ AliceAllMeshesShiny AliceAllMeshesShiny_new(){
|
||||
|
||||
struct Alice {
|
||||
AliceCallbacks callbacks;
|
||||
void* guest;
|
||||
AliceWaylandApp wl;
|
||||
|
||||
MargaretInstanceAndItsDebug instance_and_debug;
|
||||
@ -828,8 +830,8 @@ ListNodeAliceGenericMeshHand* Alice_add_generic_mesh(Alice* alice, AliceGenericM
|
||||
AliceGenericMeshHand* mm = &mm_node->el;
|
||||
mm->indexes = topology.indexes.len;
|
||||
mm->instance_attr.count = 0;
|
||||
mm->instance_attr.staging = MargaretBufAllocator_alloc(&alice->staging_buffers, 69);
|
||||
mm->instance_attr.device_local = MargaretBufAllocator_alloc(&alice->dev_local_buffers, 69);
|
||||
mm->instance_attr.staging = MargaretBufAllocator_alloc(&alice->staging_buffers, 200);
|
||||
mm->instance_attr.device_local = MargaretBufAllocator_alloc(&alice->dev_local_buffers, 200);
|
||||
|
||||
mm->staging_vbo = MargaretBufAllocator_alloc(&alice->staging_buffers,
|
||||
topology.vertices.len * sizeof(GenericMeshVertex));
|
||||
@ -1066,7 +1068,7 @@ void AliceShinyMeshHand_resize_instance_arr(Alice* alice, AliceShinyMeshHand* se
|
||||
self->instance_attr.count = new_count;
|
||||
}
|
||||
|
||||
void AliceGenericMeshHand_set(AliceGenericMeshHand* self, size_t instance, GenericMeshInstanceInc uncomp){
|
||||
void AliceGenericMeshHand_set_inst(AliceGenericMeshHand* self, size_t instance, GenericMeshInstanceInc uncomp){
|
||||
assert(instance < self->instance_attr.count);
|
||||
GenericMeshInstance* staging = (GenericMeshInstance*)MargaretSubbuf_get_mapped(&self->instance_attr.staging);
|
||||
staging[instance].base = uncomp;
|
||||
@ -1077,7 +1079,7 @@ void AliceGenericMeshHand_set(AliceGenericMeshHand* self, size_t instance, Gener
|
||||
tr_inv.x.z, tr_inv.y.z, tr_inv.z.z );
|
||||
}
|
||||
|
||||
void AliceShinyMeshHand_set(AliceShinyMeshHand* self, size_t instance, ShinyMeshInstanceInc uncomp){
|
||||
void AliceShinyMeshHand_set_inst(AliceShinyMeshHand* self, size_t instance, ShinyMeshInstanceInc uncomp){
|
||||
assert(instance < self->instance_attr.count);
|
||||
ShinyMeshInstance* staging = (ShinyMeshInstance*)MargaretSubbuf_get_mapped(&self->instance_attr.staging);
|
||||
staging[instance].base = uncomp;
|
||||
@ -1551,7 +1553,7 @@ void alice_frame_drawing(Alice* alice) {
|
||||
mat4 camera_translation_matrix = marie_translation_mat4(vec3_minus(alice->cam_info.cam.pos));
|
||||
mat4 t_mat = mat4_mul_mat4(projection_matrix, mat4_mul_mat4(camera_rotation_matrix, camera_translation_matrix));
|
||||
|
||||
alice->callbacks.on_another_frame(alice);
|
||||
alice->callbacks.on_another_frame(alice->guest, (float)(alice->wl.cur_frame_time - alice->wl.last_frame_time) / 1000);
|
||||
|
||||
margaret_reset_and_begin_command_buffer(alice->transfer_command_buf);
|
||||
AliceScene__another_frame(alice);
|
||||
@ -1630,7 +1632,7 @@ void alice_frame_drawing(Alice* alice) {
|
||||
}
|
||||
}
|
||||
|
||||
static void main_h_xdg_surface_configure(void *data, struct xdg_surface *xdg_surface, uint32_t serial){
|
||||
static void alice_mainloop_h_xdg_surface_configure(void *data, struct xdg_surface *xdg_surface, uint32_t serial){
|
||||
Alice* alice = data;
|
||||
printf("XDG surface configured! (%d %d)\n", alice->wl.width_heard, alice->wl.height_heard);
|
||||
alice->wl.width_confirmed = alice->wl.width_heard;
|
||||
@ -1642,10 +1644,10 @@ static void main_h_xdg_surface_configure(void *data, struct xdg_surface *xdg_sur
|
||||
}
|
||||
|
||||
static const struct xdg_surface_listener xdg_surface_listener = {
|
||||
.configure = main_h_xdg_surface_configure,
|
||||
.configure = alice_mainloop_h_xdg_surface_configure,
|
||||
};
|
||||
|
||||
static void main_h_xdg_toplevel_configure(
|
||||
static void alice_mainloop_h_xdg_toplevel_configure(
|
||||
void *data, struct xdg_toplevel *xdg_toplevel, int32_t width, int32_t height, struct wl_array *states
|
||||
){
|
||||
Alice* alice = data;
|
||||
@ -1660,25 +1662,25 @@ static void main_h_xdg_toplevel_configure(
|
||||
alice->wl.height_heard = height;
|
||||
}
|
||||
|
||||
static void main_h_xdg_toplevel_close(void *data, struct xdg_toplevel *toplevel){
|
||||
static void alice_mainloop_h_xdg_toplevel_close(void *data, struct xdg_toplevel *toplevel){
|
||||
Alice* alice = data;
|
||||
alice->wl.closed = true;
|
||||
}
|
||||
|
||||
static const struct xdg_toplevel_listener main_h_xdg_toplevel_listener = {
|
||||
.configure = main_h_xdg_toplevel_configure,
|
||||
.close = main_h_xdg_toplevel_close,
|
||||
static const struct xdg_toplevel_listener alice_mainloop_h_xdg_toplevel_listener = {
|
||||
.configure = alice_mainloop_h_xdg_toplevel_configure,
|
||||
.close = alice_mainloop_h_xdg_toplevel_close,
|
||||
};
|
||||
|
||||
static void main_h_xdg_wm_base_ping(void *data, struct xdg_wm_base *xdg_wm_base, uint32_t serial){
|
||||
static void alice_mainloop_h_xdg_wm_base_ping(void *data, struct xdg_wm_base *xdg_wm_base, uint32_t serial){
|
||||
xdg_wm_base_pong(xdg_wm_base, serial);
|
||||
}
|
||||
|
||||
static const struct xdg_wm_base_listener main_h_xdg_wm_base_listener = {
|
||||
.ping = main_h_xdg_wm_base_ping,
|
||||
static const struct xdg_wm_base_listener alice_mainloop_h_xdg_wm_base_listener = {
|
||||
.ping = alice_mainloop_h_xdg_wm_base_ping,
|
||||
};
|
||||
|
||||
static void main_h_wl_keyboard_keymap(
|
||||
static void alice_mainloop_h_wl_keyboard_keymap(
|
||||
void *data, struct wl_keyboard *wl_keyboard, uint32_t format, int32_t fd, uint32_t size
|
||||
) {
|
||||
Alice* alice = data;
|
||||
@ -1699,7 +1701,7 @@ static void main_h_wl_keyboard_keymap(
|
||||
memset(&alice->wl.first_0x80_keys, 0, sizeof(alice->wl.first_0x80_keys));
|
||||
}
|
||||
|
||||
static void main_h_wl_keyboard_enter(
|
||||
static void alice_mainloop_h_wl_keyboard_enter(
|
||||
void *data, struct wl_keyboard *wl_keyboard, uint32_t serial, struct wl_surface *surface, struct wl_array *keys
|
||||
) {
|
||||
Alice* alice = data;
|
||||
@ -1713,14 +1715,14 @@ static void main_h_wl_keyboard_enter(
|
||||
}
|
||||
}
|
||||
|
||||
static void main_h_wl_keyboard_leave(
|
||||
static void alice_mainloop_h_wl_keyboard_leave(
|
||||
void *data, struct wl_keyboard *wl_keyboard, uint32_t serial, struct wl_surface *surface
|
||||
) {
|
||||
Alice* alice = data;
|
||||
memset(&alice->wl.first_0x80_keys, 0, sizeof(alice->wl.first_0x80_keys));
|
||||
}
|
||||
|
||||
static void main_h_wl_keyboard_key(
|
||||
static void alice_mainloop_h_wl_keyboard_key(
|
||||
void *data, struct wl_keyboard *wl_keyboard, uint32_t serial, uint32_t time, uint32_t key, uint32_t key_action
|
||||
) {
|
||||
Alice* alice = data;
|
||||
@ -1732,7 +1734,7 @@ static void main_h_wl_keyboard_key(
|
||||
} else if (keysym < 0x80 && key_action == WL_KEYBOARD_KEY_STATE_PRESSED) {
|
||||
alice->wl.first_0x80_keys[keysym] = true;
|
||||
}
|
||||
alice->callbacks.on_wl_keyboard_key(alice);
|
||||
alice->callbacks.on_wl_keyboard_key(alice->guest, keysym, key_action);
|
||||
if (key_action == WL_KEYBOARD_KEY_STATE_RELEASED) {
|
||||
if (keysym == XKB_KEY_1) {
|
||||
// vec3 p = alice->cam_info.pos;
|
||||
@ -1757,7 +1759,7 @@ static void main_h_wl_keyboard_key(
|
||||
}
|
||||
}
|
||||
|
||||
static void main_h_wl_keyboard_modifiers(
|
||||
static void alice_mainloop_h_wl_keyboard_modifiers(
|
||||
void *data, struct wl_keyboard *wl_keyboard, uint32_t serial,
|
||||
uint32_t mods_depressed, uint32_t mods_latched, uint32_t mods_locked, uint32_t group
|
||||
) {
|
||||
@ -1765,32 +1767,32 @@ static void main_h_wl_keyboard_modifiers(
|
||||
xkb_state_update_mask(alice->wl.xkb_state, mods_depressed, mods_latched, mods_locked, 0, 0, group);
|
||||
}
|
||||
|
||||
static void main_h_wl_keyboard_repeat_info(void *data, struct wl_keyboard *wl_keyboard, int32_t rate, int32_t delay){
|
||||
static void alice_mainloop_h_wl_keyboard_repeat_info(void *data, struct wl_keyboard *wl_keyboard, int32_t rate, int32_t delay){
|
||||
printf("Repeat timings changed: rate = %d, delay = %d\n", rate, delay);
|
||||
}
|
||||
|
||||
static const struct wl_keyboard_listener main_h_wl_keyboard_listener = {
|
||||
.keymap = main_h_wl_keyboard_keymap,
|
||||
.enter = main_h_wl_keyboard_enter,
|
||||
.leave = main_h_wl_keyboard_leave,
|
||||
.key = main_h_wl_keyboard_key,
|
||||
.modifiers = main_h_wl_keyboard_modifiers,
|
||||
.repeat_info = main_h_wl_keyboard_repeat_info,
|
||||
static const struct wl_keyboard_listener alice_mainloop_h_wl_keyboard_listener = {
|
||||
.keymap = alice_mainloop_h_wl_keyboard_keymap,
|
||||
.enter = alice_mainloop_h_wl_keyboard_enter,
|
||||
.leave = alice_mainloop_h_wl_keyboard_leave,
|
||||
.key = alice_mainloop_h_wl_keyboard_key,
|
||||
.modifiers = alice_mainloop_h_wl_keyboard_modifiers,
|
||||
.repeat_info = alice_mainloop_h_wl_keyboard_repeat_info,
|
||||
};
|
||||
|
||||
|
||||
static void main_h_wl_pointer_enter(
|
||||
static void alice_mainloop_h_wl_pointer_enter(
|
||||
void *data, struct wl_pointer *wl_pointer, uint32_t serial,
|
||||
struct wl_surface *surface, wl_fixed_t surface_x, wl_fixed_t surface_y
|
||||
) {
|
||||
}
|
||||
|
||||
static void main_h_wl_pointer_leave(
|
||||
static void alice_mainloop_h_wl_pointer_leave(
|
||||
void *data, struct wl_pointer *wl_pointer, uint32_t serial, struct wl_surface *surface
|
||||
) {
|
||||
}
|
||||
|
||||
static void main_h_wl_pointer_motion(
|
||||
static void alice_mainloop_h_wl_pointer_motion(
|
||||
void *data, struct wl_pointer *wl_pointer, uint32_t time, wl_fixed_t surface_x, wl_fixed_t surface_y
|
||||
) {
|
||||
Alice* alice = data;
|
||||
@ -1799,57 +1801,57 @@ static void main_h_wl_pointer_motion(
|
||||
(float)surface_x / 256.f, (float)surface_y / 256.f);
|
||||
}
|
||||
|
||||
static void main_h_wl_pointer_button(
|
||||
static void alice_mainloop_h_wl_pointer_button(
|
||||
void *data, struct wl_pointer *wl_pointer, uint32_t serial, uint32_t time, uint32_t button, uint32_t btn_action
|
||||
) {
|
||||
Alice* alice = data;
|
||||
}
|
||||
|
||||
static void main_h_wl_pointer_axis(
|
||||
static void alice_mainloop_h_wl_pointer_axis(
|
||||
void *data, struct wl_pointer *wl_pointer, uint32_t time, uint32_t axis, wl_fixed_t value
|
||||
) {
|
||||
Alice* alice = data;
|
||||
}
|
||||
|
||||
static void main_h_wl_pointer_frame(void *data, struct wl_pointer *wl_pointer) {
|
||||
static void alice_mainloop_h_wl_pointer_frame(void *data, struct wl_pointer *wl_pointer) {
|
||||
Alice* alice = data;
|
||||
}
|
||||
|
||||
const struct wl_pointer_listener main_h_wl_pointer_listener = {
|
||||
.enter = main_h_wl_pointer_enter,
|
||||
.leave = main_h_wl_pointer_leave,
|
||||
.motion = main_h_wl_pointer_motion,
|
||||
.button = main_h_wl_pointer_button,
|
||||
.axis = main_h_wl_pointer_axis,
|
||||
.frame = main_h_wl_pointer_frame
|
||||
const struct wl_pointer_listener alice_mainloop_h_wl_pointer_listener = {
|
||||
.enter = alice_mainloop_h_wl_pointer_enter,
|
||||
.leave = alice_mainloop_h_wl_pointer_leave,
|
||||
.motion = alice_mainloop_h_wl_pointer_motion,
|
||||
.button = alice_mainloop_h_wl_pointer_button,
|
||||
.axis = alice_mainloop_h_wl_pointer_axis,
|
||||
.frame = alice_mainloop_h_wl_pointer_frame
|
||||
};
|
||||
|
||||
static void main_h_wl_seat_capabilities(void *data, struct wl_seat *wl_seat, uint32_t capabilities) {
|
||||
static void alice_mainloop_h_wl_seat_capabilities(void *data, struct wl_seat *wl_seat, uint32_t capabilities) {
|
||||
Alice* alice = data;
|
||||
if (capabilities & WL_SEAT_CAPABILITY_POINTER) {
|
||||
alice->wl.pointer = wl_seat_get_pointer(wl_seat);
|
||||
if (!alice->wl.pointer)
|
||||
abortf("wl_seat_get_pointer\n");
|
||||
wl_pointer_add_listener(alice->wl.pointer, &main_h_wl_pointer_listener, alice);
|
||||
wl_pointer_add_listener(alice->wl.pointer, &alice_mainloop_h_wl_pointer_listener, alice);
|
||||
}
|
||||
if (capabilities & WL_SEAT_CAPABILITY_KEYBOARD) {
|
||||
alice->wl.keyboard = wl_seat_get_keyboard(wl_seat);
|
||||
if (!alice->wl.keyboard)
|
||||
abortf("wl_seat_get_keyboard\n");
|
||||
wl_keyboard_add_listener(alice->wl.keyboard, &main_h_wl_keyboard_listener, alice);
|
||||
wl_keyboard_add_listener(alice->wl.keyboard, &alice_mainloop_h_wl_keyboard_listener, alice);
|
||||
}
|
||||
}
|
||||
|
||||
static void main_h_wl_seat_name(void* data, struct wl_seat* wl_seat, const char* name) {
|
||||
static void alice_mainloop_h_wl_seat_name(void* data, struct wl_seat* wl_seat, const char* name) {
|
||||
printf("Our seat name: %s\n", name);
|
||||
}
|
||||
|
||||
static const struct wl_seat_listener main_h_wl_seat_listener = {
|
||||
.capabilities = main_h_wl_seat_capabilities,
|
||||
.name = main_h_wl_seat_name,
|
||||
static const struct wl_seat_listener alice_mainloop_h_wl_seat_listener = {
|
||||
.capabilities = alice_mainloop_h_wl_seat_capabilities,
|
||||
.name = alice_mainloop_h_wl_seat_name,
|
||||
};
|
||||
|
||||
static void main_h_wl_registry_global(
|
||||
static void alice_mainloop_h_wl_registry_global(
|
||||
void *data, struct wl_registry *wl_registry, uint32_t name, const char *interface, uint32_t version
|
||||
) {
|
||||
Alice* alice = data;
|
||||
@ -1861,7 +1863,7 @@ static void main_h_wl_registry_global(
|
||||
alice->wl.xdg_wm_base = wl_registry_bind(wl_registry, name, &xdg_wm_base_interface, 1);
|
||||
if (!alice->wl.xdg_wm_base)
|
||||
abortf("wl_registry_bind\n");
|
||||
xdg_wm_base_add_listener(alice->wl.xdg_wm_base, &main_h_xdg_wm_base_listener, alice);
|
||||
xdg_wm_base_add_listener(alice->wl.xdg_wm_base, &alice_mainloop_h_xdg_wm_base_listener, alice);
|
||||
} else if (strcmp(interface, wl_seat_interface.name) == 0) {
|
||||
if (alice->wl.wl_seat) {
|
||||
printf("We got second seat, but we only need one\n");
|
||||
@ -1870,39 +1872,40 @@ static void main_h_wl_registry_global(
|
||||
alice->wl.wl_seat = wl_registry_bind(wl_registry, name, &wl_seat_interface, 4);
|
||||
if (!alice->wl.wl_seat)
|
||||
abortf("wl_registry_bind\n");
|
||||
wl_seat_add_listener(alice->wl.wl_seat, &main_h_wl_seat_listener, alice);
|
||||
wl_seat_add_listener(alice->wl.wl_seat, &alice_mainloop_h_wl_seat_listener, alice);
|
||||
}
|
||||
}
|
||||
|
||||
static void main_h_wl_registry_global_remove(void *data, struct wl_registry *wl_registry, uint32_t name){
|
||||
static void alice_mainloop_h_wl_registry_global_remove(void *data, struct wl_registry *wl_registry, uint32_t name){
|
||||
|
||||
}
|
||||
|
||||
static const struct wl_registry_listener main_h_wl_registry_listener = {
|
||||
.global = main_h_wl_registry_global,
|
||||
.global_remove = main_h_wl_registry_global_remove,
|
||||
static const struct wl_registry_listener alice_mainloop_h_wl_registry_listener = {
|
||||
.global = alice_mainloop_h_wl_registry_global,
|
||||
.global_remove = alice_mainloop_h_wl_registry_global_remove,
|
||||
};
|
||||
|
||||
static const struct wl_callback_listener main_h_wl_surface_frame_listener;
|
||||
static const struct wl_callback_listener alice_mainloop_h_wl_surface_frame_listener;
|
||||
|
||||
static void main_h_wl_surface_frame_done(void *data, struct wl_callback *cb, uint32_t time){
|
||||
static void alice_mainloop_h_wl_surface_frame_done(void *data, struct wl_callback *cb, uint32_t time){
|
||||
Alice* alice = data;
|
||||
wl_callback_destroy(cb);
|
||||
alice->wl.wl_callback = wl_surface_frame(alice->wl.wl_surface);
|
||||
if (!alice->wl.wl_callback)
|
||||
abortf("wl_surface_frame\n");
|
||||
wl_callback_add_listener(alice->wl.wl_callback, &main_h_wl_surface_frame_listener, alice);
|
||||
wl_callback_add_listener(alice->wl.wl_callback, &alice_mainloop_h_wl_surface_frame_listener, alice);
|
||||
|
||||
alice->wl.cur_frame_time = time;
|
||||
alice_frame_drawing(alice);
|
||||
alice->wl.last_frame_time = time;
|
||||
}
|
||||
|
||||
static const struct wl_callback_listener main_h_wl_surface_frame_listener = {
|
||||
.done = main_h_wl_surface_frame_done,
|
||||
static const struct wl_callback_listener alice_mainloop_h_wl_surface_frame_listener = {
|
||||
.done = alice_mainloop_h_wl_surface_frame_done,
|
||||
};
|
||||
|
||||
Alice* Alice_new(){
|
||||
Alice* alice = malloc(sizeof(Alice));
|
||||
Alice* alice = safe_malloc(sizeof(Alice));
|
||||
SpanU8 root_dir = cstr(".");
|
||||
SpanU8 GPU = cstr("nvidia");
|
||||
SpanU8 bugged_GPU = cstr("nothere");
|
||||
@ -1919,7 +1922,7 @@ Alice* Alice_new(){
|
||||
alice->wl.wl_registry = wl_display_get_registry(alice->wl.wl_display);
|
||||
if (!alice->wl.wl_registry)
|
||||
abortf("wl_display_get_registry");
|
||||
wl_registry_add_listener(alice->wl.wl_registry, &main_h_wl_registry_listener, alice);
|
||||
wl_registry_add_listener(alice->wl.wl_registry, &alice_mainloop_h_wl_registry_listener, alice);
|
||||
wl_display_roundtrip(alice->wl.wl_display);
|
||||
if (!alice->wl.wl_compositor)
|
||||
abortf("No wl_compositor");
|
||||
@ -1939,7 +1942,7 @@ Alice* Alice_new(){
|
||||
alice->wl.xdg_toplevel = xdg_surface_get_toplevel(alice->wl.xdg_surface);
|
||||
if (!alice->wl.xdg_toplevel)
|
||||
abortf("xdg_surface_get_toplevel\n");
|
||||
xdg_toplevel_add_listener(alice->wl.xdg_toplevel, &main_h_xdg_toplevel_listener, alice);
|
||||
xdg_toplevel_add_listener(alice->wl.xdg_toplevel, &alice_mainloop_h_xdg_toplevel_listener, alice);
|
||||
xdg_toplevel_set_title(alice->wl.xdg_toplevel, "r3");
|
||||
xdg_toplevel_set_app_id(alice->wl.xdg_toplevel, "r3");
|
||||
wl_surface_commit(alice->wl.wl_surface);
|
||||
@ -1947,7 +1950,7 @@ Alice* Alice_new(){
|
||||
alice->wl.wl_callback = wl_surface_frame(alice->wl.wl_surface);
|
||||
if (!alice->wl.wl_callback)
|
||||
abortf("wl_surface_frame\n");
|
||||
wl_callback_add_listener(alice->wl.wl_callback, &main_h_wl_surface_frame_listener, alice);
|
||||
wl_callback_add_listener(alice->wl.wl_callback, &alice_mainloop_h_wl_surface_frame_listener, alice);
|
||||
alice->wl.cur_frame_time = alice->wl.last_frame_time = 0;
|
||||
|
||||
alice->instance_and_debug = MargaretInstanceAndItsDebug_new(ENABLE_VALIDATION_LAYERS);
|
||||
@ -2112,7 +2115,7 @@ void Alice_add_screen_text(Alice* alice, RBTreeNodeLucyFaceFixedSize* ffs, vec4
|
||||
LucyRenderer_add_text(&alice->lucy_renderer, ffs, color, 0, text, start_pos);
|
||||
}
|
||||
|
||||
/* This function actually consumes alice handler */
|
||||
/* This function actually consumes alice handler. Alice must not be used after */
|
||||
void Alice_mainloop(Alice* alice, const AliceCallbacks* callbacks) {
|
||||
alice->callbacks.on_wl_keyboard_key = callbacks->on_wl_keyboard_key;
|
||||
alice->callbacks.on_another_frame = callbacks->on_another_frame;
|
||||
@ -2122,7 +2125,6 @@ void Alice_mainloop(Alice* alice, const AliceCallbacks* callbacks) {
|
||||
break;
|
||||
}
|
||||
vkDeviceWaitIdle(alice->device);
|
||||
AliceCallbacks_set_default(&alice->callbacks);
|
||||
|
||||
// The End
|
||||
// vkDestroyDescriptorPool(vk->device, vk->descriptor_pool, NULL);
|
||||
@ -2165,3 +2167,140 @@ void Alice_mainloop(Alice* alice, const AliceCallbacks* callbacks) {
|
||||
// wl_registry_destroy(alice->wl.wl_registry);
|
||||
wl_display_disconnect(alice->wl.wl_display);
|
||||
}
|
||||
|
||||
void allie_alice_set_sky_color(Alice* alice, float x, float y, float z, float w){
|
||||
alice->rendering_config.clear_color = (vec4){x, y, z, w};
|
||||
}
|
||||
|
||||
Alice* allie_alice_new(){
|
||||
return Alice_new();
|
||||
}
|
||||
|
||||
void allie_alice_mainloop(Alice* alice, const AliceCallbacks* callbacks){
|
||||
Alice_mainloop(alice, callbacks);
|
||||
}
|
||||
|
||||
LucyFace* allie_alice_new_lucy_face(Alice* alice, const U8* path_data, U64 path_len){
|
||||
return LucyFace_new(alice->ft_library, &alice->lucy_cache, VecU8_from_span((SpanU8){path_data, path_len}));
|
||||
}
|
||||
|
||||
RBTreeNodeLucyFaceFixedSize* allie_alice_lucy_face_of_size(LucyFace* face, U32 height){
|
||||
return LucyFace_of_size(face, height);
|
||||
}
|
||||
|
||||
/* lol */
|
||||
void allie_lucy_face_add_glyphs(RBTreeNodeLucyFaceFixedSize* face_fs, U32 start, U32 seg_len){
|
||||
VecLucyGlyphCachingRequest lucy_requests = VecLucyGlyphCachingRequest_new();
|
||||
VecU32Segment ranges_needed = VecU32Segment_new();
|
||||
VecU32Segment_append(&ranges_needed, (U32Segment){.start = start, .len = seg_len});
|
||||
VecLucyGlyphCachingRequest_append(&lucy_requests, (LucyGlyphCachingRequest){
|
||||
.sized_face = face_fs, .codepoint_ranges = ranges_needed,
|
||||
});
|
||||
LucyGlyphCache_add_glyphs(lucy_requests);
|
||||
}
|
||||
|
||||
void allie_alice_clear_text(Alice* alice){
|
||||
LucyRenderer_clear(&alice->lucy_renderer);
|
||||
}
|
||||
|
||||
void allie_alice_add_text(Alice* alice, RBTreeNodeLucyFaceFixedSize* ffs,
|
||||
float color_x, float color_y, float color_z, float color_w, const U8* text_data, U64 text_len,
|
||||
S32 start_pos_x, S32 start_pos_y){
|
||||
LucyRenderer_add_text(&alice->lucy_renderer, ffs, (vec4){color_x, color_y, color_z, color_w}, 0,
|
||||
(SpanU8){text_data, text_len}, (ivec2){start_pos_x, start_pos_y});
|
||||
}
|
||||
|
||||
ListNodeAliceGenericMeshHand* allie_alice_add_generic_mesh_hand(
|
||||
Alice* alice, const U8* topology_path_data, U64 topology_path_len,
|
||||
const U8* diffuse_path_data, U64 diffuse_path_len,
|
||||
const U8* normal_path_data, U64 normal_path_len,
|
||||
const U8* specular_path_data, U64 specular_path_len){
|
||||
/* Todo: figure out how to pass vectors properly in haskell */
|
||||
return Alice_add_generic_mesh(alice, (AliceGenericMeshPath){
|
||||
VecU8_from_span((SpanU8){topology_path_data, topology_path_len}),
|
||||
VecU8_from_span((SpanU8){diffuse_path_data, diffuse_path_len}),
|
||||
VecU8_from_span((SpanU8){normal_path_data, normal_path_len}),
|
||||
VecU8_from_span((SpanU8){specular_path_data, specular_path_len}),
|
||||
});
|
||||
}
|
||||
|
||||
ListNodeAliceShinyMeshHand* allie_alice_add_shiny_mesh_hand(Alice* alice, const U8* mesh_path_data, U64 mesh_path_len){
|
||||
return Alice_add_shiny_mesh(alice, VecU8_from_span((SpanU8){mesh_path_data, mesh_path_len}));
|
||||
}
|
||||
|
||||
void allie_alice_generic_mesh_resize_instance_arr(Alice* alice, ListNodeAliceGenericMeshHand* mesh_hand, U64 new_count){
|
||||
AliceGenericMeshHand_resize_instance_arr(alice, &mesh_hand->el, new_count);
|
||||
}
|
||||
|
||||
void allie_alice_shiny_mesh_resize_instance_arr(Alice* alice, ListNodeAliceShinyMeshHand* mesh_hand, U64 new_count){
|
||||
AliceShinyMeshHand_resize_instance_arr(alice, &mesh_hand->el, new_count);
|
||||
}
|
||||
|
||||
// void allie_alice_generic_mesh_set_inst(
|
||||
// ListNodeAliceGenericMeshHand* mesh_hand, U64 index,
|
||||
// float xx, float xy, float xz, float xw, float yx, float yy, float yz, float yw,
|
||||
// float zx, float zy, float zz, float zw, float wx, float wy, float wz, float ww){
|
||||
// AliceGenericMeshHand_set_inst(&mesh_hand->el, index, (GenericMeshInstanceInc){.model_t = {
|
||||
// .x = {xx, xy, xz, xw}, .y = {yx, yy, yz, yw}, .z = {zx, zy, zz, zw}, .w = {wx, wy, wz, ww},
|
||||
// }});
|
||||
// }
|
||||
//
|
||||
// void allie_alice_shiny_mesh_set_inst(
|
||||
// ListNodeAliceGenericMeshHand* mesh_hand, U64 index,
|
||||
// float xx, float xy, float xz, float xw, float yx, float yy, float yz, float yw,
|
||||
// float zx, float zy, float zz, float zw, float wx, float wy, float wz, float ww,
|
||||
// float clr_off_x, float clr_off_y, float clr_off_z, float clr_off_w,
|
||||
// float clr_on_x, float clr_on_y, float clr_on_z, float clr_on_w){
|
||||
// AliceShinyMeshHand_set_inst(&mesh_hand->el, index, (ShinyMeshInstanceInc){.model_t = {
|
||||
// }, .color_on = {}});
|
||||
//
|
||||
// }
|
||||
|
||||
void allie_alice_generic_mesh_set_inst(
|
||||
ListNodeAliceGenericMeshHand* mesh_hand, U64 index, const GenericMeshInstanceInc* inst){
|
||||
AliceGenericMeshHand_set_inst(&mesh_hand->el, index, *inst);
|
||||
}
|
||||
|
||||
void allie_alice_shiny_mesh_set_inst(
|
||||
ListNodeAliceShinyMeshHand* mesh_hand, U64 index, const ShinyMeshInstanceInc* inst){
|
||||
AliceShinyMeshHand_set_inst(&mesh_hand->el, index, *inst);
|
||||
}
|
||||
|
||||
void allie_alice_get_cam_back(Alice* alice, vec3* ret){
|
||||
*ret = alice->cam_info.cam.cam_basis.z;
|
||||
}
|
||||
|
||||
void allie_alice_get_cam_right(Alice* alice, vec3* ret){
|
||||
*ret = alice->cam_info.cam.cam_basis.x;
|
||||
}
|
||||
|
||||
void allie_alice_get_cam_up(Alice* alice, vec3* ret){
|
||||
*ret = alice->cam_info.cam.cam_basis.y;
|
||||
}
|
||||
|
||||
void allie_alice_get_cam_pos(Alice* alice, vec3* ret){
|
||||
*ret = alice->cam_info.cam.pos;
|
||||
}
|
||||
|
||||
void allie_alice_set_cam_pos(Alice* alice, float x, float y, float z){
|
||||
alice->cam_info.cam.pos = (vec3){x, y, z};
|
||||
}
|
||||
|
||||
void allie_alice_set_fov(Alice* alice, float fov){
|
||||
alice->cam_info.cam.fov = fov;
|
||||
}
|
||||
|
||||
void allie_alice_set_point_light_count(Alice* alice, int new_count){
|
||||
Alice_set_point_light_count(alice, new_count);
|
||||
}
|
||||
|
||||
void allie_alice_set_point_light(Alice* alice, int index,
|
||||
float pos_x, float pos_y, float pos_z, float color_x, float color_y, float color_z){
|
||||
Alice_set_point_light(alice, index, (Pipeline0PointLight){
|
||||
.pos = {pos_x, pos_y, pos_z}, .color = {color_x, color_y, color_z}});
|
||||
}
|
||||
|
||||
/* Works incorrectly */
|
||||
bool alice_is_pressed(Alice* alice, U32 keysym){
|
||||
return keysym >= 0x80 ? false : alice->wl.first_0x80_keys[keysym];
|
||||
}
|
||||
217
src/l2/anne/r4.h
217
src/l2/anne/r4.h
@ -422,7 +422,7 @@ void TextureDataR8G8B8A8_draw_triang_part_bublazhuzhka(
|
||||
|
||||
|
||||
|
||||
|
||||
// todo: rewrite this shit (again)
|
||||
TextureDataR8G8B8A8 generate_tex_template_for_one_fourth_of_a_cylinder(float s_resol, float w, float r, U32 k) {
|
||||
assert(k >= 1);
|
||||
const float a = M_PI_2f / (float)k;
|
||||
@ -438,8 +438,8 @@ TextureDataR8G8B8A8 generate_tex_template_for_one_fourth_of_a_cylinder(float s_r
|
||||
mat3x2 cord_resol_trop = (mat3x2){.x.x = cord_resol.x, .y.y = cord_resol.y};
|
||||
|
||||
vec3 color_1 = (vec3){0.3f, 0.5f, 0.1f};
|
||||
TextureDataR8G8B8A8_draw_triangle_of_one_color(&res, color_1, (MarieTriangle){v0tex, v4tex, v5tex}, cord_resol_trop);
|
||||
TextureDataR8G8B8A8_draw_triangle_of_one_color(&res, color_1, (MarieTriangle){v0tex, v5tex, v1tex}, cord_resol_trop);
|
||||
TextureDataR8G8B8A8_draw_parametrized_triangle_of_one_color(&res, color_1, (MarieTriangle){v0tex, v4tex, v5tex}, cord_resol_trop);
|
||||
TextureDataR8G8B8A8_draw_parametrized_triangle_of_one_color(&res, color_1, (MarieTriangle){v0tex, v5tex, v1tex}, cord_resol_trop);
|
||||
vec3 color_2 = (vec3){0.1f, 0.2f, 0.8f};
|
||||
vec3 color_3 = (vec3){0.2f, 0.3f, 0.9f};
|
||||
vec3 color_4 = (vec3){0.1f, 0.5f, 0.7f};
|
||||
@ -447,12 +447,12 @@ TextureDataR8G8B8A8 generate_tex_template_for_one_fourth_of_a_cylinder(float s_r
|
||||
for (size_t i = 1; i <= k; i++) {
|
||||
vec2 A = (vec2){r - r * sinf(a * (float)i), r + r * cosf(a * (float)i)};
|
||||
vec2 B = (vec2){r - r * sinf(a * (float)(i-1)), r + r * cosf(a * (float)(i-1))};
|
||||
TextureDataR8G8B8A8_draw_triangle_of_one_color(&res, color_2, (MarieTriangle){v0tex, B, A}, cord_resol_trop);
|
||||
TextureDataR8G8B8A8_draw_parametrized_triangle_of_one_color(&res, color_2, (MarieTriangle){v0tex, B, A}, cord_resol_trop);
|
||||
}
|
||||
for (size_t i = 1; i <= k; i++) {
|
||||
vec2 A = (vec2){r + w + r * sinf(a * (float)i), r + r * cosf(a * (float)i)};
|
||||
vec2 B = (vec2){r + w + r * sinf(a * (float)(i-1)), r + r * cosf(a * (float)(i-1))};
|
||||
TextureDataR8G8B8A8_draw_triangle_of_one_color(&res, color_3, (MarieTriangle){v1tex, A, B}, cord_resol_trop);
|
||||
TextureDataR8G8B8A8_draw_parametrized_triangle_of_one_color(&res, color_3, (MarieTriangle){v1tex, A, B}, cord_resol_trop);
|
||||
}
|
||||
for (size_t i = 1; i <= k; i++) {
|
||||
vec2 A = (vec2){r, 2 * r + (float)(i) * l};
|
||||
@ -460,8 +460,9 @@ TextureDataR8G8B8A8 generate_tex_template_for_one_fourth_of_a_cylinder(float s_r
|
||||
vec2 C = (vec2){r + w, 2 * r + (float)(i-1) * l};
|
||||
vec2 D = (vec2){r + w, 2 * r + (float)(i) * l};
|
||||
vec3 c = i % 2 ? color_4 : color_5;
|
||||
TextureDataR8G8B8A8_draw_triangle_of_one_color(&res, c, (MarieTriangle){A, B, C}, cord_resol_trop);
|
||||
TextureDataR8G8B8A8_draw_triangle_of_one_color(&res, c, (MarieTriangle){A, C, D}, cord_resol_trop);
|
||||
// todo: replace this shit with something more normal
|
||||
TextureDataR8G8B8A8_draw_parametrized_triangle_of_one_color(&res, c, (MarieTriangle){A, B, C}, cord_resol_trop);
|
||||
TextureDataR8G8B8A8_draw_parametrized_triangle_of_one_color(&res, c, (MarieTriangle){A, C, D}, cord_resol_trop);
|
||||
}
|
||||
|
||||
Bublazhuzhka crap_on_back_side = fill_rectangle_with_crap(w, r);
|
||||
@ -479,6 +480,7 @@ vec2 height_map_cb_that_uses_bublazhuzhka(void* ug, vec2 v) {
|
||||
return Bublazhuzhka_get_derivative(bzh, v);
|
||||
}
|
||||
|
||||
// todo: rewrite this shit and merge it with other one-fourth-of-a-cylinder generiting functions
|
||||
TextureDataR8G8B8A8 generate_normal_tex_for_one_fourth_of_a_cylinder(float s_resol, float w, float r, U32 k) {
|
||||
assert(k >= 1);
|
||||
const float a = M_PI_2f / (float)k;
|
||||
@ -664,17 +666,200 @@ CubeVertOfFace CubeVertOfFace_next(CubeVertOfFace vert) {
|
||||
return (CubeVertOfFace){vert.face, (vert.vert_on_it + 1) % 4};
|
||||
}
|
||||
|
||||
|
||||
#include "../../../gen/l1/margaret/png_pixel_masses.h"
|
||||
#include "../marie/texture_processing.h"
|
||||
#include "../../l1/system/fsmanip.h"
|
||||
#include "../alice/model_file.h"
|
||||
|
||||
void for_log(U64 w, U64 r, U64 k) {
|
||||
/* Situation: we generated vertices array of generic mesh, we filled .tex attribute (scaled pixel pos)
|
||||
* Now I want the normally scaled stuff back */
|
||||
MarieTriangle restore_triangle_from_mesh_topology(const VecGenericMeshVertexInc* vertices,
|
||||
U32 texture_width, U32 texture_height, U32 vi1, U32 vi2, U32 vi3){
|
||||
vec2 tex1 = VecGenericMeshVertexInc_at(vertices, vi1)->tex;
|
||||
vec2 tex2 = VecGenericMeshVertexInc_at(vertices, vi2)->tex;
|
||||
vec2 tex3 = VecGenericMeshVertexInc_at(vertices, vi3)->tex;
|
||||
return (MarieTriangle){
|
||||
.v0 = {tex1.x * (float)texture_width, tex1.y * (float)texture_height},
|
||||
.v1 = {tex2.x * (float)texture_width, tex2.y * (float)texture_height},
|
||||
.v2 = {tex3.x * (float)texture_width, tex3.y * (float)texture_height},
|
||||
};
|
||||
}
|
||||
|
||||
/* r is radius, w is length of cylinder. Will write everything into files for us */
|
||||
void r4_asset_gen_generic_mesh_cylinder(float s_resol, float r, float w, U32 k,
|
||||
VecU8 path_to_mesh, VecU8 path_to_template_tex, VecU8 path_to_normal_tex){
|
||||
assert(k >= 3);
|
||||
VecGenericMeshVertexInc vertices = VecGenericMeshVertexInc_new_reserved(6 * k);
|
||||
VecU32 indexes = VecU32_new_reserved(3 * (2 * (k - 2) + 2 * k));
|
||||
|
||||
U32 uber_square_takes_px = (U32)ceilf(2 * r * s_resol);
|
||||
float r_px = (float)uber_square_takes_px / 2;
|
||||
|
||||
vec2 ubs_front_center = (vec2){r_px, r_px};
|
||||
|
||||
U32 back_ubs_x = uber_square_takes_px + 1;
|
||||
vec2 ubs_back_center = (vec2){(float)back_ubs_x + r_px, r_px};
|
||||
|
||||
U32 belt_y = uber_square_takes_px + 1;
|
||||
|
||||
/* l is a length of a side. I am 100 % that there is a simpler formula for that */
|
||||
float l = r * sqrtf(2 - 2 * cosf(2 * M_PIf / (float)k));
|
||||
U32 belt_takes_px = (U32)ceilf(l * (float)k * s_resol);
|
||||
float l_px = (float)belt_takes_px / (float)k;
|
||||
|
||||
U32 cyl_length_takes_px = (U32)ceilf(w * s_resol);
|
||||
U32 texture_width = MAX_U32(back_ubs_x + uber_square_takes_px, belt_takes_px);
|
||||
U32 texture_height = belt_y + cyl_length_takes_px;
|
||||
|
||||
for (U32 i = 0; i < k; i++) {
|
||||
float angle = (float)i * 2 * M_PIf / (float)k;
|
||||
VecGenericMeshVertexInc_append(&vertices, (GenericMeshVertexInc){
|
||||
.pos = {r * cosf(angle), r * sinf(angle), w / 2},
|
||||
.tex = {
|
||||
(ubs_front_center.x + cosf(angle) * r_px) / (float)texture_width,
|
||||
(ubs_front_center.y - sinf(angle) * r_px) / (float)texture_height},
|
||||
});
|
||||
}
|
||||
for (U32 i = 0; i < k; i++) {
|
||||
float angle = (float)i * 2 * M_PIf / (float)k;
|
||||
VecGenericMeshVertexInc_append(&vertices, (GenericMeshVertexInc){
|
||||
.pos = {r * cosf(angle), r * sinf(angle), -w / 2},
|
||||
.tex = {
|
||||
(ubs_back_center.x - cosf(angle) * r_px) / (float)texture_width,
|
||||
(ubs_back_center.y - sinf(angle) * r_px) / (float)texture_height},
|
||||
});
|
||||
}
|
||||
for (U32 i = 0; i < k; i++) {
|
||||
float angle = (float)i * 2 * M_PIf / (float)k;
|
||||
float anext = (float)(i + 1) * 2 * M_PIf / (float)k;
|
||||
|
||||
vec2 tex0 = {l_px * (float)i / (float)texture_width, (float)belt_y / (float)texture_height};
|
||||
vec2 tex4 = {l_px * (float)(i + 1) / (float)texture_width,
|
||||
(float)(belt_y + cyl_length_takes_px) / (float)texture_height};
|
||||
VecGenericMeshVertexInc_append(&vertices, (GenericMeshVertexInc){
|
||||
.pos = {r * cosf(angle), r * sinf(angle), w / 2},
|
||||
.tex = tex0
|
||||
});
|
||||
VecGenericMeshVertexInc_append(&vertices, (GenericMeshVertexInc){
|
||||
.pos = {r * cosf(anext), r * sinf(anext), w / 2},
|
||||
.tex = (vec2){tex4.x, tex0.y}
|
||||
});
|
||||
VecGenericMeshVertexInc_append(&vertices, (GenericMeshVertexInc){
|
||||
.pos = {r * cosf(angle), r * sinf(angle), -w / 2},
|
||||
.tex = (vec2){tex0.x, tex4.y}
|
||||
});
|
||||
VecGenericMeshVertexInc_append(&vertices, (GenericMeshVertexInc){
|
||||
.pos = {r * cosf(anext), r * sinf(anext), -w / 2},
|
||||
.tex = tex4
|
||||
});
|
||||
}
|
||||
TextureDataR8G8B8A8 template = TextureDataR8G8B8A8_new(texture_width, texture_height);
|
||||
|
||||
for (U32 i = 1; i + 1 < k; i++) {
|
||||
U32 vis = i;
|
||||
U32 vin = i + 1;
|
||||
U32 vic = 0;
|
||||
VecU32_append_span(&indexes, (SpanU32){.data = (U32[]){vis, vin, vic}, .len = 3});
|
||||
MarieTriangle tex_trig = restore_triangle_from_mesh_topology(&vertices, texture_width, texture_height,
|
||||
vis, vin, vic);
|
||||
TextureDataR8G8B8A8_draw_triangle_of_one_color(&template, (vec3){0.5f, 0.9f, 0.5f}, tex_trig);
|
||||
}
|
||||
for (U32 i = 1; i + 1 < k; i++) {
|
||||
U32 vis = k + i;
|
||||
U32 vin = k + i + 1;
|
||||
U32 vic = k;
|
||||
VecU32_append_span(&indexes, (SpanU32){.data = (U32[]){vin, vis, vic}, .len = 3});
|
||||
MarieTriangle tex_trig = restore_triangle_from_mesh_topology(&vertices, texture_width, texture_height,
|
||||
vis, vin, vic);
|
||||
TextureDataR8G8B8A8_draw_triangle_of_one_color(&template, (vec3){0.2f, 0.1f, 0.9f}, tex_trig);
|
||||
}
|
||||
for (U32 i = 0; i < k; i++) {
|
||||
vec3 color = (i % 3 == 0) ? (vec3){0.8f, 0.8f, 0} :
|
||||
((i % 3 == 1) ? (vec3){0.6f, 0.2f, 0.7f} : (vec3){0.3f, 0, 0.95f});
|
||||
U32 v0 = 2 * k + 4 * i;
|
||||
VecU32_append_span(&indexes, (SpanU32){.data = (U32[]){v0 + 1, v0, v0 + 2, v0 + 1, v0 + 2, v0 + 3}, .len = 6});
|
||||
MarieTriangle tex_trig_1 = restore_triangle_from_mesh_topology(&vertices, texture_width, texture_height,
|
||||
v0 + 1, v0, v0 + 2);
|
||||
TextureDataR8G8B8A8_draw_triangle_of_one_color(&template, color, tex_trig_1);
|
||||
MarieTriangle tex_trig_2 = restore_triangle_from_mesh_topology(&vertices, texture_width, texture_height,
|
||||
v0 + 1, v0 + 2, v0 + 3);
|
||||
TextureDataR8G8B8A8_draw_triangle_of_one_color(&template, color, tex_trig_2);
|
||||
}
|
||||
|
||||
alice_write_generic_mesh_to_file((GenericMeshTopology){.vertices = vertices, .indexes = indexes}, path_to_mesh);
|
||||
TextureDataR8G8B8A8_write_to_png_nofail(&template, VecU8_to_span(&path_to_template_tex));
|
||||
VecU8_drop(path_to_template_tex);
|
||||
TextureDataR8G8B8A8_drop(template);
|
||||
|
||||
/* Here I generate normal tex trivially. */
|
||||
TextureDataR8G8B8A8 normal = TextureDataR8G8B8A8_new(1, 1);
|
||||
*TextureDataR8G8B8A8_mat(&normal, 0, 0) = compress_normal_vec_into_norm_texel((vec3){0, 1, 0});
|
||||
/* Right now it's just a pixel... */
|
||||
TextureDataR8G8B8A8_write_to_png_nofail(&normal, VecU8_to_span(&path_to_normal_tex));
|
||||
VecU8_drop(path_to_normal_tex);
|
||||
TextureDataR8G8B8A8_drop(normal);
|
||||
}
|
||||
|
||||
void r4_asset_gen_generic_mesh_quad(float width, float length, VecU8 path_to_save){
|
||||
VecGenericMeshVertexInc vert = VecGenericMeshVertexInc_from_span((SpanGenericMeshVertexInc){
|
||||
.data = (GenericMeshVertexInc[]){
|
||||
{.pos = {0, 0, 0}, .tex = {0, 0}},
|
||||
{.pos = {width, 0, 0}, .tex = {1, 0}},
|
||||
{.pos = {0, 0, length}, .tex = {0, 1}},
|
||||
{.pos = {width, 0, length}, .tex = {1, 1}}
|
||||
}, .len = 4});
|
||||
VecU32 indexes = VecU32_from_span((SpanU32){.data = (U32[]){1, 0, 2, 1, 2, 3}, .len = 6});
|
||||
alice_write_generic_mesh_to_file((GenericMeshTopology){.vertices = vert, .indexes = indexes}, path_to_save);
|
||||
}
|
||||
|
||||
/* a is r at bottom, b is r on top. y is in [0, height]. Shape is symmetrical from Oy */
|
||||
ShinyMeshTopology generate_shiny_lamp(float height, float a, float b){
|
||||
ShinyMeshVertexInc vert[24] = {
|
||||
{{+b, height, +b}},
|
||||
{{+b, 0, +b}},
|
||||
{{+b, 0, -b}},
|
||||
{{+b, height, -b}},
|
||||
|
||||
{{-b, 0, -b}},
|
||||
{{-b, 0, +b}},
|
||||
{{-b, height, +b}},
|
||||
{{-b, height, -b}},
|
||||
|
||||
{{+b, height, +b}},
|
||||
{{+b, height, -b}},
|
||||
{{-b, height, -b}},
|
||||
{{-b, height, +b}},
|
||||
|
||||
{{-b, 0, -b}},
|
||||
{{+b, 0, -b}},
|
||||
{{+b, 0, +b}},
|
||||
{{-b, 0, +b}},
|
||||
|
||||
{{+b, height, +b}},
|
||||
{{-b, height, +b}},
|
||||
{{-b, 0, +b}},
|
||||
{{+b, 0, +b}},
|
||||
|
||||
{{-b, 0, -b}},
|
||||
{{-b, height, -b}},
|
||||
{{+b, height, -b}},
|
||||
{{+b, 0, -b}},
|
||||
};
|
||||
VecShinyMeshVertexInc vertices = VecShinyMeshVertexInc_from_span(
|
||||
(SpanShinyMeshVertexInc){ .data = vert, .len = ARRAY_SIZE(vert) });
|
||||
VecU32 indexes = VecU32_new_reserved(36);
|
||||
for (U32 f = 0; f < 6; f++) {
|
||||
for (U32 j = 0; j < 6; j++)
|
||||
VecU32_append(&indexes, f * 4 + quad_to_triangles_conv_arr[j]);
|
||||
}
|
||||
return (ShinyMeshTopology){ .vertices = vertices, .indexes = indexes};
|
||||
}
|
||||
|
||||
void generate_one_forth_of_a_cylinder_with_bublazhuzhka(U64 w, U64 r, U64 k) {
|
||||
{
|
||||
TextureDataR8G8B8A8 tex = generate_tex_template_for_one_fourth_of_a_cylinder(120, (float)w, (float)r, k);
|
||||
TextureDataR8G8B8A8 fixed_tex = TextureDataR8G8B8A8_expand_nontransparent_1px(&tex);
|
||||
VecU8 name = VecU8_fmt("l2/textures/r4/log_%u_%u_%u_TEMPLATE.png", w, r, k);
|
||||
VecU8 name = VecU8_fmt("l2/textures/log_%u_%u_%u_TEMPLATE.png", w, r, k);
|
||||
TextureDataR8G8B8A8_write_to_png_nofail(&fixed_tex, VecU8_to_span(&name));
|
||||
VecU8_drop(name);
|
||||
TextureDataR8G8B8A8_drop(fixed_tex);
|
||||
@ -683,7 +868,7 @@ void for_log(U64 w, U64 r, U64 k) {
|
||||
{
|
||||
TextureDataR8G8B8A8 tex = generate_normal_tex_for_one_fourth_of_a_cylinder(120, (float)w, (float)r, k);
|
||||
TextureDataR8G8B8A8 fixed_tex = TextureDataR8G8B8A8_expand_nontransparent_1px(&tex);
|
||||
VecU8 name = VecU8_fmt("l2/textures/r4/log_%u_%u_%u_NORMAL.png", w, r, k);
|
||||
VecU8 name = VecU8_fmt("l2/textures/log_%u_%u_%u_NORMAL.png", w, r, k);
|
||||
TextureDataR8G8B8A8_write_to_png_nofail(&fixed_tex, VecU8_to_span(&name));
|
||||
VecU8_drop(name);
|
||||
TextureDataR8G8B8A8_drop(fixed_tex);
|
||||
@ -693,15 +878,19 @@ void for_log(U64 w, U64 r, U64 k) {
|
||||
alice_write_generic_mesh_to_file(top, VecU8_fmt("l2/models/log_%u_%u_%u.AliceGenericMesh", w, r, k));
|
||||
}
|
||||
|
||||
|
||||
|
||||
/* We are on l2 */
|
||||
int gen_assets_for_r4() {
|
||||
mkdir_nofail("l2/models");
|
||||
mkdir_nofail("l2/textures");
|
||||
mkdir_nofail("l2/textures/r4");
|
||||
for_log(10, 2, 6);
|
||||
generate_one_forth_of_a_cylinder_with_bublazhuzhka(10, 2, 6);
|
||||
alice_write_shiny_mesh_to_file(generate_shiny_cube(0.3f), vcstr("l2/models/cube.AliceShinyMesh"));
|
||||
alice_write_shiny_mesh_to_file(generate_shiny_lamp(0.3f, 0.13f, 0.19f), vcstr("l2/models/lamp.AliceShinyMesh"));
|
||||
r4_asset_gen_generic_mesh_quad(10, 10, vcstr("l2/models/quad.AliceGenericMesh"));
|
||||
r4_asset_gen_generic_mesh_cylinder(200, 0.4f, 0.06f, 5, vcstr("l2/models/puck.AliceGenericMesh"),
|
||||
vcstr("l2/textures/puck_TEMPLATE.png"), vcstr("l2/textures/puck_NORMAL.png"));
|
||||
r4_asset_gen_generic_mesh_cylinder(80, 0.13f, 1.5f, 4, vcstr("l2/models/stick.AliceGenericMesh"),
|
||||
vcstr("l2/textures/stick_TEMPLATE.png"), vcstr("l2/textures/stick_NORMAL.png"));
|
||||
return 0;
|
||||
}
|
||||
|
||||
|
||||
@ -362,13 +362,15 @@ void LucyGlyphCache_another_frame(LucyGlyphCache* self){
|
||||
}
|
||||
|
||||
/* This function does not check font file for correctness, use only with trusted fonts */
|
||||
LucyFace LucyFace_new(FT_Library lib, LucyGlyphCache* cache, VecU8 path){
|
||||
LucyFace* LucyFace_new(FT_Library lib, LucyGlyphCache* cache, VecU8 path){
|
||||
VecU8_append(&path, 0); // Making it null-terminated
|
||||
FT_Face face;
|
||||
FT_Error ret = FT_New_Face(lib, (const char*)path.buf, 0, &face);
|
||||
check(ret == 0);
|
||||
VecU8_drop(path);
|
||||
return (LucyFace){.p = cache, .ft_face = face, .sizes = RBTree_MapU32ToLucyFaceFixedSize_new()};
|
||||
LucyFace* hand = safe_malloc(sizeof(LucyFace));
|
||||
*hand = (LucyFace){.p = cache, .ft_face = face, .sizes = RBTree_MapU32ToLucyFaceFixedSize_new()};
|
||||
return hand;
|
||||
}
|
||||
|
||||
RBTreeNodeLucyFaceFixedSize* LucyFace_of_size(LucyFace* self, U32 size){
|
||||
|
||||
@ -192,23 +192,10 @@ void MargaretBufAllocator_drop(MargaretBufAllocator self){
|
||||
BufRBTreeByLen_SetMargaretBAFreeSegment_drop(self.mem_free_space);
|
||||
}
|
||||
|
||||
/* Free one subbuffer, not a whole MBA :) */
|
||||
void MargaretBufAllocator_free(MargaretBufAllocator* self, MargaretSubbuf allocation){
|
||||
U64Segment left_free_space = MargaretBufAllocator__get_left_free_space(self, &allocation);
|
||||
U64Segment right_free_space = MargaretBufAllocator__get_right_free_space(self, &allocation);
|
||||
|
||||
MargaretBufAllocator__erase_gap(self, allocation.block, left_free_space.start, left_free_space.len);
|
||||
MargaretBufAllocator__erase_gap(self, allocation.block, right_free_space.start, right_free_space.len);
|
||||
MargaretBufAllocator__insert_gap(self, allocation.block,
|
||||
left_free_space.start,
|
||||
right_free_space.start + right_free_space.len - left_free_space.start);
|
||||
|
||||
bool eret = BufRBTree_MapU64ToU64_erase(&allocation.block->occupants, allocation.start);
|
||||
assert(eret);
|
||||
}
|
||||
|
||||
/* Idk how to hide this monster */
|
||||
void MargaretBufAllocator_debug(const MargaretBufAllocator* self){
|
||||
if (!self->host_visible)
|
||||
return;
|
||||
printf(" ======== MargaretBufAllocator state ======== \n");
|
||||
int n_segments = (int)self->mem_free_space.el.len;
|
||||
printf("Blocks:\n");
|
||||
@ -241,7 +228,24 @@ void MargaretBufAllocator_debug(const MargaretBufAllocator* self){
|
||||
}
|
||||
}
|
||||
|
||||
/* Free one subbuffer, not a whole MBA :) */
|
||||
void MargaretBufAllocator_free(MargaretBufAllocator* self, MargaretSubbuf allocation){
|
||||
U64Segment left_free_space = MargaretBufAllocator__get_left_free_space(self, &allocation);
|
||||
U64Segment right_free_space = MargaretBufAllocator__get_right_free_space(self, &allocation);
|
||||
|
||||
MargaretBufAllocator__erase_gap(self, allocation.block, left_free_space.start, left_free_space.len);
|
||||
MargaretBufAllocator__erase_gap(self, allocation.block, right_free_space.start, right_free_space.len);
|
||||
MargaretBufAllocator__insert_gap(self, allocation.block,
|
||||
left_free_space.start,
|
||||
right_free_space.start + right_free_space.len - left_free_space.start);
|
||||
|
||||
bool eret = BufRBTree_MapU64ToU64_erase(&allocation.block->occupants, allocation.start);
|
||||
assert(eret);
|
||||
MargaretBufAllocator_debug(self);
|
||||
}
|
||||
|
||||
NODISCARD MargaretSubbuf MargaretBufAllocator_alloc(MargaretBufAllocator* self, U64 req_size){
|
||||
MargaretBufAllocator_debug(self);
|
||||
req_size = margaret_bump_buffer_size_to_alignment(req_size, self->alignment_exp);
|
||||
|
||||
VkPhysicalDeviceMaintenance3Properties maintenance3_properties = {
|
||||
@ -266,9 +270,11 @@ NODISCARD MargaretSubbuf MargaretBufAllocator_alloc(MargaretBufAllocator* self,
|
||||
new_block->occupation_counter = req_size;
|
||||
bool iret = BufRBTree_MapU64ToU64_insert(&new_block->occupants, 0, req_size);
|
||||
assert(iret);
|
||||
MargaretBufAllocator_debug(self);
|
||||
return (MargaretSubbuf){.block = &self->blocks.first->el, 0, req_size};
|
||||
}
|
||||
MargaretBufAllocator__put_buf_to_a_gap(self, free_gap.some, req_size);
|
||||
MargaretBufAllocator_debug(self);
|
||||
return (MargaretSubbuf){.block = free_gap.some.block, .start = free_gap.some.start, req_size};
|
||||
}
|
||||
|
||||
@ -299,12 +305,17 @@ NODISCARD MargaretSubbuf MargaretBufAllocator_expand(
|
||||
if (allocation->start + bigger_size > right_free_space.start + right_free_space.len){
|
||||
return MargaretBufAllocator_alloc(self, bigger_size);
|
||||
}
|
||||
MargaretBufAllocator_debug(self);
|
||||
MargaretBufAllocator__erase_gap(self, allocation->block, right_free_space.start, right_free_space.len);
|
||||
MargaretBufAllocator__insert_gap(self, allocation->block,
|
||||
allocation->start + bigger_size,
|
||||
right_free_space.len + (allocation->len - bigger_size));
|
||||
|
||||
allocation->len = bigger_size;
|
||||
U64 my_it = BufRBTree_MapU64ToU64_find(&allocation->block->occupants, allocation->start);
|
||||
assert(my_it > 0 && my_it <= allocation->block->occupants.el.len);
|
||||
allocation->block->occupants.el.buf[my_it - 1].value = bigger_size;
|
||||
MargaretBufAllocator_debug(self);
|
||||
return (MargaretSubbuf){0};
|
||||
}
|
||||
|
||||
@ -331,7 +342,9 @@ void MargaretBufAllocator_expand_or_move_old_host_visible(
|
||||
memcpy(MargaretSubbuf_get_mapped(&maybe_bigger), MargaretSubbuf_get_mapped(allocation), allocation->len);
|
||||
MargaretBufAllocator_free(self, *allocation);
|
||||
*allocation = maybe_bigger;
|
||||
MargaretBufAllocator_debug(self);
|
||||
}
|
||||
MargaretBufAllocator_debug(self);
|
||||
}
|
||||
|
||||
/* It tries to expand buffer, but if it fails, it creates a freshly-new buffer. It
|
||||
|
||||
@ -64,7 +64,7 @@ void TextureDataR8G8B8A8_draw_triangle_of_one_color_h_draw_guest(void* ug, S32 x
|
||||
}
|
||||
|
||||
/* Given triangle is not natural : it is from parameter space */
|
||||
void TextureDataR8G8B8A8_draw_triangle_of_one_color(
|
||||
void TextureDataR8G8B8A8_draw_parametrized_triangle_of_one_color(
|
||||
TextureDataR8G8B8A8* self, vec3 color, MarieTriangle param_triang, mat3x2 trop
|
||||
) {
|
||||
TextureDataR8G8B8A8_draw_triangle_of_one_color_H_DrawGuest aboba =
|
||||
@ -76,4 +76,13 @@ void TextureDataR8G8B8A8_draw_triangle_of_one_color(
|
||||
.guest = &aboba});
|
||||
}
|
||||
|
||||
void TextureDataR8G8B8A8_draw_triangle_of_one_color(TextureDataR8G8B8A8* self, vec3 color, MarieTriangle trig){
|
||||
TextureDataR8G8B8A8_draw_triangle_of_one_color_H_DrawGuest aboba =
|
||||
{ self, marie_color_vec4_to_cvec4(vec3_and_one(color)) };
|
||||
marie_rasterize_triangle_with_attr(
|
||||
(MariePlaneVertAttr){trig.v0, {}}, (MariePlaneVertAttr){trig.v1, {}}, (MariePlaneVertAttr){trig.v2, {}},
|
||||
(FnMarieRasterizerCallback){.fn = TextureDataR8G8B8A8_draw_triangle_of_one_color_h_draw_guest,
|
||||
.guest = &aboba});
|
||||
}
|
||||
|
||||
#endif
|
||||
@ -1,4 +1,56 @@
|
||||
import Allie
|
||||
import Geom
|
||||
import Control.Monad (forM_)
|
||||
|
||||
goodColorOfCube :: (Integral a) => a -> Vec3
|
||||
goodColorOfCube i = ((Vec3 100 0 0) ^*^ t) ^+^ ((Vec3 0 50 90) ^*^ (1 - t)) where t = ((fromIntegral i :: Float) / 4)
|
||||
|
||||
goodLightPos :: (Integral a) => a -> Vec3
|
||||
goodLightPos i = ((Vec3 0 2 1) ^*^ t) ^+^ ((Vec3 5 1 1) ^*^ (1 - t)) where t = ((fromIntegral i :: Float) / 4)
|
||||
|
||||
main :: IO()
|
||||
main = justFuckingDoSomething
|
||||
main = do
|
||||
alice <- newAlice
|
||||
aliceSetSkyColor alice (Vec4 0.9 0 0.6 1)
|
||||
face <- aliceNewLucyFace alice "src/l3/fonts/DMSerifText-Regular.ttf"
|
||||
faceOf40 <- aliceLucyFaceOfSize face 40
|
||||
lucyFaceAddGlyphs faceOf40 32 (126 - 32 + 1)
|
||||
aliceAddText alice faceOf40 (Vec4 1 1 0 1) "Privet" 100 200
|
||||
|
||||
weirdStructure <- aliceAddGenericMeshHand alice "gen/l2/models/log_10_2_6.AliceGenericMesh"
|
||||
"src/l3/textures/log_10_2_6_diffuse.png" "gen/l2/textures/log_10_2_6_NORMAL.png" "src/l3/textures/log_10_2_6_specular.png"
|
||||
aliceGenericMeshResizeInstanceArr alice weirdStructure 1
|
||||
aliceGenericMeshSetInst weirdStructure 0 (AliceGenericMeshInstance (mat4Transit (Vec3 (-3.0) (-2.0) (-5.0))))
|
||||
|
||||
cube <- aliceAddShinyMeshHand alice "gen/l2/models/cube.AliceShinyMesh"
|
||||
aliceShinyMeshResizeInstanceArr alice cube 5
|
||||
|
||||
|
||||
aliceSetPointLightCount alice 5
|
||||
forM_ [0..4] $ \i -> do
|
||||
aliceShinyMeshSetInst cube i (AliceShinyMeshInstance (mat4Transit (goodLightPos i)) (Vec3 1 1 1) (goodColorOfCube i))
|
||||
aliceSetPointLight alice (fromIntegral i) (AlicePointLight (goodLightPos i) (goodColorOfCube i))
|
||||
|
||||
-- state <- newIORef 67
|
||||
-- Create the Callbacks structure.
|
||||
let callbacks = Callbacks myonKeyboardKey myonAnotherFrame where
|
||||
myonKeyboardKey keysym keyAction = do
|
||||
-- old <- readIORef state
|
||||
-- writeIORef state (old + 1)
|
||||
putStrLn ("Got a keypress")
|
||||
myonAnotherFrame fl = do
|
||||
oldPos <- aliceGetCamPos alice
|
||||
goForward <- aliceIsPressed alice 0x77
|
||||
if goForward
|
||||
then do
|
||||
backDir <- aliceGetCamBack alice
|
||||
aliceSetCamPos alice (oldPos ^+^ (backDir ^*^ (-fl * 10)))
|
||||
else return ()
|
||||
|
||||
--cur <- readIORef state
|
||||
--aliceClearScreenTextLabel alicePerm
|
||||
--aliceAddScreenTextLabel alicePerm ("Current value is = " ++ show cur)
|
||||
|
||||
|
||||
-- Allocate space for the struct, poke it, and pass to C.
|
||||
aliceMainloop alice callbacks
|
||||
|
||||
@ -4,25 +4,34 @@ AliceGenericMeshPath AliceGenericMeshPath_for_log(SpanU8 root_dir, U64 w, U64 r,
|
||||
return (AliceGenericMeshPath){
|
||||
.topology_path = VecU8_fmt("%s/gen/l2/models/log_%u_%u_%u.AliceGenericMesh", root_dir, w, r, k),
|
||||
.diffuse_texture_path = VecU8_fmt("%s/src/l3/textures/log_%u_%u_%u_diffuse.png", root_dir, w, r, k),
|
||||
.normal_texture_path = VecU8_fmt("%s/gen/l2/textures/r4/log_%u_%u_%u_NORMAL.png", root_dir, w, r, k),
|
||||
.normal_texture_path = VecU8_fmt("%s/gen/l2/textures/log_%u_%u_%u_NORMAL.png", root_dir, w, r, k),
|
||||
.specular_texture_path = VecU8_fmt("%s/src/l3/textures/log_%u_%u_%u_specular.png", root_dir, w, r, k),
|
||||
};
|
||||
}
|
||||
|
||||
void main_h_on_wayland_keyboard_key(Alice* alice){
|
||||
AliceGenericMeshPath AliceGenericMeshPath_for_puck(){
|
||||
return (AliceGenericMeshPath){
|
||||
.topology_path = VecU8_fmt("gen/l2/models/puck.AliceGenericMesh"),
|
||||
.diffuse_texture_path = VecU8_fmt("src/l3/textures/puck_diffuse.png"),
|
||||
.normal_texture_path = VecU8_fmt("gen/l2/textures/puck_NORMAL.png"),
|
||||
.specular_texture_path = VecU8_fmt("src/l3/textures/puck_specular.png"),
|
||||
};
|
||||
}
|
||||
|
||||
void main_h_on_wayland_keyboard_key(void* data, U32 keysym, U32 act){
|
||||
|
||||
}
|
||||
|
||||
void main_h_on_another_frame(Alice* alice){
|
||||
void main_h_on_another_frame(void* data, float fl){
|
||||
|
||||
}
|
||||
|
||||
int main(){
|
||||
Alice* alice = Alice_new();
|
||||
|
||||
LucyFace font_face = LucyFace_new(alice->ft_library, &alice->lucy_cache,
|
||||
LucyFace* font_face = LucyFace_new(alice->ft_library, &alice->lucy_cache,
|
||||
VecU8_fmt("%s/src/l3/fonts/DMSerifText-Regular.ttf", cstr(".")));
|
||||
RBTreeNodeLucyFaceFixedSize* font_face_of_size_40 = LucyFace_of_size(&font_face, 40);
|
||||
RBTreeNodeLucyFaceFixedSize* font_face_of_size_40 = LucyFace_of_size(font_face, 40);
|
||||
VecLucyGlyphCachingRequest lucy_requests = VecLucyGlyphCachingRequest_new();
|
||||
VecU32Segment ranges_needed = VecU32Segment_new();
|
||||
VecU32Segment_append(&ranges_needed, (U32Segment){.start = 32, .len = 126 - 32 + 1});
|
||||
@ -31,46 +40,56 @@ int main(){
|
||||
});
|
||||
LucyGlyphCache_add_glyphs(lucy_requests);
|
||||
|
||||
ListNodeAliceGenericMeshHand* model_gen = Alice_add_generic_mesh(alice, AliceGenericMeshPath_for_log(cstr("."), 10, 2, 6));
|
||||
AliceGenericMeshHand_resize_instance_arr(alice, &model_gen->el, 100);
|
||||
LucyRenderer_add_text(&alice->lucy_renderer, font_face_of_size_40, (vec4){1, 0, 0, 1}, 0,
|
||||
cstr("Bebra budet\notnyahana"), (ivec2){10, 10});
|
||||
|
||||
for (int X = 0; X < 10; X++) {
|
||||
for (int Z = 0; Z < 10; Z++) {
|
||||
AliceGenericMeshHand_set(&model_gen->el, X * 10 + Z, (GenericMeshInstanceInc){
|
||||
ListNodeAliceGenericMeshHand* model_gen = Alice_add_generic_mesh(alice, AliceGenericMeshPath_for_log(cstr("."), 10, 2, 6));
|
||||
AliceGenericMeshHand_resize_instance_arr(alice, &model_gen->el, 1);
|
||||
|
||||
for (int X = 0; X < 1; X++) {
|
||||
for (int Z = 0; Z < 1; Z++) {
|
||||
AliceGenericMeshHand_set_inst(&model_gen->el, X * 10 + Z, (GenericMeshInstanceInc){
|
||||
.model_t = marie_translation_mat4((vec3){11.f * (float)X, -6, 4.f * (float)Z}),
|
||||
});
|
||||
}
|
||||
}
|
||||
|
||||
ListNodeAliceShinyMeshHand *model_sh = Alice_add_shiny_mesh(alice, vcstr("./gen/l2/models/cube.AliceShinyMesh"));
|
||||
AliceShinyMeshHand_resize_instance_arr(alice, &model_sh->el, 100);
|
||||
// ListNodeAliceShinyMeshHand *model_sh = Alice_add_shiny_mesh(alice, vcstr("./gen/l2/models/cube.AliceShinyMesh"));
|
||||
// AliceShinyMeshHand_resize_instance_arr(alice, &model_sh->el, 100);
|
||||
|
||||
for (int X = 0; X < 10; X++) {
|
||||
for (int Z = 0; Z < 10; Z++) {
|
||||
AliceShinyMeshHand_set(&model_sh->el, X * 10 + Z, (ShinyMeshInstanceInc){
|
||||
.color_on = {0, 1, 0}, .color_off = {0.3f, 0.6f, 0.3f},
|
||||
.model_t = marie_translation_mat4((vec3){11.f * (float)X - 20, 10, 4.f * (float)Z - 10}),
|
||||
});
|
||||
}
|
||||
}
|
||||
// for (int X = 0; X < 10; X++) {
|
||||
// for (int Z = 0; Z < 10; Z++) {
|
||||
// AliceShinyMeshHand_set_inst(&model_sh->el, X * 10 + Z, (ShinyMeshInstanceInc){
|
||||
// .color_on = {0, 1, 0}, .color_off = {0.3f, 0.6f, 0.3f},
|
||||
// .model_t = marie_translation_mat4((vec3){11.f * (float)X - 20, 10, 4.f * (float)Z - 10}),
|
||||
// });
|
||||
// }
|
||||
// }
|
||||
|
||||
Pipeline0UBO* ubo = (Pipeline0UBO*)MargaretSubbuf_get_mapped(&alice->pipeline0_ubo.staging);
|
||||
assert(pipeline_0_ubo_point_light_max_count >= 100);
|
||||
ubo->point_light_count = 100;
|
||||
ubo->spotlight_count = 0;
|
||||
for (int X = 0; X < 10; X++) {
|
||||
for (int Z = 0; Z < 10; Z++) {
|
||||
ubo->point_light_arr[X * 10 + Z] = (Pipeline0PointLight){
|
||||
.pos = (vec3){11.f * (float)X - 20, 10, 4.f * (float)Z - 10},
|
||||
.color = {5, 5, 5}
|
||||
};
|
||||
}
|
||||
}
|
||||
ubo->point_light_arr[0].color = (vec3){100, 100, 100};
|
||||
// Pipeline0UBO* ubo = (Pipeline0UBO*)MargaretSubbuf_get_mapped(&alice->pipeline0_ubo.staging);
|
||||
// assert(pipeline_0_ubo_point_light_max_count >= 100);
|
||||
// ubo->point_light_count = 100;
|
||||
// ubo->spotlight_count = 0;
|
||||
// for (int X = 0; X < 10; X++) {
|
||||
// for (int Z = 0; Z < 10; Z++) {
|
||||
// ubo->point_light_arr[X * 10 + Z] = (Pipeline0PointLight){
|
||||
// .pos = (vec3){11.f * (float)X - 20, 10, 4.f * (float)Z - 10},
|
||||
// .color = {5, 5, 5}
|
||||
// };
|
||||
// }
|
||||
// }
|
||||
// ubo->point_light_arr[0].color = (vec3){100, 100, 100};
|
||||
|
||||
LucyRenderer_add_text(&alice->lucy_renderer, font_face_of_size_40, (vec4){1, 0, 0, 1}, 0,
|
||||
cstr("Bebra budet\notnyahana"), (ivec2){10, 10});
|
||||
|
||||
// ListNodeAliceGenericMeshHand* model_puck = Alice_add_generic_mesh(alice, AliceGenericMeshPath_for_puck());
|
||||
// AliceGenericMeshHand_resize_instance_arr(alice, &model_puck->el, 100);
|
||||
// for (int X = 0; X < 10; X++) {
|
||||
// for (int Z = 0; Z < 10; Z++) {
|
||||
// AliceGenericMeshHand_set_inst(&model_puck->el, X * 10 + Z, (GenericMeshInstanceInc){
|
||||
// .model_t = marie_translation_mat4((vec3){11.f * (float)X - 20, -1, 4.f * (float)Z - 10}),
|
||||
// });
|
||||
// }
|
||||
// }
|
||||
Alice_mainloop(alice, &(AliceCallbacks){
|
||||
.on_wl_keyboard_key = main_h_on_wayland_keyboard_key,
|
||||
.on_another_frame = main_h_on_another_frame,
|
||||
|
||||
BIN
src/l3/textures/asphalt.png
Normal file
BIN
src/l3/textures/asphalt.png
Normal file
Binary file not shown.
|
After Width: | Height: | Size: 2.5 MiB |
BIN
src/l3/textures/funny_floor_specular.png
Normal file
BIN
src/l3/textures/funny_floor_specular.png
Normal file
Binary file not shown.
|
After Width: | Height: | Size: 860 B |
BIN
src/l3/textures/puck_diffuse.png
Normal file
BIN
src/l3/textures/puck_diffuse.png
Normal file
Binary file not shown.
|
After Width: | Height: | Size: 11 KiB |
BIN
src/l3/textures/puck_specular.png
Normal file
BIN
src/l3/textures/puck_specular.png
Normal file
Binary file not shown.
|
After Width: | Height: | Size: 8.5 KiB |
Loading…
x
Reference in New Issue
Block a user