1 {-# LANGUAGE UndecidableInstances #-}
2 {-# OPTIONS_GHC -fno-warn-orphans #-}
3 -- | Symantic for '()'.
4 module Language.Symantic.Lib.Unit where
6 import Prelude hiding ((&&), not, (||))
8 import Language.Symantic
9 import Language.Symantic.Grammar
12 type instance Sym (Proxy ()) = Sym_Unit
13 class Sym_Unit term where
15 default unit :: Sym_Unit (UnT term) => Trans term => term ()
19 instance Sym_Unit Eval where
21 instance Sym_Unit View where
22 unit = View $ \_p _v -> "()"
23 instance (Sym_Unit r1, Sym_Unit r2) => Sym_Unit (Dup r1 r2) where
24 unit = unit `Dup` unit
27 instance (Sym_Unit term, Sym_Lambda term) => Sym_Unit (BetaT term)
30 instance ClassInstancesFor () where
31 proveConstraintFor _ (TyApp _ (TyConst _ _ q) z)
32 | Just HRefl <- proj_ConstKiTy @_ @() z
34 _ | Just Refl <- proj_Const @Bounded q -> Just Dict
35 | Just Refl <- proj_Const @Enum q -> Just Dict
36 | Just Refl <- proj_Const @Eq q -> Just Dict
37 | Just Refl <- proj_Const @Monoid q -> Just Dict
38 | Just Refl <- proj_Const @Ord q -> Just Dict
39 | Just Refl <- proj_Const @Show q -> Just Dict
41 proveConstraintFor _c _q = Nothing
42 instance TypeInstancesFor ()
50 ) => Gram_Term_AtomsFor src ss g () where
54 (\src -> BinTree0 $ Token_Term $ TermAVT $ (`setSource` src) $ teUnit)
58 instance ModuleFor src ss ()
61 tyUnit :: Source src => Inj_Len vs => Type src vs ()
62 tyUnit = tyConst @(K ()) @()
65 teUnit :: TermDef () '[] (() #> ())
66 teUnit = Term noConstraint tyUnit $ teSym @() $ unit