store the magic CoreVar for hetmet brak/esc in WeakExpr Esc/Brak
[coq-hetmet.git] / src / HaskStrongToWeak.v
1 (*********************************************************************************************************************************)
2 (* HaskStrongToWeak: convert HaskStrong to HaskWeak                                                                              *)
3 (*********************************************************************************************************************************)
4
5 Generalizable All Variables.
6 Require Import Preamble.
7 Require Import General.
8 Require Import NaturalDeduction.
9 Require Import Coq.Strings.String.
10 Require Import Coq.Lists.List.
11 Require Import Coq.Init.Specif.
12 Require Import HaskKinds.
13 Require Import HaskCoreLiterals.
14 Require Import HaskCoreVars.
15 Require Import HaskWeakTypes.
16 Require Import HaskWeakVars.
17 Require Import HaskWeak.
18 Require Import HaskStrongTypes.
19 Require Import HaskStrong.
20
21 Fixpoint mfresh (f:Fresh Kind (fun _ => WeakTypeVar))(lk:list Kind){Γ}(ite:IList _ (fun _ => WeakTypeVar) Γ)
22   : (Fresh Kind (fun _ => WeakTypeVar)) * ((vec WeakTypeVar (length lk)) * (IList _ (fun _ => WeakTypeVar) (app lk Γ))) :=
23   match lk as LK return (Fresh Kind (fun _ => WeakTypeVar)) * ((vec WeakTypeVar (length LK)) *
24                           (IList _ (fun _ => WeakTypeVar) (app LK Γ))) with
25   | nil    => (f,(vec_nil,ite))
26   | k::lk' =>
27     let (f',varsite') := mfresh f lk' ite
28     in  let (vars,ite') := varsite'
29     in  let (v,f'') := next _ _ f' k
30     in (f'',((v:::vars),v::::ite'))
31   end.
32
33 Fixpoint rawHaskTypeToWeakType (f:Fresh Kind (fun _ => WeakTypeVar)){κ}(rht:RawHaskType (fun _ => WeakTypeVar) κ)
34  {struct rht} : WeakType :=
35 match rht with
36   | TVar  _  v                 => WTyVarTy v
37   | TCon      tc              => WTyCon tc
38   | TCoerc _ t1 t2 t3          => WCoFunTy (rawHaskTypeToWeakType f t1) (rawHaskTypeToWeakType f t2) (rawHaskTypeToWeakType f t3)
39   | TArrow                    => WFunTyCon
40   | TApp  _ _  t1 t2             => WAppTy (rawHaskTypeToWeakType f t1) (rawHaskTypeToWeakType f t2)
41   | TAll    k rht'            => let (tv,f') := next _ _ f k in WForAllTy tv (rawHaskTypeToWeakType f' (rht' tv))
42   | TCode   t1 t2             => 
43     match (rawHaskTypeToWeakType f t1) with
44       | WTyVarTy ec => WCodeTy ec (rawHaskTypeToWeakType f t2)
45       | impossible  => impossible  (* TODO: find a way to convince Coq this can't happen *)
46     end
47   | TyFunApp    tfc tls         => WTyFunApp tfc (rawHaskTypeListToWeakType f tls)
48 end
49 with rawHaskTypeListToWeakType (f:Fresh Kind (fun _ => WeakTypeVar)){κ}(rht:RawHaskTypeList κ) :=
50 match rht with
51   | TyFunApp_nil   => nil
52   | TyFunApp_cons  κ kl rht' rhtl' => (rawHaskTypeToWeakType f rht')::(rawHaskTypeListToWeakType f rhtl')
53 end.
54
55 Definition typeToWeakType (f:Fresh Kind (fun _ => WeakTypeVar))
56   {Γ}{κ}(τ:HaskType Γ κ)(φ:InstantiatedTypeEnv (fun _ => WeakTypeVar) Γ) : WeakType :=
57   rawHaskTypeToWeakType f (τ _ φ).
58
59 Variable unsafeCoerce           : WeakCoercion.    Extract Inlined Constant unsafeCoerce => "Coercion.unsafeCoerce".
60
61 Definition strongCoercionToWeakCoercion {Γ}{Δ}{ck}(τ:HaskCoercion Γ Δ ck)(φ:InstantiatedTypeEnv (fun _ => WeakTypeVar) Γ)
62   : WeakCoercion := unsafeCoerce.
63
64 (* This can be used to turn HaskStrong's with arbitrary expression variables into HaskStrong's which use WeakExprVar's
65  * for their variables; those can subsequently be passed to the following function (strongExprToWeakExpr) *)
66 (*
67 Definition reindexStrongExpr {VV}{HH}{eqVV:EqDecidable VV}{eqHH:EqDecidable HH}
68   {Γ}{Δ}{ξ}{lev}(exp:@Expr VV eqVV Γ Δ ξ lev) : { ξ' : HH -> LeveledHaskType Γ & @Expr HH eqHH Γ Δ ξ' lev }.
69   Defined.
70   *)
71
72 Definition updateITE {Γ:TypeEnv}{TV:Kind->Type}{κ}(tv:TV κ)(ite:InstantiatedTypeEnv TV Γ) : InstantiatedTypeEnv TV (κ::Γ)
73   := tv::::ite.
74
75 Section strongExprToWeakExpr.
76
77   Context (hetmet_brak : CoreVar).
78   Context (hetmet_esc  : CoreVar).
79 Axiom FIXME : forall {t}, t.
80
81 Fixpoint strongExprToWeakExpr {Γ}{Δ}{ξ}{τ}
82   (ftv:Fresh Kind                (fun _ => WeakTypeVar))
83   (fcv:Fresh (WeakType*WeakType) (fun _ => WeakCoerVar))
84   (exp:@Expr _ CoreVarEqDecidable Γ Δ ξ τ)
85   : InstantiatedTypeEnv (fun _ => WeakTypeVar) Γ -> WeakExpr :=
86 match exp as E in @Expr _ _ G D X L return InstantiatedTypeEnv (fun _ => WeakTypeVar) G -> WeakExpr with
87 | EVar  Γ' _ ξ' ev              => fun ite => WEVar (weakExprVar ev (@typeToWeakType ftv Γ' ★  (unlev (ξ' ev)) ite))
88 | ELit  _ _ _ lit _             => fun ite => WELit lit
89 | EApp  Γ' _ _ _ _ _ e1 e2      => fun ite => WEApp (strongExprToWeakExpr ftv fcv e1 ite) (strongExprToWeakExpr ftv fcv e2 ite)
90 | ELam  Γ'   _ _ _ t _ cv e     => fun ite => WELam (weakExprVar cv (typeToWeakType ftv t ite)) (strongExprToWeakExpr ftv fcv e ite)
91 | ELet  Γ' _ _ t _ _ ev e1 e2   => fun ite => WELet (weakExprVar ev (typeToWeakType ftv t ite)) (strongExprToWeakExpr ftv fcv e1 ite) (strongExprToWeakExpr ftv fcv e2 ite)
92 | EEsc  Γ' _ _ ec t _ e         => fun ite => WEEsc  hetmet_esc (ec _ ite) (strongExprToWeakExpr ftv fcv e ite) (typeToWeakType ftv t ite)
93 | EBrak Γ' _ _ ec t _ e         => fun ite => WEBrak hetmet_brak (ec _ ite) (strongExprToWeakExpr ftv fcv e ite) (typeToWeakType ftv t ite)
94 | ECast Γ Δ ξ t1 t2 γ l e       => fun ite => WECast (strongExprToWeakExpr ftv fcv e ite) (strongCoercionToWeakCoercion γ ite)
95 | ENote _ _ _ _ n e             => fun ite => WENote n (strongExprToWeakExpr ftv fcv e ite)
96 | ETyApp  Γ Δ κ σ τ ξ l       e => fun ite => WETyApp (strongExprToWeakExpr ftv fcv e ite) (typeToWeakType ftv τ ite)
97 | ELetRec _ _ _ _ _ vars elrb e =>fun ite=>WELetRec (exprLetRec2WeakExprLetRec ftv fcv elrb ite)(strongExprToWeakExpr ftv fcv e ite)
98 | ECoApp Γ Δ κ σ₁ σ₂ γ σ ξ l e  => fun ite => WECoApp (strongExprToWeakExpr ftv fcv e ite) (strongCoercionToWeakCoercion γ ite)
99 | ECase Γ Δ ξ l tc tbranches atypes e alts =>
100   fun ite => WECase
101     (strongExprToWeakExpr ftv fcv e ite)
102     (@typeToWeakType ftv Γ _ tbranches ite)
103     tc
104     (ilist_to_list (@ilmap _ _ (fun _ => WeakType) _ (fun _ t => typeToWeakType ftv t ite) atypes))
105     ((fix caseBranches
106       (tree:Tree ??{ scb : StrongCaseBranchWithVVs _ _ tc atypes
107                             & Expr (sac_Γ scb Γ)
108                                    (sac_Δ scb Γ atypes (weakCK'' Δ))
109                                    (update_ξ (weakLT'○ξ) (vec2list (vec_map
110                                      (fun x => ((fst x),(snd x @@ weakL' l))) (scbwv_varstypes scb))))
111                                    (weakLT' (tbranches@@l)) })
112       : Tree ??(AltCon * list WeakTypeVar * list WeakCoerVar * list WeakExprVar * WeakExpr) :=
113       match tree with
114         | T_Leaf None     => []
115         | T_Leaf (Some x) => let (scb,e) := x in
116           let (ftv',evarsite') := mfresh ftv _ ite in
117           let fcv' :=  fcv in
118             let (evars,ite') := evarsite' in
119             [(sac_altcon scb,
120               vec2list evars,
121               nil (*FIXME*),
122               map (fun vt => weakExprVar (fst vt) (typeToWeakType ftv' (snd vt) ite')) (vec2list (scbwv_varstypes scb)),
123               strongExprToWeakExpr ftv' fcv' e ite'
124             )]
125         | T_Branch b1 b2  => (caseBranches b1),,(caseBranches b2)
126       end
127     ) alts)
128 | ETyLam _ _ _ k _ _ e          => fun ite =>
129   let (tv,ftv') := next _ _ ftv k in WETyLam tv (strongExprToWeakExpr ftv' fcv e (updateITE tv ite))
130 | ECoLam Γ Δ κ σ σ₁ σ₂ ξ l e => fun ite =>
131   let t1' := typeToWeakType ftv σ₁ ite in 
132   let t2' := typeToWeakType ftv σ₂ ite in
133   let (cv,fcv') := next _ _ fcv (t1',t2') in WECoLam cv (strongExprToWeakExpr ftv fcv' e ite)
134 end
135 with exprLetRec2WeakExprLetRec {Γ}{Δ}{ξ}{τ}{vars}
136   (ftv:Fresh Kind                (fun _ => WeakTypeVar))
137   (fcv:Fresh (WeakType*WeakType) (fun _ => WeakCoerVar))
138   (elrb:@ELetRecBindings _ CoreVarEqDecidable Γ Δ ξ τ vars)
139   : InstantiatedTypeEnv (fun _ => WeakTypeVar) Γ -> Tree ??(WeakExprVar * WeakExpr) :=
140 match elrb as E in ELetRecBindings G D X L V
141    return InstantiatedTypeEnv (fun _ => WeakTypeVar) G -> Tree ??(WeakExprVar * WeakExpr) with
142 | ELR_nil    _ _ _ _           => fun ite => []
143 | ELR_leaf   _ _ ξ' cv v e    => fun ite => [((weakExprVar v (typeToWeakType ftv (unlev (ξ' v)) ite)),(strongExprToWeakExpr ftv fcv e ite))]
144 | ELR_branch _ _ _ _ _ _ b1 b2 => fun ite => (exprLetRec2WeakExprLetRec ftv fcv b1 ite),, (exprLetRec2WeakExprLetRec ftv fcv b2 ite)
145 end.
146 End strongExprToWeakExpr.