blob: 03f1abb59df0100b33f10575611d710ba2950fa7 [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 Hubercc960f22024-01-29 01:13:45 +010064 Block : FSBlock := 32;
65 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
169 if Character'Pos (Str (I)) /= Buf (Buf'First + (I - Str'First)) then
170 return False;
171 end if;
172 end loop;
173 return True;
174 end Str_Buf_Equal;
175
176 Found_Inode : Inode_Index;
177 Dir_Pos : File_Length;
178 begin
179 File_Len := 0;
180 File_Type := FS.File_Type'First;
181
182 if File_Name'Length > File_Name_Max then
183 Success := False;
184 return;
185 end if;
186
187 -- Ensure dir is opened:
188 --
189 if State.S = File_Opened then
190 if State.Cur_Dir /= State.Inode.I then
191 Success := False;
192 return;
193 end if;
194 else
195 if In_Root then
196 State.Cur_Dir := State.Static.Root_Inode;
197 end if;
198 declare
199 Cur_Dir : constant Inode_Index := State.Cur_Dir;
200 begin
201 Open (State, Cur_Dir, Success);
202 if not Success then
203 return;
204 end if;
205 end;
206 end if;
207
208 -- Lookup file in opened dir:
209 --
210 Dir_Pos := 0;
211 Success := False;
212 loop
213 pragma Loop_Invariant (Is_Open (State) and not Success);
Nico Huber4210fcc2024-01-29 16:33:47 +0100214 pragma Loop_Invariant
215 (FSBlock_Index (Dir_Pos mod FSBlock_Size) <= Directory_Record_Offset'Last);
216
Nico Hubercc960f22024-01-29 01:13:45 +0100217 declare
218 Dir_Rec : Directory_Record;
219 Dir_Rec_Name : Buffer_Type (0 .. File_Name_Max - 1);
220 Record_Dir_Pos : File_Offset := Dir_Pos;
221 Dir_Rec_Length : File_Length;
222 Inode : Inode_Index;
223 Len : Natural;
224 begin
225 Read
226 (State => State,
227 File_Pos => Record_Dir_Pos,
228 Buf => Dir_Rec,
229 Len => Len);
230 if Len < Dir_Rec'Length then
231 return;
232 end if;
233
234 -- FIXME: need to strip trailing . and file version
235 if File_Name'Length = Natural (Dir_Rec (32)) then
236 pragma Warnings
237 (GNATprove, Off, """Record_Dir_Pos"" is set*but not used",
238 Reason => "We only care about intermedidate values.");
239 Read
240 (State => State,
241 File_Pos => Record_Dir_Pos,
242 Buf => Dir_Rec_Name,
243 Len => Len);
244 pragma Warnings (GNATprove, On, """Record_Dir_Pos"" is set*but not used");
245 if Len < File_Name'Length then
246 return;
247 end if;
248
249 Success := Str_Buf_Equal (File_Name, Dir_Rec_Name);
250 if Success then
251 Found_Inode :=
252 (Block => FSBlock (Dir_Pos / FSBlock_Size),
253 Offset => FSBlock_Index (Dir_Pos mod FSBlock_Size));
254 exit;
255 end if;
256 end if;
257
258 Dir_Rec_Length := File_Length (Dir_Rec (0));
Nico Huber4210fcc2024-01-29 16:33:47 +0100259 if Dir_Rec_Length = 0 or else
260 Dir_Pos > File_Length'Last - Dir_Rec_Length or else
261 (Dir_Pos + Dir_Rec_Length) mod FSBlock_Size
262 > File_Length (Directory_Record_Offset'Last) or else
Nico Hubercc960f22024-01-29 01:13:45 +0100263 Unsigned_64 (Dir_Pos) >= Unsigned_64 (State.Inode.Size) - Unsigned_64 (Dir_Rec_Length)
264 then
265 return;
266 end if;
267 Dir_Pos := Dir_Pos + Dir_Rec_Length;
268 end;
269 end loop;
270 pragma Assert_And_Cut (Success and Is_Mounted (State));
271
272 Open (State, Found_Inode, Success);
273 if not Success then
274 return;
275 end if;
276
277 if State.Inode.Mode = Dir then
278 State.Cur_Dir := Found_Inode;
279 end if;
280
Nico Huber4210fcc2024-01-29 16:33:47 +0100281 Success := State.Inode.Size <= Inode_Length (File_Length'Last);
Nico Hubercc960f22024-01-29 01:13:45 +0100282 if Success then
283 File_Len := File_Length (State.Inode.Size);
284 File_Type := State.Inode.Mode;
285 else
286 Close (State);
287 end if;
288 end Open;
289
290 procedure Close (State : in out T) is
291 begin
292 State.S := Mounted;
293 end Close;
294
295 procedure Read
296 (State : in out T;
297 File_Pos : in out File_Offset;
298 Buf : out Buffer_Type;
299 Len : out Natural)
300 is
301 Static : Mount_State renames State.Static;
302
303 Pos : Natural range Buf'First .. Buf'Last + 1;
304 begin
305 Len := 0;
306 Pos := Buf'First;
307 while Pos <= Buf'Last and
308 File_Pos < File_Offset'Last and
309 Inode_Length (File_Pos) < State.Inode.Size
310 loop
Nico Huber4210fcc2024-01-29 16:33:47 +0100311 pragma Loop_Invariant (for all I in Buf'First .. Pos - 1 => Buf (I)'Initialized);
Nico Hubercc960f22024-01-29 01:13:45 +0100312 pragma Loop_Invariant (Is_Open (State));
313 declare
314 In_Block : constant FSBlock_Index := Natural (File_Pos mod FSBlock_Size);
315 Logical : constant FSBlock_Logical := FSBlock_Logical (File_Pos / FSBlock_Size);
316 In_Block_Space : constant Positive := Index_Type (FSBlock_Size) - In_Block;
317 In_File_Space : constant Inode_Length := State.Inode.Size - Inode_Length (File_Pos);
318 In_Buf_Space : constant Positive := Buf'Last - Pos + 1;
319 Len_Here : Positive;
320 begin
321 exit when FSBlock (Logical) > FSBlock'Last - State.Inode.Extents (0).Start;
322
323 Len_Here := In_Block_Space;
324 if In_File_Space < Inode_Length (Len_Here) then
325 Len_Here := Positive (In_File_Space);
326 end if;
327 if In_Buf_Space < Len_Here then
328 Len_Here := In_Buf_Space;
329 end if;
330 if File_Offset'Last - File_Pos < File_Length (Len_Here) then
331 Len_Here := Positive (File_Offset'Last - File_Pos);
332 end if;
333
334 declare
335 Last : constant Index_Type := Pos + Len_Here - 1;
336 Physical : constant FSBlock := State.Inode.Extents (0).Start + FSBlock (Logical);
337 Success : Boolean;
338 begin
339 Read
340 (Buf => Buf (Pos .. Last),
341 Block => Physical,
342 Offset => In_Block,
343 FS_Len => Static.Part_Len,
344 Success => Success);
345 exit when not Success;
346
347 File_Pos := File_Pos + File_Length (Len_Here);
348 Pos := Pos + Len_Here;
349 Len := Pos - Buf'First;
350 end;
351 end;
352 end loop;
353 Buf (Pos .. Buf'Last) := (others => 16#00#);
354 end Read;
355
356 --------------------------------------------------------------------------
357
358 package C is new VFS (T => T, Initial => (S => Unmounted, others => <>));
359
360 function C_Mount return int
361 with
362 Export,
363 Convention => C,
364 External_Name => "iso9660_mount";
365 function C_Mount return int
366 with
367 SPARK_Mode => Off
368 is
369 begin
370 return C.C_Mount;
371 end C_Mount;
372
373 function C_Open (File_Path : System.Address) return int
374 with
375 Export,
376 Convention => C,
377 External_Name => "iso9660_dir";
378 function C_Open (File_Path : System.Address) return int
379 with
380 SPARK_Mode => Off
381 is
382 begin
383 return C.C_Open (File_Path);
384 end C_Open;
385
386 function C_Read (Buf : System.Address; Len : int) return int
387 with
388 Export,
389 Convention => C,
390 External_Name => "iso9660_read";
391 function C_Read (Buf : System.Address; Len : int) return int
392 with
393 SPARK_Mode => Off
394 is
395 begin
396 return C.C_Read (Buf, Len);
397 end C_Read;
398
399end FILO.FS.ISO9660;