-- | Symantic for 'Integer'.
module Language.Symantic.Lib.Integer where
+import Data.Eq (Eq)
+import Data.Function (($), (.))
+import Data.Functor ((<$>))
+import Data.Maybe (Maybe(..))
+import Data.Ord (Ord)
+import Prelude (Enum, Integer, Integral, Num, Real)
+import Text.Show (Show(..))
+import Text.Read (read)
import qualified Data.Text as Text
import Language.Symantic
instance NameTyOf Integer where
nameTyOf _c = ["Integer"] `Mod` "Integer"
instance ClassInstancesFor Integer where
- proveConstraintFor _ (TyApp _ (TyConst _ _ q) z)
+ proveConstraintFor _ (TyConst _ _ q :$ z)
| Just HRefl <- proj_ConstKiTy @_ @Integer z
= case () of
_ | Just Refl <- proj_Const @Enum q -> Just Dict