Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
7 changes: 1 addition & 6 deletions src/model/names.ml
Original file line number Diff line number Diff line change
Expand Up @@ -68,12 +68,7 @@ module Name : Name = struct

let equal (x : t) (y : t) = x = y

let compare x y =
match (x, y) with
| Internal (x, _), Internal (y, _) -> String.compare x y
Copy link
Collaborator Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Eliding this field was probably the reason of all this but I think this is not right because we use this function for data-structures, where this would be hazardous, and never intentionally for checking that two Internal have the same name.
Also, equal above uses ( = ).

| Std x, Std y -> String.compare x y
| Internal _, Std _ -> -1
| Std _, Internal _ -> 1
let compare = compare

let fmt ppf x = Format.fprintf ppf "%s" (to_string x)

Expand Down
171 changes: 32 additions & 139 deletions src/model/paths.ml
Original file line number Diff line number Diff line change
Expand Up @@ -72,118 +72,11 @@ module Identifier = struct

let label_parent n = label_parent_aux (n :> t)

let rec hash (id : t) =
let open Paths_types.Identifier in
match id with
| `Root (r, s) -> Hashtbl.hash (1, hash (r : container_page :> any), s)
| `RootPage s -> Hashtbl.hash (2, s)
| `Page (r, s) -> Hashtbl.hash (0, hash (r : container_page :> any), s)
| `LeafPage (r, s) -> Hashtbl.hash (20, hash (r : container_page :> any), s)
| `Module (id, s) -> Hashtbl.hash (3, hash (id : signature :> any), s)
| `Parameter (id, s) -> Hashtbl.hash (4, hash (id : signature :> any), s)
| `Result s -> Hashtbl.hash (5, hash (s : signature :> any))
| `ModuleType (id, s) -> Hashtbl.hash (6, hash (id : signature :> any), s)
| `Type (id, s) -> Hashtbl.hash (7, hash (id : signature :> any), s)
| `CoreType s -> Hashtbl.hash (8, s)
| `Constructor (id, s) -> Hashtbl.hash (9, hash (id : type_ :> any), s)
| `Field (id, s) -> Hashtbl.hash (10, hash (id : parent :> any), s)
| `Extension (id, s) -> Hashtbl.hash (11, hash (id : signature :> any), s)
| `Exception (id, s) -> Hashtbl.hash (12, hash (id : signature :> any), s)
| `CoreException s -> Hashtbl.hash (13, s)
| `Value (id, s) -> Hashtbl.hash (14, hash (id : signature :> any), s)
| `Class (id, s) -> Hashtbl.hash (15, hash (id : signature :> any), s)
| `ClassType (id, s) -> Hashtbl.hash (16, hash (id : signature :> any), s)
| `Method (id, s) -> Hashtbl.hash (17, hash (id : class_signature :> any), s)
| `InstanceVariable (id, s) ->
Hashtbl.hash (18, hash (id : class_signature :> any), s)
| `Label (id, s) -> Hashtbl.hash (19, hash (id : label_parent :> any), s)

let constructor_id : t -> int = function
| `Root _ -> 1
| `RootPage _ -> 2
| `Module _ -> 3
| `Parameter _ -> 4
| `Result _ -> 5
| `ModuleType _ -> 6
| `Type _ -> 7
| `CoreType _ -> 8
| `Constructor _ -> 9
| `Field _ -> 10
| `Extension _ -> 11
| `Exception _ -> 12
| `CoreException _ -> 13
| `Value _ -> 14
| `Class _ -> 15
| `ClassType _ -> 16
| `Method _ -> 17
| `InstanceVariable _ -> 18
| `Label _ -> 19
| `Page _ -> 20
| `LeafPage _ -> 21

let std_compare = compare

