Skip to content

Commit

Permalink
Rename EffectHandlers module to Effect (#10879)
Browse files Browse the repository at this point in the history
  • Loading branch information
avsm authored Jan 12, 2022
1 parent 2526e22 commit f3f6ee0
Show file tree
Hide file tree
Showing 36 changed files with 66 additions and 66 deletions.
4 changes: 2 additions & 2 deletions manual/src/library/stdlib-blurb.etex
Original file line number Diff line number Diff line change
Expand Up @@ -109,7 +109,7 @@ be called from C \\
"Mutex" & p.~\stdpageref{Mutex} & mutual exclusion locks \\
"Condition" & p.~\stdpageref{Condition} & condition variables \\
"Semaphore" & p.~\stdpageref{Semaphore} & semaphores \\
"EffectHandlers" & p.~\stdpageref{EffectHandlers} & deep and shallow effect handlers \\
"Effect" & p.~\stdpageref{Effect} & deep and shallow effect handlers \\
\end{tabular}
\subsubsection*{sss:stdlib-misc}{Misc:}
\begin{tabular}{lll}
Expand All @@ -133,7 +133,7 @@ be called from C \\
\stddocitem{Condition}{condition variables to synchronize between threads}
\stddocitem{Domain}{Domain spawn/join and domain local variables}
\stddocitem{Digest}{MD5 message digest}
\stddocitem{EffectHandlers}{deep and shallow effect handlers}
\stddocitem{Effect}{deep and shallow effect handlers}
\stddocitem{Either}{either values}
\stddocitem{Ephemeron}{Ephemerons and weak hash table}
\stddocitem{Filename}{operations on file names}
Expand Down
10 changes: 5 additions & 5 deletions stdlib/.depend
Original file line number Diff line number Diff line change
Expand Up @@ -229,15 +229,15 @@ stdlib__Domain.cmx : domain.ml \
stdlib__Array.cmx \
stdlib__Domain.cmi
stdlib__Domain.cmi : domain.mli
stdlib__EffectHandlers.cmo : effectHandlers.ml \
stdlib__Effect.cmo : effect.ml \
stdlib__Printexc.cmi \
stdlib__Obj.cmi \
stdlib__EffectHandlers.cmi
stdlib__EffectHandlers.cmx : effectHandlers.ml \
stdlib__Effect.cmi
stdlib__Effect.cmx : effect.ml \
stdlib__Printexc.cmx \
stdlib__Obj.cmx \
stdlib__EffectHandlers.cmi
stdlib__EffectHandlers.cmi : effectHandlers.mli \
stdlib__Effect.cmi
stdlib__Effect.cmi : effect.mli \
stdlib__Printexc.cmi
stdlib__Either.cmo : either.ml \
stdlib__Either.cmi
Expand Down
2 changes: 1 addition & 1 deletion stdlib/StdlibModules
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,7 @@ STDLIB_MODULE_BASENAMES = \
printexc fun gc digest random hashtbl weak \
format scanf callback camlinternalOO oo camlinternalMod genlex ephemeron \
filename complex arrayLabels listLabels bytesLabels stringLabels moreLabels \
stdLabels bigarray in_channel out_channel effectHandlers
stdLabels bigarray in_channel out_channel effect

STDLIB_PREFIXED_MODULES = \
$(filter-out stdlib camlinternal%, $(STDLIB_MODULE_BASENAMES))
Expand Down
File renamed without changes.
File renamed without changes.
2 changes: 1 addition & 1 deletion stdlib/stdlib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -585,7 +585,7 @@ module Complex = Complex
module Condition = Condition
module Digest = Digest
module Domain = Domain
module EffectHandlers = EffectHandlers
module Effect = Effect
module Either = Either
module Ephemeron = Ephemeron
module Filename = Filename
Expand Down
2 changes: 1 addition & 1 deletion stdlib/stdlib.mli
Original file line number Diff line number Diff line change
Expand Up @@ -1379,7 +1379,7 @@ module Complex = Complex
module Condition = Condition
module Digest = Digest
module Domain = Domain
module EffectHandlers = EffectHandlers
module Effect = Effect
module Either = Either
module Ephemeron = Ephemeron
module Filename = Filename
Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/backtrace/backtrace_effects.ml
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,8 @@
exit_status = "2"
*)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += E : unit eff

Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/backtrace/backtrace_effects_nested.ml
Original file line number Diff line number Diff line change
Expand Up @@ -2,8 +2,8 @@
flags = "-g"
*)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += E : unit eff
| Inc : unit eff
Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/callback/nested_fiber.ml
Original file line number Diff line number Diff line change
Expand Up @@ -8,8 +8,8 @@

