{-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} module Language.LOL.Symantic.Expr.If where import Data.Proxy (Proxy(..)) import Data.Type.Equality ((:~:)(Refl)) import Language.LOL.Symantic.AST import Language.LOL.Symantic.Expr.Bool import Language.LOL.Symantic.Expr.Common import Language.LOL.Symantic.Expr.Lambda import Language.LOL.Symantic.Repr.Dup import Language.LOL.Symantic.Trans.Common import Language.LOL.Symantic.Type -- * Class 'Sym_If' class Sym_If repr where if_ :: repr Bool -> repr a -> repr a -> repr a when_ :: repr Bool -> repr () -> repr () default if_ :: Trans t repr => t repr Bool -> t repr a -> t repr a -> t repr a default when_ :: Trans t repr => t repr Bool -> t repr () -> t repr () if_ = trans_map3 if_ when_ = trans_map2 when_ instance -- Sym_If Dup ( Sym_If r1 , Sym_If r2 ) => Sym_If (Dup r1 r2) where if_ (c1 `Dup` c2) (ok1 `Dup` ok2) (ko1 `Dup` ko2) = if_ c1 ok1 ko1 `Dup` if_ c2 ok2 ko2 when_ (c1 `Dup` c2) (ok1 `Dup` ok2) = when_ c1 ok1 `Dup` when_ c2 ok2 -- * Type 'Expr_If' -- | Expression. data Expr_If (root:: *) type instance Root_of_Expr (Expr_If root) = root type instance Type_of_Expr (Expr_If root) = No_Type type instance Sym_of_Expr (Expr_If root) repr = (Sym_If repr) type instance Error_of_Expr ast (Expr_If root) = No_Error_Expr instance -- Expr_from AST Expr_If ( Type_from AST (Type_Root_of_Expr root) , Expr_from AST root , Type_Root_Lift Type_Bool (Type_Root_of_Expr root) , Error_Expr_Lift (Error_Expr (Error_of_Type AST (Type_Root_of_Expr root)) ( Type_Root_of_Expr root) AST) (Error_of_Expr AST root) , Root_of_Expr root ~ root , Implicit_HBool (Is_Last_Expr (Expr_If root) root) ) => Expr_from AST (Expr_If root) where expr_from px_ex ctx ast k = case ast of AST "if" asts -> case asts of [ast_cond, ast_ok, ast_ko] -> expr_from (Proxy::Proxy root) ctx ast_cond $ \(ty_cond::Type_Root_of_Expr root h_n) (Forall_Repr_with_Context cond) -> expr_from (Proxy::Proxy root) ctx ast_ok $ \(ty_ok::Type_Root_of_Expr root h_ok) (Forall_Repr_with_Context ok) -> expr_from (Proxy::Proxy root) ctx ast_ko $ \(ty_ko::Type_Root_of_Expr root h_ko) (Forall_Repr_with_Context ko) -> when_type_eq px_ex ast type_bool ty_cond $ \Refl -> when_type_eq px_ex ast ty_ok ty_ko $ \Refl -> k ty_ok $ Forall_Repr_with_Context $ \c -> if_ (cond c) (ok c) (ko c) _ -> Left $ error_expr px_ex $ Error_Expr_Wrong_number_of_arguments ast 3 _ -> Left $ error_expr_unsupported px_ex ast -- ** Type 'Expr_Lambda_Bool_If' -- | Convenient alias. type Expr_Lambda_If_Bool lam = Expr_Root (Expr_Alt (Expr_Lambda lam) (Expr_Alt Expr_If Expr_Bool)) -- | Convenient alias around 'expr_from'. expr_lambda_if_bool_from :: forall lam ast root. ( Expr_from ast (Expr_Lambda_If_Bool lam) , root ~ Expr_Lambda_If_Bool lam ) => Proxy lam -> ast -> Either (Error_of_Expr ast root) (Exists_Type_and_Repr (Type_Root_of_Expr root) (Forall_Repr root)) expr_lambda_if_bool_from _px_lam ast = expr_from (Proxy::Proxy root) Context_Empty ast $ \ty (Forall_Repr_with_Context repr) -> Right $ Exists_Type_and_Repr ty $ Forall_Repr $ repr Context_Empty