blob: 110201f5d39ee5595acf1de5790b2b2accb5bf66 [file] [log] [blame]
Nico Hubercc960f22024-01-29 01:13:45 +01001-- Copyright (C) 2024 secunet Security Networks AG
2--
3-- This program is free software; you can redistribute it and/or modify
4-- it under the terms of the GNU General Public License as published by
5-- the Free Software Foundation; either version 2 of the License, or
6-- (at your option) any later version.
7
8with System;
9with Interfaces;
10with Interfaces.C;
11
12with FILO.Blockdev;
13with FILO.FS.VFS;
14
15use Interfaces.C;
16
17package body FILO.FS.ISO9660 is
18
19 function Is_Mounted (State : T) return Boolean is (State.S >= Mounted);
20 function Is_Open (State : T) return Boolean is (State.S = File_Opened);
21
22 --------------------------------------------------------------------------
23
24 procedure Read
Nico Huber4210fcc2024-01-29 16:33:47 +010025 (Buf : out Buffer_Type;
Nico Hubercc960f22024-01-29 01:13:45 +010026 Block : in FSBlock;
27 Offset : in FSBlock_Index;
28 FS_Len : in Partition_Length;
29 Success : out Boolean)
30 with
31 Pre => Buf'Length <= FSBlock_Size - Offset
32 is
33 Block_64 : constant Integer_64 := Integer_64 (Block);
34 Offset_64 : constant Integer_64 := Integer_64 (Offset);
35 Max_Block_Offset : constant Integer_64 := Integer_64 (FS_Len) / FSBlock_Size - 1;
36 begin
37 if Block_64 > Max_Block_Offset then
Nico Huber4210fcc2024-01-29 16:33:47 +010038 Buf := (others => 16#00#);
Nico Hubercc960f22024-01-29 01:13:45 +010039 Success := False;
40 return;
41 end if;
42 Blockdev.Read (Buf, Blockdev_Length (Block_64 * FSBlock_Size + Offset_64), Success);
43 end Read;
44
45 procedure Mount
46 (State : in out T;
47 Part_Len : in Partition_Length;
48 Success : out Boolean)
49 is
50 D_Type : constant Index_Type := 0;
51 D_Id : constant Index_Type := 1;
52 D_Ver : constant Index_Type := 6;
53
54 D_Type_Primary : constant := 1;
55 D_Type_Terminator : constant := 255;
56
57 CD001 : constant Buffer_Type :=
58 (Character'Pos ('C'), Character'Pos ('D'),
59 Character'Pos ('0'), Character'Pos ('0'), Character'Pos ('1'));
60
61 Static : Mount_State renames State.Static;
62
Nico Huber4210fcc2024-01-29 16:33:47 +010063 Volume_Descriptor : Buffer_Type (0 .. D_Ver);
Nico Huber65f2ea22024-02-06 17:37:35 +010064 Block : FSBlock := 16;
Nico Hubercc960f22024-01-29 01:13:45 +010065 begin
66 loop
67 pragma Loop_Invariant (Block < 1024);
Nico Huber4210fcc2024-01-29 16:33:47 +010068 pragma Loop_Invariant (not Is_Mounted (State));
Nico Hubercc960f22024-01-29 01:13:45 +010069
70 if Part_Len < Partition_Length (Block + 1) * FSBlock_Size then
71 Success := False;
72 return;
73 end if;
74
Nico Huber4210fcc2024-01-29 16:33:47 +010075 Read (Volume_Descriptor, Block, 0, Part_Len, Success);
Nico Hubercc960f22024-01-29 01:13:45 +010076 if not Success then
77 return;
78 end if;
79
80 if Volume_Descriptor (D_Ver) /= 1 or
81 Volume_Descriptor (D_Id .. D_Ver - 1) /= CD001 or
82 Volume_Descriptor (D_Type) = D_Type_Terminator
83 then
Nico Huber4210fcc2024-01-29 16:33:47 +010084 Success := False;
Nico Hubercc960f22024-01-29 01:13:45 +010085 return;
86 end if;
87
88 exit when Volume_Descriptor (D_Type) = D_Type_Primary;
89
90 Block := Block + 1;
91 if Block >= 1024 then
Nico Huber4210fcc2024-01-29 16:33:47 +010092 Success := False;
Nico Hubercc960f22024-01-29 01:13:45 +010093 return;
94 end if;
95 end loop;
96
97 Static.Part_Len := Part_Len;
98 Static.Root_Inode := (Block, 156);
99
100 State.S := Mounted;
101 end Mount;
102
103 procedure Open
104 (State : in out T;
105 I : in Inode_Index;
106 Success : out Boolean)
107 with
108 Pre => Is_Mounted (State),
109 Post => Is_Mounted (State) and (Success = Is_Open (State))
110 is
111 Static : Mount_State renames State.Static;
112 Inode : Inode_Info renames State.Inode;
113
114 Dir_Rec : Directory_Record;
115 begin
Nico Huber4210fcc2024-01-29 16:33:47 +0100116 State.S := Mounted;
117
Nico Hubercc960f22024-01-29 01:13:45 +0100118 Inode := (I, others => <>);
119
120 Read (Dir_Rec, I.Block, I.Offset, Static.Part_Len, Success);
121 if not Success then
122 return;
123 end if;
124
125 declare
126 D_Flag_Dir : constant := 16#02#;
127 D_Flag_Cont : constant := 16#80#;
128 D_Flags : constant Unsigned_8 := Dir_Rec (25);
Nico Huber4210fcc2024-01-29 16:33:47 +0100129 D_Extent : constant Unsigned_32 := Read_LE32 (Dir_Rec, 2);
Nico Hubercc960f22024-01-29 01:13:45 +0100130 begin
Nico Huber4210fcc2024-01-29 16:33:47 +0100131 if D_Extent > Unsigned_32 (FSBlock'Last) then
132 Success := False;
133 return;
134 end if;
Nico Hubercc960f22024-01-29 01:13:45 +0100135 if (D_Flags and D_Flag_Cont) /= 0 then
136 Success := False;
137 return;
138 end if;
Nico Huber4210fcc2024-01-29 16:33:47 +0100139
Nico Hubercc960f22024-01-29 01:13:45 +0100140 if (D_Flags and D_Flag_Dir) /= 0 then
141 Inode.Mode := Dir;
142 else
143 Inode.Mode := Regular;
144 end if;
145 Inode.Size := Inode_Length (Read_LE32 (Dir_Rec, 10));
146 Inode.Extents (0) :=
Nico Huber4210fcc2024-01-29 16:33:47 +0100147 (Start => FSBlock (D_Extent),
Nico Hubercc960f22024-01-29 01:13:45 +0100148 Count => FSBlock_Count (Inode.Size / Inode_Length (FSBlock_Size)));
149 State.S := File_Opened;
150 end;
151 end Open;
152
153 procedure Open
154 (State : in out T;
155 File_Len : out File_Length;
156 File_Type : out FS.File_Type;
157 File_Name : in String;
158 In_Root : in Boolean;
159 Success : out Boolean)
160 is
161 File_Name_Max : constant := 255;
162
163 function Str_Buf_Equal (Str : String; Buf : Buffer_Type) return Boolean
164 with
165 Pre => Str'Length <= Buf'Length
166 is
167 begin
168 for I in Str'Range loop
Nico Hubereae183a2024-02-06 17:38:55 +0100169 declare
170 Chr : constant Unsigned_8 :=
171 (if 'a' <= Str (I) and Str (I) <= 'z' then
172 Character'Pos (Str (I)) - Character'Pos ('a') + Character'Pos ('A')
173 else Character'Pos (Str (I)));
174 begin
175 if Chr /= Buf (Buf'First + (I - Str'First)) then
176 return False;
177 end if;
178 end;
Nico Hubercc960f22024-01-29 01:13:45 +0100179 end loop;
180 return True;
181 end Str_Buf_Equal;
182
183 Found_Inode : Inode_Index;
184 Dir_Pos : File_Length;
185 begin
186 File_Len := 0;
187 File_Type := FS.File_Type'First;
188
189 if File_Name'Length > File_Name_Max then
190 Success := False;
191 return;
192 end if;
193
194 -- Ensure dir is opened:
195 --
196 if State.S = File_Opened then
197 if State.Cur_Dir /= State.Inode.I then
198 Success := False;
199 return;
200 end if;
201 else
202 if In_Root then
203 State.Cur_Dir := State.Static.Root_Inode;
204 end if;
205 declare
206 Cur_Dir : constant Inode_Index := State.Cur_Dir;
207 begin
208 Open (State, Cur_Dir, Success);
209 if not Success then
210 return;
211 end if;
212 end;
213 end if;
214
215 -- Lookup file in opened dir:
216 --
217 Dir_Pos := 0;
218 Success := False;
219 loop
220 pragma Loop_Invariant (Is_Open (State) and not Success);
Nico Huber4210fcc2024-01-29 16:33:47 +0100221 pragma Loop_Invariant
222 (FSBlock_Index (Dir_Pos mod FSBlock_Size) <= Directory_Record_Offset'Last);
223
Nico Hubercc960f22024-01-29 01:13:45 +0100224 declare
225 Dir_Rec : Directory_Record;
226 Dir_Rec_Name : Buffer_Type (0 .. File_Name_Max - 1);
227 Record_Dir_Pos : File_Offset := Dir_Pos;
228 Dir_Rec_Length : File_Length;
Nico Hubercc960f22024-01-29 01:13:45 +0100229 Len : Natural;
230 begin
231 Read
232 (State => State,
233 File_Pos => Record_Dir_Pos,
234 Buf => Dir_Rec,
235 Len => Len);
236 if Len < Dir_Rec'Length then
237 return;
238 end if;
239
Nico Huberfa5f8902024-02-06 17:49:42 +0100240 if File_Name'Length <= Natural (Dir_Rec (32)) and
241 Natural (Dir_Rec (32)) <= File_Name'Length + 3
242 then
Nico Hubercc960f22024-01-29 01:13:45 +0100243 pragma Warnings
244 (GNATprove, Off, """Record_Dir_Pos"" is set*but not used",
245 Reason => "We only care about intermedidate values.");
246 Read
247 (State => State,
248 File_Pos => Record_Dir_Pos,
Nico Huberfa5f8902024-02-06 17:49:42 +0100249 Buf => Dir_Rec_Name (0 .. Natural (Dir_Rec (32) - 1)),
Nico Hubercc960f22024-01-29 01:13:45 +0100250 Len => Len);
251 pragma Warnings (GNATprove, On, """Record_Dir_Pos"" is set*but not used");
Nico Hubercc960f22024-01-29 01:13:45 +0100252
Nico Huberfa5f8902024-02-06 17:49:42 +0100253 if (Len = 1 and Dir_Rec_Name (0) = 16#00# and File_Name = ".") or
254 (Len = 1 and Dir_Rec_Name (0) = 16#01# and File_Name = "..")
255 then
256 Success := True;
257 else
258 -- Remove file version
259 if Len >= File_Name'Length + 2 and
260 Dir_Rec_Name (Len - 2) = Character'Pos (';') and
261 Dir_Rec_Name (Len - 1) = Character'Pos ('1')
262 then
263 Len := Len - 2;
264 end if;
265
266 -- Remove trailing .
267 if Len >= File_Name'Length + 1 and
268 Dir_Rec_Name (Len - 1) = Character'Pos ('.')
269 then
270 Len := Len - 1;
271 end if;
272
273 Success := Len = File_Name'Length and then
274 Str_Buf_Equal (File_Name, Dir_Rec_Name);
275 end if;
Nico Hubercc960f22024-01-29 01:13:45 +0100276 if Success then
277 Found_Inode :=
Nico Huberfa5f8902024-02-06 17:49:42 +0100278 (Block => FSBlock (Dir_Pos / FSBlock_Size) + State.Inode.Extents (0).Start,
Nico Hubercc960f22024-01-29 01:13:45 +0100279 Offset => FSBlock_Index (Dir_Pos mod FSBlock_Size));
280 exit;
281 end if;
282 end if;
283
284 Dir_Rec_Length := File_Length (Dir_Rec (0));
Nico Huber4210fcc2024-01-29 16:33:47 +0100285 if Dir_Rec_Length = 0 or else
286 Dir_Pos > File_Length'Last - Dir_Rec_Length or else
287 (Dir_Pos + Dir_Rec_Length) mod FSBlock_Size
288 > File_Length (Directory_Record_Offset'Last) or else
Nico Hubercc960f22024-01-29 01:13:45 +0100289 Unsigned_64 (Dir_Pos) >= Unsigned_64 (State.Inode.Size) - Unsigned_64 (Dir_Rec_Length)
290 then
291 return;
292 end if;
293 Dir_Pos := Dir_Pos + Dir_Rec_Length;
294 end;
295 end loop;
296 pragma Assert_And_Cut (Success and Is_Mounted (State));
297
298 Open (State, Found_Inode, Success);
299 if not Success then
300 return;
301 end if;
302
303 if State.Inode.Mode = Dir then
304 State.Cur_Dir := Found_Inode;
305 end if;
306
Nico Huber4210fcc2024-01-29 16:33:47 +0100307 Success := State.Inode.Size <= Inode_Length (File_Length'Last);
Nico Hubercc960f22024-01-29 01:13:45 +0100308 if Success then
309 File_Len := File_Length (State.Inode.Size);
310 File_Type := State.Inode.Mode;
311 else
312 Close (State);
313 end if;
314 end Open;
315
316 procedure Close (State : in out T) is
317 begin
318 State.S := Mounted;
319 end Close;
320
321 procedure Read
322 (State : in out T;
323 File_Pos : in out File_Offset;
324 Buf : out Buffer_Type;
325 Len : out Natural)
326 is
327 Static : Mount_State renames State.Static;
328
329 Pos : Natural range Buf'First .. Buf'Last + 1;
330 begin
331 Len := 0;
332 Pos := Buf'First;
333 while Pos <= Buf'Last and
334 File_Pos < File_Offset'Last and
335 Inode_Length (File_Pos) < State.Inode.Size
336 loop
Nico Huber4210fcc2024-01-29 16:33:47 +0100337 pragma Loop_Invariant (for all I in Buf'First .. Pos - 1 => Buf (I)'Initialized);
Nico Hubercc960f22024-01-29 01:13:45 +0100338 pragma Loop_Invariant (Is_Open (State));
339 declare
340 In_Block : constant FSBlock_Index := Natural (File_Pos mod FSBlock_Size);
341 Logical : constant FSBlock_Logical := FSBlock_Logical (File_Pos / FSBlock_Size);
342 In_Block_Space : constant Positive := Index_Type (FSBlock_Size) - In_Block;
343 In_File_Space : constant Inode_Length := State.Inode.Size - Inode_Length (File_Pos);
344 In_Buf_Space : constant Positive := Buf'Last - Pos + 1;
345 Len_Here : Positive;
346 begin
347 exit when FSBlock (Logical) > FSBlock'Last - State.Inode.Extents (0).Start;
348
349 Len_Here := In_Block_Space;
350 if In_File_Space < Inode_Length (Len_Here) then
351 Len_Here := Positive (In_File_Space);
352 end if;
353 if In_Buf_Space < Len_Here then
354 Len_Here := In_Buf_Space;
355 end if;
356 if File_Offset'Last - File_Pos < File_Length (Len_Here) then
357 Len_Here := Positive (File_Offset'Last - File_Pos);
358 end if;
359
360 declare
361 Last : constant Index_Type := Pos + Len_Here - 1;
362 Physical : constant FSBlock := State.Inode.Extents (0).Start + FSBlock (Logical);
363 Success : Boolean;
364 begin
365 Read
366 (Buf => Buf (Pos .. Last),
367 Block => Physical,
368 Offset => In_Block,
369 FS_Len => Static.Part_Len,
370 Success => Success);
371 exit when not Success;
372
373 File_Pos := File_Pos + File_Length (Len_Here);
374 Pos := Pos + Len_Here;
375 Len := Pos - Buf'First;
376 end;
377 end;
378 end loop;
379 Buf (Pos .. Buf'Last) := (others => 16#00#);
380 end Read;
381
382 --------------------------------------------------------------------------
383
384 package C is new VFS (T => T, Initial => (S => Unmounted, others => <>));
385
386 function C_Mount return int
387 with
388 Export,
389 Convention => C,
390 External_Name => "iso9660_mount";
391 function C_Mount return int
392 with
393 SPARK_Mode => Off
394 is
395 begin
396 return C.C_Mount;
397 end C_Mount;
398
399 function C_Open (File_Path : System.Address) return int
400 with
401 Export,
402 Convention => C,
403 External_Name => "iso9660_dir";
404 function C_Open (File_Path : System.Address) return int
405 with
406 SPARK_Mode => Off
407 is
408 begin
409 return C.C_Open (File_Path);
410 end C_Open;
411
412 function C_Read (Buf : System.Address; Len : int) return int
413 with
414 Export,
415 Convention => C,
416 External_Name => "iso9660_read";
417 function C_Read (Buf : System.Address; Len : int) return int
418 with
419 SPARK_Mode => Off
420 is
421 begin
422 return C.C_Read (Buf, Len);
423 end C_Read;
424
425end FILO.FS.ISO9660;