1+ --- @class placeAction
2+ --- @field funciton fun ( turtle : TurtleProxy | TurtleMock , item : item , position : position ): boolean , any[]
3+
4+ --- @class item
5+ --- @field name string
6+ --- @field durability integer | nil
7+ --- @field equipable boolean | nil
8+ --- @field fuelgain integer | nil
9+ --- @field placeAble boolean | nil
10+ --- @field placeAction placeAction | nil
11+ --- @field maxcount number | nil
12+ --- @field wildcardInfo any | nil
13+ --- @field count integer | nil
14+ --- @field tags table<string , any> | nil
15+
16+ --- @class inventory
17+ --- @field inventorySize integer
18+ --- @field [ integer] item | nil
19+ --- @field defaultMaxSlotSize integer
20+ --- @field selectedSlot integer
21+ --- @field createInventory fun ( self : inventory , inventorySize : integer ): inventory
22+ --- @field removeItem fun ( self : inventory , slot : integer , count : integer ): boolean , string | nil
23+ --- @field getItemDetail fun ( self : inventory , slot : integer | nil ): item | nil
24+ --- @field getItemSpace fun ( self : inventory , slot : integer | nil ): integer
25+ --- @field compareTo fun ( self : inventory , slot : integer ): boolean
26+ --- @field transferTo fun ( self : inventory , slot : integer , count : integer ): boolean , string | nil
27+ --- @field addItemToInventory fun ( self : inventory , item : item , slot : integer | nil ): boolean , string | nil
28+ --- @field getItemCount fun ( self : inventory , slot : integer | nil ): integer
29+ --- @field findFittingSlot fun ( self : inventory , item : item , slot : integer ): number
30+ --- @field select fun ( self : inventory , slot : integer ): boolean
31+ --- @field list fun (): item[]
32+ --- @field __index any
33+
34+ local deepCopy = require (" ../generalFunctions" ).deepCopy
35+
36+ --- # inventory
37+ --- Inventory system emulated
38+ local inventory = {
39+ inventorySize = 27 ,
40+ selectedSlot = 1 ,
41+ defaultMaxSlotSize = 64 ,
42+ }
43+
44+ -- #region local functions
45+ local function slotNotEmpty (slot )
46+ return slot ~= nil
47+ end
48+
49+ --- gets the space in the selected slot or the specified slot
50+ --- @param inventory inventory the inventory to get the space from
51+ --- @param slot integer | nil the slot to get the space for
52+ --- @return integer space maxcount - currentcount
53+ local function getItemSpace (inventory , slot )
54+ slot = slot or inventory .selectedSlot
55+ assert ((slot >= 1 and slot <= 16 ) or slot == nil , " Slot number " .. slot .. " out of range" )
56+ return slotNotEmpty (inventory [slot ]) and inventory [slot ].maxcount - inventory [slot ].count or
57+ inventory .defaultMaxSlotSize
58+ end
59+
60+ --- Finds the first slot containing the specified item or no Item, starting with the selected slot and looping around.
61+ --- @param inventory inventory
62+ --- @param item item
63+ --- @param startingSlot number
64+ local function findFittingSlot (inventory , item , startingSlot )
65+ for i = startingSlot , 16 do
66+ if inventory [i ] == nil then
67+ return i
68+ end
69+ if inventory [i ].name == item .name and getItemSpace (inventory , i ) > 0 then
70+ return i
71+ end
72+ end
73+ for i = 1 , startingSlot - 1 do
74+ if inventory [i ] == nil then
75+ return i
76+ end
77+ if inventory [i ].name == item .name and getItemSpace (inventory , i ) > 0 then
78+ return i
79+ end
80+ end
81+ end
82+
83+ --- gets the item count in the selected slot or the specified slot
84+ --- @param inventory inventory the inventory to get the item-count from
85+ --- @param slot integer the slot to get the item-count from
86+ --- @return integer count the amount of items in the slot
87+ local function getItemCount (inventory , slot )
88+ slot = slot or inventory .selectedSlot
89+ assert ((slot >= 1 and slot <= 16 ) or slot == nil , " Slot number " .. slot .. " out of range" )
90+ return slotNotEmpty (inventory [slot ]) and inventory [slot ].count or 0
91+ end
92+
93+ --- Adds items to the selected slot or the specified slot.
94+ ---
95+ --- <b>note</b>: This function will only work for tests and does not work on the CraftOS-Turtle
96+ --- @param inventory inventory
97+ --- @param item item
98+ --- @param slot number | nil
99+ local function pickUpItem (inventory , item , slot )
100+ assert (item .count > 0 , " Count must be greater than 0" )
101+ if slot == nil then
102+ while item .count > 0 do
103+ local fittingSlot = findFittingSlot (inventory , item , inventory .selectedSlot )
104+ if fittingSlot == nil then
105+ return false , " No fitting slot found"
106+ end
107+ local space = getItemSpace (inventory , fittingSlot )
108+ local toTransfer = math.min (space , item .count )
109+
110+ local currentCount = getItemCount (inventory , fittingSlot )
111+ inventory [fittingSlot ] = deepCopy (item )
112+ if (inventory [fittingSlot ] == nil ) then
113+ inventory [fittingSlot ].maxcount = item .maxcount or inventory .defaultMaxSlotSize
114+ end
115+ inventory [fittingSlot ].count = currentCount + toTransfer
116+ item .count = item .count - toTransfer
117+ end
118+ else
119+ assert ((slot >= 1 and slot <= 16 ), " Slot number " .. slot .. " out of range" )
120+ if slotNotEmpty (inventory [slot ] ) and inventory [slot ].name ~= item .name then
121+ return false , " Can't pick up item, slot is not empty"
122+ end
123+ if getItemSpace (inventory , slot ) < item .count then
124+ return false , " Not enough space in the slot"
125+ end
126+ if inventory [slot ] == nil then
127+ inventory [slot ] = item
128+ else
129+ inventory [slot ].count = inventory [slot ].count + item .count
130+ end
131+ end
132+ return true
133+ end
134+
135+ -- #endregion
136+
137+ -- #region public functions
138+
139+ --- ### Description:
140+ --- creates an Instance of of the Inventory class
141+ --- @param inventorySize any
142+ function inventory :createInventory (inventorySize )
143+ local i = {
144+ inventorySize = inventorySize or 27 ,
145+ selectedSlot = 1 ,
146+ defaultMaxSlotSize = 64 ,
147+ }
148+ setmetatable (i , self )
149+ self .__index = self
150+ return i
151+ end
152+
153+ --- ### Description:
154+ --- @param slot number
155+ --- @param count number
156+ --- @return boolean
157+ --- @return string | nil
158+ function inventory :removeItem ( slot , count )
159+ local item = self [slot ]
160+ if item == nil then
161+ return false , " No item in the slot"
162+ end
163+ if item .count < count then
164+ return false , " Not enough items in the slot"
165+ end
166+ item .count = item .count - count
167+ if item .count == 0 then
168+ self [slot ] = nil
169+ end
170+ return true
171+ end
172+
173+ --- ### Description:
174+ --- gets the item in the selected slot or the specified slot
175+ --- @param slot integer | nil the slot to get the item-details from
176+ --- @return item | nil item the item in the slot
177+ function inventory :getItemDetail (slot )
178+ slot = slot or self .selectedSlot
179+ assert ((slot >= 1 and slot <= self .inventorySize ) or slot == nil , " Slot number " .. slot .. " out of range" )
180+ --- @type item
181+ local iSlot = self [slot ]
182+ return iSlot ~= nil and { name = iSlot .name , count = iSlot .count } or nil
183+ end
184+
185+ --- gets the space in the selected slot or the specified slot
186+ --- @param slot integer | nil the slot to get the space for
187+ --- @return integer space maxcount - currentcount
188+ function inventory :getItemSpace (slot )
189+ return getItemSpace (self , slot )
190+ end
191+
192+ --- ### Description:
193+ --- Compare the item in the selected slot to the item in the specified slot.
194+ --- @param slot integer
195+ --- @return boolean equal true if the items are equal
196+ function inventory :compareTo (slot )
197+ assert ((slot >= 1 and slot <= 16 ), " Slot number " .. slot .. " out of range" )
198+ local iSlot = self [self .selectedSlot ]
199+ local compareSlot = self [slot ]
200+ if iSlot == nil and compareSlot == nil then
201+ return true
202+ elseif iSlot == nil or compareSlot == nil then
203+ return false
204+ end
205+ return iSlot .name == compareSlot .name
206+ end
207+
208+ --- ### Description:
209+ --- Transfers items between the selected slot and the specified slot.
210+ ---
211+ --- <b>note</b>: this function will transfer items when there is not enough room, but will return false non the less...
212+ --- @param slot integer the slot to transfer to
213+ --- @param count integer the amount of items to transfer
214+ --- @return boolean success true if the transfer was successful
215+ --- @return string | nil errorReason the reason why the transfer failed
216+ function inventory :transferTo (slot , count )
217+ assert (slot ~= nil , " Slot must be specified" )
218+ assert (count ~= nil , " Count must be specified" )
219+ assert ((slot >= 1 and slot <= 16 ), " Slot number " .. slot .. " out of range" )
220+ assert (count > 0 , " Count must be greater than 0" )
221+ local currentSlot = self [self .selectedSlot ]
222+ local targetSlot = self [slot ]
223+ if (currentSlot == nil ) or (targetSlot == nil ) then
224+ if currentSlot == nil then
225+ return true
226+ end
227+ self [slot ] = deepCopy (self [self .selectedSlot ])
228+ self [slot ].count = math.min (self [slot ] and self [slot ].maxcount or 0 , count )
229+ local transferTo = math.min (currentSlot .count , count )
230+ currentSlot .count = currentSlot .count - transferTo
231+ if currentSlot .count < 1 then
232+ self [self .selectedSlot ] = nil
233+ end
234+ return true
235+ elseif currentSlot .name == targetSlot .name then
236+ local space = targetSlot .maxcount - targetSlot .count
237+ local worked = false
238+ local toTransfer = math.min (space , count )
239+ if space >= count then
240+ worked = true
241+ end
242+ targetSlot .count = targetSlot .count + toTransfer
243+ currentSlot .count = currentSlot .count - toTransfer
244+ if currentSlot .count < 1 then
245+ self [self .selectedSlot ] = nil
246+ end
247+ --- @diagnostic disable-next-line : deprecated
248+ local unpack = table.unpack or unpack
249+ return worked and true or unpack ({ false , " Not enough space in the target slot" })
250+ end
251+ return false , " Not enough space in the target slot"
252+ end
253+
254+ --- ### Description:
255+ --- for Testing purposes:
256+ --- adds an item to the inventory
257+ --- @param item item
258+ --- @param slot number | nil
259+ function inventory :addItemToInventory (item , slot )
260+ local succ , errorReason = pickUpItem (self , item , slot )
261+ assert (succ , errorReason )
262+ return succ , errorReason
263+ end
264+
265+ --- ### Description:
266+ --- selects the slot
267+ --- @param slot integer the slot to select
268+ --- @return boolean success true if the slot was selected
269+ function inventory :select (slot )
270+ assert (slot >= 1 and slot <= 16 , " bad argument #1 (expected number between 1 and 16)" )
271+ self .selectedSlot = slot
272+ return true
273+ end
274+
275+ --- ### Description:
276+ --- @param item item
277+ --- @param slot number
278+ --- @return number
279+ function inventory :findFittingSlot (item , slot )
280+ return findFittingSlot (self , item , slot )
281+ end
282+
283+ --- gets the item count in the selected slot or the specified slot
284+ --- @param slot integer the slot to get the item-count from
285+ --- @return integer count the amount of items in the slot
286+ function inventory :getItemCount (slot )
287+ return getItemCount (self , slot )
288+ end
289+
290+ --- ### Description:
291+ --- List all items in this inventory.
292+ --- This returns a table, with an entry for each slot.
293+ function inventory :list ()
294+ --- todo: implement
295+ local items = {}
296+ for i = 1 , inventory .inventorySize do
297+ table.insert (items , inventory :getItemDetail (i ))
298+ end
299+ return items
300+ end
301+
302+ -- #endregion
303+
304+ return inventory
0 commit comments