Skip to content

Crash when pattern-matching lazy values modifies the scrutinee #5992

@vicuna

Description

@vicuna

Original bug ID: 5992
Reporter: @yallop
Assigned to: @maranget
Status: closed (set by @xavierleroy on 2015-12-11T18:18:47Z)
Resolution: fixed
Priority: normal
Severity: major
Category: back end (clambda to assembly)
Related to: #7241
Monitored by: @gasche

Bug description

$ cat lazypatterns.ml 
type ('a, 'b) eq = Refl : ('a, 'a) eq

let cast (type a) (type b) (Refl : (a, b) eq) (x : a) = (x : b)

type ('a, 'b) either = L of 'a | R of 'b

type e = ((bool, bool) eq, (int, string) eq) either

let f : unit Lazy.t * unit Lazy.t * bool ref * e -> string = function
  | lazy (), _, {contents=false}, L x  -> "ok"
  | _, lazy (), {contents=true}, L x -> "ok"
  | _, _, _, R refl -> cast refl 0 ^ "not ok"

let s = ref false
let set_true = lazy (s := true)
let set_false = lazy (s := false)

let _ = f (set_true, set_false, s, L Refl)
$ ocaml lazypatterns.ml 
Segmentation fault (core dumped)

File attachments

Metadata

Metadata

Assignees

Type

No type

Projects

No projects

Milestone

No milestone

Relationships

None yet

Development

No branches or pull requests

Issue actions