2424--- @alias height integer
2525--- @alias position { x : north , y : east , z : height }
2626
27- --- @alias item { name : string , count : integer }
28- --- @alias turtleSlot { name : string , count : integer , maxcount : integer , durabilty : integer , fuelgain : integer , placeAble : boolean , equipable : boolean }
29- --- @alias inventory { [integer] : turtleSlot }
27+ --- @alias item { name : string , durabilty : integer , equipable : boolean , fuelgain : integer , placeAble : boolean , maxcount : number , wildcardInfo : any , count : integer }
28+ --- @alias inventory { [integer] : item }
29+
30+ -- ---@alias equipslots {left : }
3031
3132
3233
@@ -96,6 +97,9 @@ local function down(self)
9697 self .position .y = self .position .y - 1
9798 return true
9899end
100+ local function slotNotEmpty (slot )
101+ return slot ~= nil
102+ end
99103
100104--- @return TurtleProxy
101105function turtleMock .createMock ()
@@ -110,7 +114,7 @@ function turtleMock.createMock()
110114 --- @type number
111115 fuelLevel = 0 ,
112116 --- @type boolean
113- canPrint = true ,
117+ canPrint = false ,
114118 --- @type inventory
115119 inventory = {},
116120 --- @type integer
210214function turtleMock :getItemCount (slot )
211215 slot = slot or self .selectedSlot
212216 assert ((slot >= 1 and slot <= 16 ) or slot == nil , " Slot number " .. slot .. " out of range" )
213- return self .inventory [slot ] ~= nil and self .inventory [slot ].count or 0
217+ return slotNotEmpty ( self .inventory [slot ]) and self .inventory [slot ].count or 0
214218end
215219
216220--- gets the space in the selected slot or the specified slot
219223function turtleMock :getItemSpace (slot )
220224 slot = slot or self .selectedSlot
221225 assert ((slot >= 1 and slot <= 16 ) or slot == nil , " Slot number " .. slot .. " out of range" )
222- return self .inventory [slot ] ~= nil and self .inventory [slot ].maxcount - self .inventory [slot ].count or
226+ return slotNotEmpty ( self .inventory [slot ]) and self .inventory [slot ].maxcount - self .inventory [slot ].count or
223227 self .defaultMaxSlotSize
224228end
225229
@@ -233,23 +237,24 @@ end
233237function turtleMock :getItemDetail (slot )
234238 slot = slot or self .selectedSlot
235239 assert ((slot >= 1 and slot <= 16 ) or slot == nil , " Slot number " .. slot .. " out of range" )
236- local item = self .inventory [slot ]
237- return item ~= nil and { name = item .name , count = item .count } or nil
240+ --- @type item
241+ local iSlot = self .inventory [slot ]
242+ return iSlot ~= nil and { name = iSlot .name , count = iSlot .count } or nil
238243end
239244
240245--- Compare the item in the selected slot to the item in the specified slot.
241246--- @param slot integer
242247--- @return boolean equal true if the items are equal
243248function turtleMock :compareTo (slot )
244249 assert ((slot >= 1 and slot <= 16 ), " Slot number " .. slot .. " out of range" )
245- local item = self .inventory [self .selectedSlot ]
246- local compareItem = self .inventory [slot ]
247- if item == nil and compareItem == nil then
250+ local iSlot = self .inventory [self .selectedSlot ]
251+ local compareSlot = self .inventory [slot ]
252+ if iSlot == nil and compareSlot == nil then
248253 return true
249- elseif item == nil or compareItem == nil then
254+ elseif iSlot == nil or compareSlot == nil then
250255 return false
251256 end
252- return item .name == compareItem .name
257+ return iSlot .name == compareSlot .name
253258end
254259
255260--- Transfers items between the selected slot and the specified slot.
@@ -271,7 +276,7 @@ function turtleMock:transferTo(slot, count)
271276 return true
272277 end
273278 self .inventory [slot ] = deepCopy (self .inventory [self .selectedSlot ])
274- self .inventory [slot ].count = math.min (self .inventory [slot ]. maxcount , count )
279+ self .inventory [slot ].count = math.min (self .inventory [slot ] and self . inventory [ slot ]. maxcount or 0 , count )
275280 local transferTo = math.min (currentSlot .count , count )
276281 currentSlot .count = currentSlot .count - transferTo
277282 if currentSlot .count < 1 then
298303
299304--- Finds the first slot containing the specified item or no Item, starting with the selected slot and looping around.
300305--- @param turtle TurtleMock
301- --- @param item turtleSlot
306+ --- @param item item
302307--- @param startingSlot number
303308local function findFittingSlot (turtle , item , startingSlot )
304309 for i = startingSlot , 16 do
@@ -323,10 +328,11 @@ end
323328---
324329--- <b>note</b>: This function will only work for tests and does not work on the CraftOS-Turtle
325330--- @param turtle TurtleMock
326- --- @param item turtleSlot
331+ --- @param item item
327332--- @param slot number | nil
328333local function pickUpItem (turtle , item , slot )
329334 assert (item .count > 0 , " Count must be greater than 0" )
335+ turtle :print (" Item: " , item .count )
330336 if slot == nil then
331337 while item .count > 0 do
332338 local fittingSlot = findFittingSlot (turtle , item , turtle .selectedSlot )
@@ -335,19 +341,18 @@ local function pickUpItem(turtle, item, slot)
335341 end
336342 local space = turtle :getItemSpace (fittingSlot )
337343 local toTransfer = math.min (space , item .count )
344+
345+ local currentCount = turtle :getItemCount (fittingSlot )
346+ turtle .inventory [fittingSlot ] = deepCopy (item )
338347 if (turtle .inventory [fittingSlot ] == nil ) then
339- turtle .inventory [fittingSlot ] = {
340- name = item .name ,
341- count = toTransfer ,
342- maxcount = turtle
343- .defaultMaxSlotSize
344- }
348+ turtle .inventory [fittingSlot ].maxcount = item .maxcount or turtle .defaultMaxSlotSize
345349 end
350+ turtle .inventory [fittingSlot ].count = currentCount + toTransfer
346351 item .count = item .count - toTransfer
347352 end
348353 else
349354 assert ((slot >= 1 and slot <= 16 ), " Slot number " .. slot .. " out of range" )
350- if turtle .inventory [slot ] ~= nil and turtle .inventory [slot ].name ~= item .name then
355+ if slotNotEmpty ( turtle .inventory [slot ] ) and turtle .inventory [slot ].name ~= item .name then
351356 return false , " Can't pick up item, slot is not empty"
352357 end
353358 if turtle :getItemSpace (slot ) < item .count then
@@ -362,10 +367,12 @@ local function pickUpItem(turtle, item, slot)
362367 return true
363368end
364369
370+
371+
365372--- for Testing purposes:
366373
367374--- adds an item to the inventory
368- --- @param item turtleSlot
375+ --- @param item item
369376--- @param slot number | nil
370377function turtleMock :addItemToInventory (item , slot )
371378 local succ , errorReason = pickUpItem (self , item , slot )
@@ -379,6 +386,10 @@ function turtleMock:getFuelLevel()
379386 return self .fuelLevel
380387end
381388
389+ function turtleMock :getFuelLimit ()
390+ return self .fuelLimit
391+ end
392+
382393local function functionNotFoundError (key )
383394 return error (" Function / Key: '" .. key .. " ' not found" )
384395end
389400--- @param ... any
390401--- @return nil
391402function turtleMock :print (...)
392- return self .canPrint == true and print (... )
403+ if (self .canPrint == true ) then
404+ print (... )
405+ end
393406end
394407
395408local mt = {
0 commit comments