let rec compare : t -> t -> int =
fun x y ->
match (x, y) with
| `Root (r, s), `Root (r', s') ->
let s = ModuleName.compare s s' in
if s <> 0 then s else compare (r :> t) (r' :> t)
| `RootPage s, `RootPage s' -> PageName.compare s s'
| `Page (r, s), `Page (r', s') ->
let s = PageName.compare s s' in
if s <> 0 then s else compare (r :> t) (r' :> t)
| `LeafPage (r, s), `LeafPage (r', s') ->
let s = PageName.compare s s' in
if s <> 0 then s else compare (r :> t) (r' :> t)
| `Module (p, s), `Module (p', s') ->
let s = ModuleName.compare s s' in
if s <> 0 then s else compare (p :> t) (p' :> t)
| `Parameter (p, s), `Parameter (p', s') ->
let s = ParameterName.compare s s' in
if s <> 0 then s else compare (p :> t) (p' :> t)
| `Result p, `Result p' -> compare (p :> t) (p' :> t)
| `ModuleType (p, s), `ModuleType (p', s') ->
let s = ModuleTypeName.compare s s' in
if s <> 0 then s else compare (p :> t) (p' :> t)
| `Type (p, s), `Type (p', s') ->
let s = TypeName.compare s s' in
if s <> 0 then s else compare (p :> t) (p' :> t)
| `CoreType s, `CoreType s' -> TypeName.compare s s'
| `Constructor (p, s), `Constructor (p', s') ->
let s = ConstructorName.compare s s' in
if s <> 0 then s else compare (p :> t) (p' :> t)
| `Field (p, s), `Field (p', s') ->
let s = FieldName.compare s s' in
if s <> 0 then s else compare (p :> t) (p' :> t)
| `Extension (p, s), `Extension (p', s') ->
let s = ExtensionName.compare s s' in
if s <> 0 then s else compare (p :> t) (p' :> t)
| `Exception (p, s), `Exception (p', s') ->
let s = ExceptionName.compare s s' in
if s <> 0 then s else compare (p :> t) (p' :> t)
| `CoreException s, `CoreException s' -> ExceptionName.compare s s'
| `Value (p, s), `Value (p', s') ->
let s = ValueName.compare s s' in
if s <> 0 then s else compare (p :> t) (p' :> t)
| `Class (p, s), `Class (p', s') ->
let s = ClassName.compare s s' in
if s <> 0 then s else compare (p :> t) (p' :> t)
| `ClassType (p, s), `ClassType (p', s') ->
let s = ClassTypeName.compare s s' in
if s <> 0 then s else compare (p :> t) (p' :> t)
| `Method (p, s), `Method (p', s') ->
let s = MethodName.compare s s' in
if s <> 0 then s else compare (p :> t) (p' :> t)
| `InstanceVariable (p, s), `InstanceVariable (p', s') ->
let s = InstanceVariableName.compare s s' in
if s <> 0 then s else compare (p :> t) (p' :> t)
| `Label (p, s), `Label (p', s') ->
let s = LabelName.compare s s' in
if s <> 0 then s else compare (p :> t) (p' :> t)
| x, y -> std_compare (constructor_id x) (constructor_id y)

let equal : t -> t -> bool = fun x y -> compare x y = 0
let equal = ( = )

let hash = Hashtbl.hash

let compare = compare

type any = t

Expand All @@ -192,7 +85,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -202,7 +95,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -212,7 +105,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -222,7 +115,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -232,7 +125,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -242,7 +135,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -252,7 +145,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -262,7 +155,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -282,7 +175,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -292,7 +185,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -302,7 +195,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -312,7 +205,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -322,7 +215,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -332,7 +225,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -342,7 +235,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -352,7 +245,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -362,7 +255,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -372,7 +265,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -382,7 +275,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -392,7 +285,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -402,7 +295,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -412,7 +305,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -422,7 +315,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -433,7 +326,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -443,7 +336,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -453,7 +346,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand All @@ -463,7 +356,7 @@ module Identifier = struct

let equal x y = equal (x :> any) (y :> any)

let hash x = hash (x :> any)
let hash = Hashtbl.hash

let compare x y = compare (x :> any) (y :> any)
end
Expand Down
Loading