{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Language.LOL.Symantic.Expr.Int where import Data.Proxy (Proxy(..)) import Language.LOL.Symantic.AST import Language.LOL.Symantic.Type import Language.LOL.Symantic.Expr.Common import Language.LOL.Symantic.Expr.Lambda import Language.LOL.Symantic.Expr.Bool () import Language.LOL.Symantic.Repr.Dup -- * Class 'Sym_Int' -- | Symantics acting on 'Int's. class Sym_Int repr where int :: Int -> repr Int neg :: repr Int -> repr Int add :: repr Int -> repr Int -> repr Int instance -- Sym_Int Dup ( Sym_Int r1 , Sym_Int r2 ) => Sym_Int (Dup r1 r2) where int x = int x `Dup` int x neg (x1 `Dup` x2) = neg x1 `Dup` neg x2 add (x1 `Dup` x2) (y1 `Dup` y2) = add x1 y1 `Dup` add x2 y2 -- * Type 'Expr_Int' data Expr_Int (root:: *) type instance Root_of_Expr (Expr_Int root) = root type instance Type_of_Expr (Expr_Int root) = Type_Int type instance Sym_of_Expr (Expr_Int root) repr = Sym_Int repr type instance Error_of_Expr raw (Expr_Int root) = Error_Expr_Int raw instance -- Sym_from AST Expr_Int ( Type_from AST (Type_Root_of_Expr root) , Sym_from AST root , Type_Root_Lift Type_Int (Type_Root_of_Expr root) , Error_Type_Lift (Error_Type_Fun AST) (Error_of_Type AST (Type_Root_of_Expr root)) , Error_Expr_Lift (Error_Expr_Lambda (Error_of_Type AST (Type_Root_of_Expr root)) ( Type_Root_of_Expr root) AST) (Error_of_Expr AST root) , Error_Expr_Lift (Error_Expr_Read AST) (Error_of_Expr AST root) , Expr_Unlift (Type_Int (Type_Root_of_Expr root)) ( Type_Root_of_Expr root) , Root_of_Expr root ~ root -- , Root_of_Type (Type_Root_of_Expr root) ~ Type_Root_of_Expr root ) => Sym_from AST (Expr_Int root) where sym_from _px_ex ctx raw k = case raw of AST "int" raws -> case raws of [AST raw_int []] -> case read_safe raw_int of Left err -> Left $ Just $ error_expr_lift (Error_Expr_Read err raw :: Error_Expr_Read AST) Right (i::Int) -> k type_int $ Forall_Repr_with_Context $ const $ int i _ -> Left $ Just $ error_lambda_lift $ Error_Expr_Fun_Wrong_number_of_arguments 3 raw AST "neg" raws -> unary_from raws neg AST "add" raws -> binary_from raws add _ -> Left Nothing where unary_from raws (op::forall repr. Sym_Int repr => repr Int -> repr Int) = case raws of [raw_x] -> sym_from (Proxy::Proxy root) ctx raw_x $ \(ty_x::Type_Root_of_Expr root h_x) (Forall_Repr_with_Context x) -> case expr_unlift ty_x of Just (Type_Int::Type_Int (Type_Root_of_Expr root) h_x) -> k ty_x $ Forall_Repr_with_Context (op . x) _ -> Left $ Just $ error_lambda_lift $ Error_Expr_Fun_Argument_mismatch (Exists_Type type_int) (Exists_Type ty_x) raw _ -> Left $ Just $ error_lambda_lift $ Error_Expr_Fun_Wrong_number_of_arguments 1 raw binary_from raws (op::forall repr. Sym_Int repr => repr Int -> repr Int -> repr Int) = case raws of [raw_x, raw_y] -> sym_from (Proxy::Proxy root) ctx raw_x $ \(ty_x::Type_Root_of_Expr root h_x) (Forall_Repr_with_Context x) -> sym_from (Proxy::Proxy root) ctx raw_y $ \(ty_y::Type_Root_of_Expr root h_y) (Forall_Repr_with_Context y) -> case expr_unlift ty_x of Just (Type_Int::Type_Int (Type_Root_of_Expr root) h_x) -> case expr_unlift ty_y of Just (Type_Int::Type_Int (Type_Root_of_Expr root) h_y) -> k ty_x $ Forall_Repr_with_Context $ \c -> x c `op` y c Nothing -> Left $ Just $ error_lambda_lift $ Error_Expr_Fun_Argument_mismatch (Exists_Type type_int) (Exists_Type ty_y) raw Nothing -> Left $ Just $ error_lambda_lift $ Error_Expr_Fun_Argument_mismatch (Exists_Type type_int) (Exists_Type ty_x) raw _ -> Left $ Just $ error_lambda_lift $ Error_Expr_Fun_Wrong_number_of_arguments 2 raw error_lambda_lift :: Error_Expr_Lambda (Error_of_Type AST (Type_Root_of_Expr root)) (Type_Root_of_Expr root) AST -> Error_of_Expr AST root error_lambda_lift = error_expr_lift -- ** Type 'Expr_Lambda_Int' -- | Convenient alias. type Expr_Lambda_Int lam = Expr_Root (Expr_Cons (Expr_Lambda lam) Expr_Int) expr_lambda_int_from :: forall lam raw. Sym_from raw (Expr_Lambda_Int lam) => Proxy lam -> raw -> Either (Maybe (Error_of_Expr raw (Expr_Lambda_Int lam))) (Exists_Type_and_Repr (Type_Root_of_Expr (Expr_Lambda_Int lam)) (Forall_Repr (Expr_Lambda_Int lam))) expr_lambda_int_from _px_lam raw = sym_from (Proxy::Proxy (Expr_Lambda_Int lam)) Context_Empty raw $ \ty (Forall_Repr_with_Context repr) -> Right $ Exists_Type_and_Repr ty $ Forall_Repr $ repr Context_Empty -- * Type 'Error_Expr_Int' data Error_Expr_Int raw = Error_Expr_Int deriving (Eq, Show)