]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml_toys/libext2/lib/src/ext2.ml
Update
[l4.git] / l4 / pkg / ocaml / ocaml_toys / libext2 / lib / src / ext2.ml
1 open Printf
2
3 external get_dev_block_size : unit -> int = "get_dev_block_size"
4
5 external read_block_ext : string -> int -> bool = "read_block_ext"
6
7 let dev_block_size = get_dev_block_size ()
8
9 exception Overflow of string
10
11 type inode_rec = {
12         id              : int; (* debug : number of this very inode *)
13         mode    : int;
14         uid             : int;
15         size    : int;
16         atime   : int32;
17         ctime   : int32;
18         mtime   : int32;
19         dtime   : int32;
20         gid             : int;
21         links   : int;
22         blocks  : int;
23         flags   : int;
24         block   : int array;
25 }
26
27 type sb_rec = {
28         inode_count                     : int;
29         block_count                     : int;
30         group_count                     : int;
31         blocks_per_group        : int;
32         inodes_per_group        : int;
33         inode_size                      : int;
34         block_size                      : int;
35         group_desc_size         : int;
36         backup_list                     : int list;
37 }
38
39 type read_dir_rec = {
40         dir_inode       : inode_rec;
41         block_off       : int;
42         byte_off        : int;
43         length          : int;
44         name            : string;
45         f_mode          : int;
46         inode           : int;
47 }
48
49 (* superblock *)
50 let sb = ref {inode_count=0; block_count=0; group_count=0; blocks_per_group=0; inodes_per_group=0; inode_size=0; block_size=1024; group_desc_size=32; backup_list=[]}
51
52 (* root inode *)
53 let ri = ref {id=0; mode=0; uid=0; size=0; atime=Int32.zero; ctime=Int32.zero; mtime=Int32.zero; dtime=Int32.zero; gid=0; links=0; blocks=0; flags=0; block=[||]}
54
55 let read_block s n =
56         let r = read_block_ext s n in
57         if (not r) then printf "read_block failed\n" else ()
58
59 (* byte accessors *)
60
61 let read_byte s i = int_of_char s.[i]
62
63 let read1 s i = read_byte s i
64
65 let read2 s i =
66     let ch1 = read_byte s i in
67     let ch2 = read_byte s (i+1) in
68     ch1 lor (ch2 lsl 8)
69
70 let read4 s i =
71     let ch1 = read_byte s i in
72     let ch2 = read_byte s (i+1) in
73     let ch3 = read_byte s (i+2) in
74     let ch4 = read_byte s (i+3) in
75 (*      printf "read4 %x %x %x %x\n" ch1 ch2 ch3 ch4;*)
76     if ch4 land 128 <> 0 then begin
77         if ch4 land 64 = 0 then raise (Overflow "read4");
78         ch1 lor (ch2 lsl 8) lor (ch3 lsl 16) lor ((ch4 land 127) lsl 24)
79     end else begin
80         if ch4 land 64 <> 0 then raise (Overflow "read4");
81         ch1 lor (ch2 lsl 8) lor (ch3 lsl 16) lor (ch4 lsl 24)
82     end
83
84 let read4_32 s i =
85     let ch1 = read_byte s i in
86     let ch2 = read_byte s (i+1) in
87     let ch3 = read_byte s (i+2) in
88     let ch4 = read_byte s (i+3) in
89         Int32.logor (Int32.of_int (ch1 lor (ch2 lsl 8) lor (ch3 lsl 16))) (Int32.shift_left (Int32.of_int ch4) 24)
90
91 let div_up a b = (a + b - 1) / b
92
93 let create_backup_list max =
94         let rec exp i j max l = if i > max then l else exp (i*j) j max (i::l) in
95         let f i = exp i i max [] in
96         let (l1,l2,l3) = (f 3,f 5,f 7) in
97         0::1::(List.rev_append (List.rev_append l1 l2) l3)
98
99 (* param i must be a valid inode index *)
100 let read_inode_from_block b i =
101         let r2 j = read2 b (i + j) in
102         let r4 j = read4 b (i + j) in
103         let rx j = read4_32 b (i + j) in
104         let a = Array.make 15 0 in
105         let rec ra i = if i < 15 then begin a.(i) <- r4 (40 + i * 4); ra (i+1); end else a in
106         let i = {
107                 id              = i;
108                 mode    = r2 0;
109                 uid             = r2 2;
110                 size    = r4 4;
111                 atime   = rx 8;
112                 ctime   = rx 12;
113                 mtime   = rx 16;
114                 dtime   = rx 20;
115                 gid             = r2 24;
116                 links   = r2 26;
117                 blocks  = r4 28;
118                 flags   = r4 32;
119                 block   = ra 0;
120         } in i
121
122 let read_inode inode =
123         assert (inode > 0);
124         let inode = inode - 1 in
125         let group = (inode / !sb.inodes_per_group) in
126         let block = 2 + group * !sb.blocks_per_group in
127         let block = if not (List.mem group !sb.backup_list)
128                 then block
129                 else block + div_up (!sb.group_count * !sb.group_desc_size) !sb.block_size in
130         let data = String.create !sb.block_size in
131         read_block data block;  (* read inode bitmap *)
132         assert (0 != ((read1 data (inode lsr 3)) land (1 lsl (inode land 7))));
133         read_block data (1 + block + inode * !sb.inode_size / !sb.block_size);
134         read_inode_from_block data (inode mod !sb.inodes_per_group * !sb.inode_size)
135
136 let read_superblock () =
137         let data = String.create dev_block_size in
138         let offset = match dev_block_size with
139         | 1024 -> read_block data 1; 0
140         | 2048 -> read_block data 0; 1024
141         | 4096 -> read_block data 0; 1024
142         | _ -> assert false
143         in
144
145         let r2 i = read2 data (offset+i) in
146         let r4 i = read4 data (offset+i) in
147
148         assert ((r2 56) = 0xEF53);      (* magic *)
149         assert ((r2 58) = 1);           (* state *)
150         assert (0 = ((r4 92) lor (r4 96) lor (r4 100)));        (* no fancy features *)
151
152         let b = {
153                 inode_count                     = r4 0;
154                 block_count                     = r4 4;
155                 group_count                     = 0;
156                 blocks_per_group        = r4 32;
157                 inodes_per_group        = r4 40;
158                 inode_size                      = r2 88;
159                 block_size                      = 1024 * (1 lsl r4 24);
160                 group_desc_size         = 32;   (* hard coded, sizeof (struct ext2_group_desc) *)
161                 backup_list                     = [];
162         } in sb := {
163                 b with
164                 backup_list = create_backup_list b.block_count;
165                 group_count = div_up b.block_count b.blocks_per_group
166         };
167
168         ri := read_inode 2      (* read root inode *)
169
170 (* inode number or 0 if invalid *)
171 let block_rel_to_abs inode block =
172         let data = String.create !sb.block_size in
173
174         let rec f addr block level =
175                 if block = 0 then 0 else begin
176                         read_block data block;
177                         let block = read4 data (addr lsr level land 0x3ff * 4) in
178                         if level = 0 then block else f addr block (level-10)
179                 end
180         in
181
182         let l = [|12; 12+1024; 12+1024+1024*1024|] in
183         if block < l.(0) then inode.block.(block) else
184         if block < l.(1) then f (block-l.(0)) inode.block.(12) 0 else
185         if block < l.(2) then f (block-l.(1)) inode.block.(13) 10 else
186                                                   f (block-l.(2)) inode.block.(14) 20
187
188 (* returns index or -1 *)
189 let inode_iter inode buffer func =
190         let last_block = (inode.size - 1) / !sb.block_size in
191
192         let rec f index block_number =
193                 if func buffer index then index else
194                 let rec_len = read2 buffer (index+4) in
195                 if rec_len + index < !sb.block_size
196                 then f (index+rec_len) block_number
197                 else if block_number = last_block then 0
198                 else let i = block_rel_to_abs inode (block_number+1) in
199                 if i = 0 then failwith "inode_iter: block_rel_to_abs returned None" (* this means an error in the metadata on disk *)
200                 else read_block buffer i; f 0 (block_number+1)
201
202         in let i = block_rel_to_abs inode 0 in
203         if i = 0 then -1 else (read_block buffer i; f 0 0)
204
205 let next_name s i =
206         let (j,k) = if String.contains_from s i '/'
207         then let j = String.index_from s i '/' in (j-i,j+1)
208         else (String.length s - i,-1)
209         in (String.sub s i j, k)
210
211 (* 0 or valid inode number *)
212 let path_to_inode path =
213         assert (path.[0] = '/');
214         let buffer = String.create !sb.block_size in
215
216         let search name buffer index =
217                 let name_len = read1 buffer (index+6) in
218                 let sub = String.sub buffer (index+8) name_len in
219                 String.compare name sub = 0
220
221         (* returns the inode number of the searched string or 0 if not found *)
222         in let scan_name name inode =
223                 let index = inode_iter inode buffer (search name) in
224                 if index = 0 then 0 else read4 buffer index
225
226         in let rec f i inode =
227                 let (s, i) = next_name path i in
228                 let j = scan_name s inode in
229                 if (i = -1 || j = 0) then j else f i (read_inode j)
230
231         in
232                 assert (String.length path > 0);
233                 assert (path.[0] = '/');
234                 if String.length path = 1 then 2 (* root inode is hard coded number 2 *) else
235                 f 1 !ri
236
237 let opendir path =
238         let inode_num = path_to_inode path in
239         if inode_num = 0 then None else begin
240                 let dir_inode = read_inode inode_num in
241                 let buffer = String.create !sb.block_size in
242                 read_block buffer (block_rel_to_abs dir_inode 0);
243                 let inode = read4 buffer 0 in
244                 let length = read2 buffer 4 in
245                 let file_inode = read_inode inode in
246                 let name = String.sub buffer 8 (read2 buffer 6) in
247                 Some { dir_inode = dir_inode; block_off = 0; byte_off = 0; length = length; name = name; f_mode = file_inode.mode; inode = inode; }
248         end
249
250 let readdir r =
251         let buffer = String.create !sb.block_size in
252         let byte_off = r.byte_off + r.length in
253
254         if (byte_off == !sb.block_size) && (r.dir_inode.size = !sb.block_size) then None else begin
255                 let (block_off,byte_off,length) =
256                         if r.byte_off == !sb.block_size
257                         then (r.block_off + 1,0,r.length - !sb.block_size) 
258                         else (r.block_off,byte_off,r.length) in
259                 read_block buffer (block_rel_to_abs r.dir_inode block_off);
260                 let inode = read4 buffer byte_off in
261                 let length = read2 buffer (byte_off + 4) in
262                 let file_inode = read_inode inode in
263                 let name = String.sub buffer (byte_off + 8) (read2 buffer (byte_off + 6)) in
264                 Some { dir_inode = r.dir_inode; block_off = block_off; byte_off = byte_off; length = length; name = name; f_mode = file_inode.mode; inode = inode; }
265         end
266
267 let read_file_block inode block buffer =
268         let inode = read_inode inode in
269         let block = block_rel_to_abs inode block in
270         read_block_ext buffer block
271
272 let () =
273         read_superblock ();
274
275         Callback.register "path_to_inode" path_to_inode;
276         Callback.register "read_file_block" read_file_block;
277         Callback.register "opendir" opendir;
278         Callback.register "readdir" readdir;