{-# LANGUAGE DataKinds #-} {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_GHC -fconstraint-solver-iterations=6 #-} -- | Symantic for 'Int'. module Language.Symantic.Compiling.Int where import qualified Data.Function as Fun import Data.Proxy import Data.String (IsString) import Data.Text (Text) import qualified Data.Text as Text import Data.Type.Equality ((:~:)(Refl)) import Language.Symantic.Typing import Language.Symantic.Compiling.Term import Language.Symantic.Interpreting import Language.Symantic.Transforming.Trans -- * Class 'Sym_Int' class Sym_Int term where int :: Int -> term Int default int :: Trans t term => Int -> t term Int int = trans_lift . int type instance Sym_of_Iface (Proxy Int) = Sym_Int type instance Consts_of_Iface (Proxy Int) = Proxy Int ': Consts_imported_by Int type instance Consts_imported_by Int = [ Proxy Bounded , Proxy Enum , Proxy Eq , Proxy Integral , Proxy Num , Proxy Ord , Proxy Real ] instance Sym_Int HostI where int = HostI instance Sym_Int TextI where int a = TextI $ \_p _v -> Text.pack (show a) instance (Sym_Int r1, Sym_Int r2) => Sym_Int (DupI r1 r2) where int x = int x `DupI` int x instance Const_from Text cs => Const_from Text (Proxy Int ': cs) where const_from "Int" k = k (ConstZ kind) const_from s k = const_from s $ k . ConstS instance Show_Const cs => Show_Const (Proxy Int ': cs) where show_const ConstZ{} = "Int" show_const (ConstS c) = show_const c instance -- Proj_ConC ( Proj_Const cs Int , Proj_Consts cs (Consts_imported_by Int) ) => Proj_ConC cs (Proxy Int) where proj_conC _ (TyConst q :$ TyConst c) | Just Refl <- eq_skind (kind_of_const c) SKiType , Just Refl <- proj_const c (Proxy::Proxy Int) = case () of _ | Just Refl <- proj_const q (Proxy::Proxy Bounded) -> Just Con | Just Refl <- proj_const q (Proxy::Proxy Enum) -> Just Con | Just Refl <- proj_const q (Proxy::Proxy Eq) -> Just Con | Just Refl <- proj_const q (Proxy::Proxy Integral) -> Just Con | Just Refl <- proj_const q (Proxy::Proxy Num) -> Just Con | Just Refl <- proj_const q (Proxy::Proxy Ord) -> Just Con | Just Refl <- proj_const q (Proxy::Proxy Real) -> Just Con _ -> Nothing proj_conC _c _q = Nothing instance -- Term_fromI ( AST ast , Lexem ast ~ LamVarName , Inj_Const (Consts_of_Ifaces is) Int , Show_Const (Consts_of_Ifaces is) ) => Term_fromI is (Proxy Int) ast where term_fromI ast _ctx k = case ast_lexem ast of "int" -> int_from _ -> Left $ Error_Term_unsupported where int_from = let ty = tyInt in from_ast1 ast $ \ast_lit as -> from_lex (Text.pack $ show_type ty) ast_lit $ \(lit::Int) -> k as ty $ TermLC $ Fun.const $ int lit -- | The 'Int' 'Type' tyInt :: Inj_Const cs Int => Type cs Int tyInt = TyConst inj_const sym_Int :: Proxy Sym_Int sym_Int = Proxy syInt :: IsString a => Syntax a syInt = Syntax "Int" []