{-# LANGUAGE UndecidableInstances #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_GHC -fconstraint-solver-iterations=6 #-} -- | Symantic for 'Integer'. module Language.Symantic.Compiling.Integer where import Control.Applicative (Alternative(..)) import Data.Proxy import qualified Data.Text as Text import Data.Type.Equality ((:~:)(Refl)) import Language.Symantic.Parsing import Language.Symantic.Parsing.Grammar import Language.Symantic.Typing import Language.Symantic.Compiling.Term import Language.Symantic.Interpreting import Language.Symantic.Transforming.Trans -- * Class 'Sym_Integer' class Sym_Integer term where integer :: Integer -> term Integer default integer :: Trans t term => Integer -> t term Integer integer = trans_lift . integer type instance Sym_of_Iface (Proxy Integer) = Sym_Integer type instance Consts_of_Iface (Proxy Integer) = Proxy Integer ': Consts_imported_by Integer type instance Consts_imported_by Integer = [ Proxy Enum , Proxy Eq , Proxy Integral , Proxy Num , Proxy Ord , Proxy Real , Proxy Show ] instance Sym_Integer HostI where integer = HostI instance Sym_Integer TextI where integer a = TextI $ \_p _v -> Text.pack (show a) instance (Sym_Integer r1, Sym_Integer r2) => Sym_Integer (DupI r1 r2) where integer x = integer x `DupI` integer x instance ( Read_TypeNameR Type_Name cs rs , Inj_Const cs Integer ) => Read_TypeNameR Type_Name cs (Proxy Integer ': rs) where read_typenameR _cs (Type_Name "Integer") k = k (ty @Integer) read_typenameR _rs raw k = read_typenameR (Proxy @rs) raw k instance Show_Const cs => Show_Const (Proxy Integer ': cs) where show_const ConstZ{} = "Integer" show_const (ConstS c) = show_const c instance -- Proj_ConC ( Proj_Const cs Integer , Proj_Consts cs (Consts_imported_by Integer) ) => Proj_ConC cs (Proxy Integer) where proj_conC _ (TyConst q :$ TyConst c) | Just Refl <- eq_skind (kind_of_const c) SKiType , Just Refl <- proj_const c (Proxy @Integer) = case () of _ | Just Refl <- proj_const q (Proxy @Enum) -> Just Con | Just Refl <- proj_const q (Proxy @Eq) -> Just Con | Just Refl <- proj_const q (Proxy @Integral) -> Just Con | Just Refl <- proj_const q (Proxy @Num) -> Just Con | Just Refl <- proj_const q (Proxy @Ord) -> Just Con | Just Refl <- proj_const q (Proxy @Real) -> Just Con | Just Refl <- proj_const q (Proxy @Show) -> Just Con _ -> Nothing proj_conC _c _q = Nothing data instance TokenT meta (ts::[*]) (Proxy Integer) = Token_Term_Integer Integer deriving instance Eq_Token meta ts => Eq (TokenT meta ts (Proxy Integer)) deriving instance Show_Token meta ts => Show (TokenT meta ts (Proxy Integer)) instance -- CompileI Inj_Const (Consts_of_Ifaces is) Integer => CompileI is (Proxy Integer) where compileI tok _ctx k = case tok of Token_Term_Integer i -> k (ty @Integer) $ TermO $ \_c -> integer i instance -- TokenizeT -- Inj_Token meta ts Integer => TokenizeT meta ts (Proxy Integer) instance -- Gram_Term_AtomsT ( Alt g , Alter g , Alternative g , Gram_Rule g , Gram_Lexer g , Gram_Meta meta g , Inj_Token meta ts Integer ) => Gram_Term_AtomsT meta ts (Proxy Integer) g where term_atomsT _t = [ rule "term_integer" $ lexeme $ metaG $ (\i meta -> ProTok $ inj_etoken meta $ Token_Term_Integer $ read i) <$> some (choice $ char <$> ['0'..'9']) ]