external caml_to_c : (unit -> 'a) -> 'a = "caml_to_c"

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += E : unit eff

Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/callback/stack_overflow.ml
Original file line number Diff line number Diff line change
Expand Up @@ -14,8 +14,8 @@ let rec deep = function
| n ->
caml_to_c (fun () -> deep (n-1))

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += E : unit eff

Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/callback/test7.ml
Original file line number Diff line number Diff line change
Expand Up @@ -10,8 +10,8 @@
* OCaml (c_to_caml) to C (printf functions). Effect E is performed in the
* callback, which does not have a handler. *)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += E : unit eff

Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/effects/backtrace.ml
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,8 @@
ocamlrunparam += ",b=1"
*)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

let rec foo i =
if i = 0 then ()
Expand Down
2 changes: 1 addition & 1 deletion testsuite/tests/effects/backtrace.reference
Original file line number Diff line number Diff line change
Expand Up @@ -2,5 +2,5 @@ Raised at Stdlib.failwith in file "stdlib.ml", line 29, characters 17-33
Called from Backtrace.foo in file "backtrace.ml", line 12, characters 11-27
Called from Backtrace.bar in file "backtrace.ml", line 20, characters 4-9
Called from Backtrace.task1 in file "backtrace.ml", line 29, characters 4-10
Re-raised at Stdlib__EffectHandlers.Deep.discontinue_with_backtrace.(fun) in file "effectHandlers.ml", line 41, characters 4-38
Re-raised at Stdlib__Effect.Deep.discontinue_with_backtrace.(fun) in file "effect.ml", line 41, characters 4-38
Called from Backtrace.task2 in file "backtrace.ml", line 36, characters 4-16
4 changes: 2 additions & 2 deletions testsuite/tests/effects/cmphash.ml
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
(* TEST
*)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += E : unit eff

Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/effects/evenodd.ml
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
(* TEST
*)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += E : unit eff

Expand Down
2 changes: 1 addition & 1 deletion testsuite/tests/effects/issue479.compilers.reference
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ type ('a, 'container) iterator = ('a -> unit) -> 'container -> unit
type 'a generator = unit -> 'a option
type ('a, 'container) iter2gen =
('a, 'container) iterator -> 'container -> 'a generator
type _ Stdlib.EffectHandlers.eff += Hold : unit EffectHandlers.eff
type _ Stdlib.Effect.eff += Hold : unit Effect.eff
val iter2gen : (int, 'a) iter2gen = <fun>
val f : unit -> unit = <fun>
Hold 1
Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/effects/issue479.ml
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,8 @@

(* https://github.com/ocaml-multicore/ocaml-multicore/issues/479 *)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

[@@@warning "-5-26"];;

Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/effects/overflow.ml
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
(* TEST
*)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += E : unit eff

Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/effects/partial.ml
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
(* TEST
*)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += E : unit eff
exception Done
Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/effects/reperform.ml
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
(* TEST
*)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += E : int -> int eff
| F : unit eff
Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/effects/sched.ml
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
(* TEST
*)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

exception E
type _ eff += Yield : unit eff
Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/effects/shallow_state.ml
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
(* TEST
*)

open EffectHandlers
open EffectHandlers.Shallow
open Effect
open Effect.Shallow

(*
let handle_state init f x =
Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/effects/shallow_state_io.ml
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
(* TEST
*)

open EffectHandlers
open EffectHandlers.Shallow
open Effect
open Effect.Shallow

type _ eff += Get : int eff
| Set : int -> unit eff
Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/effects/test1.ml
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
(* TEST
*)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += E : unit eff

Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/effects/test10.ml
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
(* TEST
*)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += Peek : int eff
type _ eff += Poke : unit eff
Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/effects/test11.ml
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,8 @@
(* Tests RESUMETERM with extra_args != 0 in bytecode,
by calling a handler with a tail-continue that returns a function *)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += E : int eff

Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/effects/test2.ml
Original file line number Diff line number Diff line change
Expand Up @@ -2,8 +2,8 @@
*)

open Printf
open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += E : int -> int eff

Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/effects/test3.ml
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
(* TEST
*)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += E : unit eff
exception X
Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/effects/test4.ml
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
(* TEST
*)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += Foo : int -> int eff

Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/effects/test5.ml
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
(* TEST
*)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += Foo : int -> int eff

Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/effects/test6.ml
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
(* TEST
*)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += E : unit eff
| F : unit eff
Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/effects/test_lazy.ml
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
(* TEST *)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += Stop : unit eff

Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/effects/used_cont.ml
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
(* TEST
*)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += E : unit eff

Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/parallel/deadcont.ml
Original file line number Diff line number Diff line change
Expand Up @@ -11,8 +11,8 @@ include unix
https://github.com/ocamllabs/ocaml-multicore/issues/175
*)

open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type _ eff += Poke : unit eff

Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/parallel/mctest.ml
Original file line number Diff line number Diff line change
Expand Up @@ -150,8 +150,8 @@ end

module Scheduler =
struct
open EffectHandlers
open EffectHandlers.Deep
open Effect
open Effect.Deep

type 'a cont = ('a, unit) continuation

Expand Down

0 comments on commit f3f6ee0

Please sign in to comment.