changed syntax of constructors

git-svn-id: http://caml.inria.fr/svn/ocaml/branches/gadts@10883 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Jacques Le Normand 2010-12-03 17:20:18 +00:00
parent 981758ea76
commit b16b083526
2 changed files with 30 additions and 31 deletions

View File

@ -1450,11 +1450,10 @@ constructor_declarations:
| constructor_declarations BAR constructor_declaration { $3 :: $1 }
;
constructor_declaration:
constr_ident constructor_arguments { ($1, $2, None, symbol_rloc()) }
;
| constr_ident generalized_constructor_arguments
{ let arg_types,ret_type = $2 in
($1, arg_types,Some ret_type, symbol_rloc()) }
{ let arg_types,ret_type = $2 in
($1, arg_types,ret_type, symbol_rloc()) }
;
constructor_arguments:
@ -1463,13 +1462,15 @@ constructor_arguments:
;
generalized_constructor_arguments:
| COLON core_type_list MINUSGREATER simple_core_type
{ (List.rev $2, $4) }
/*empty*/ { ([],None) }
| OF core_type_list { (List.rev $2,None) }
| OF core_type_list COLON simple_core_type { (List.rev $2,Some $4) }
| COLON simple_core_type
{ ([],$2) }
{ ([],Some $2) }
;
label_declarations:
label_declaration { [$1] }
| label_declarations SEMI label_declaration { $3 :: $1 }

View File

@ -1,14 +1,12 @@
module Exp =
struct
type _ t =
| IntLit : int -> int t
| BoolLit : bool -> bool t
| Pair : 'a t * 'b t -> ('a * 'b) t
| App : ('a -> 'b) t * 'a t -> 'b t
| Abs : ('a -> 'b) -> ('a -> 'b) t
| IntLit of int : int t
| BoolLit of bool : bool t
| Pair of 'a t * 'b t : ('a * 'b) t
| App of ('a -> 'b) t * 'a t : 'b t
| Abs of ('a -> 'b) : ('a -> 'b) t
let rec eval : type s . s t -> s =
@ -17,7 +15,7 @@ module Exp =
| BoolLit y -> y
| Pair (x,y) -> (eval x,eval y)
| App (f,a) ->
(eval f) (eval a)
(eval f) (eval a)
| Abs f -> f
end
;;
@ -27,7 +25,7 @@ module List =
type zero
type _ t =
| Nil : zero t
| Cons : 'a * 'b t -> ('a * 'b) t
| Cons of 'a * 'b t : ('a * 'b) t
let head =
function
| Cons (a,b) -> a
@ -44,11 +42,11 @@ module List =
module Nonexhaustive =
struct
type 'a u =
| C1 : int -> int u
| C2 : bool -> bool u
| C1 of int : int u
| C2 of bool : bool u
type 'a v =
| C1 : int -> int v
| C1 of int : int v
let unexhaustive : type s . s u -> s =
function
@ -61,8 +59,8 @@ module Nonexhaustive =
type u = bool
end
type 'a t =
| Foo : M.t -> M.t t
| Bar : M.u -> M.u t
| Foo of M.t : M.t t
| Bar of M.u : M.u t
let same_type : type s . s t * s t -> bool =
function
| Foo _ , Foo _ -> true
@ -75,8 +73,8 @@ module Exhaustive =
type t = int
type u = bool
type 'a v =
| Foo : t -> t v
| Bar : u -> u v
| Foo of t : t v
| Bar of u : u v
let same_type : type s . s v * s v -> bool =
function
@ -87,8 +85,8 @@ module Exhaustive =
module Existential_escape =
struct
type _ t = C : int -> int t
type u = D : 'a t -> u
type _ t = C of int : int t
type u = D of 'a t : u
let eval (D x) = x
end
;;
@ -108,8 +106,8 @@ module Rectype =
module Or_patterns =
struct
type _ t =
| IntLit : int -> int t
| BoolLit : bool -> bool t
| IntLit of int : int t
| BoolLit of bool : bool t
let rec eval : type s . s t -> unit =
function
@ -121,8 +119,8 @@ end
module Polymorphic_variants =
struct
type _ t =
| IntLit : int -> int t
| BoolLit : bool -> bool t
| IntLit of int : int t
| BoolLit of bool : bool t
let rec eval : type s . [`A] * s t -> unit =
function
@ -134,8 +132,8 @@ module Polymorphic_variants =
module Propagation =
struct
type _ t =
IntLit : int -> int t
| BoolLit : bool -> bool t
IntLit of int : int t
| BoolLit of bool : bool t
let check : type s. s t -> s = function
| IntLit n -> n