]> Git — Sourcephile - comptalang.git/blob - lcc/Hcompta/LCC/Sym/Query.hs
Commit old WIP.
[comptalang.git] / lcc / Hcompta / LCC / Sym / Query.hs
1 {-# LANGUAGE PatternSynonyms #-}
2 {-# LANGUAGE PolyKinds #-}
3 {-# LANGUAGE RankNTypes #-}
4 {-# LANGUAGE UndecidableInstances #-}
5 {-# OPTIONS_GHC -fno-warn-orphans #-}
6 -- | Symantic for 'Query'.
7 module Hcompta.LCC.Sym.Query where
8
9 import Data.Maybe (Maybe(..))
10 import Data.Typeable (Typeable)
11 import qualified Prelude ()
12
13 import Hcompta.LCC.Compta (Query, Queryable)
14
15 import Language.Symantic
16
17 -- * Class 'Sym_Query'
18 type instance Sym Query = Sym_Query
19 class Sym_Query term where
20
21 instance Sym_Query Eval where
22 instance Sym_Query View where
23 instance (Sym_Query r1, Sym_Query r2) => Sym_Query (Dup r1 r2) where
24 instance (Sym_Query term, Sym_Lambda term) => Sym_Query (BetaT term)
25
26 instance FixityOf Query
27 instance NameTyOf Query where
28 nameTyOf _c = ["LCC"] `Mod` "Query"
29 instance ClassInstancesFor Query where
30 proveConstraintFor _c _q = Nothing
31 instance TypeInstancesFor Query
32
33 instance Gram_Term_AtomsFor src ss g Query
34 instance
35 ( Source src
36 , Typeable ss
37 , SymInj ss Query
38 ) => ModuleFor src ss Query where
39 moduleFor = ["LCC"] `moduleWhere`
40 [
41 ]
42
43 tyQuery :: Source src => Type src vs db -> Type src vs a -> Type src vs (Query db a)
44 tyQuery db a = tyConstLen @(K Query) @Query (lenVars db) `tyApp` db `tyApp` a
45
46 -- * Class 'Sym_Queryable'
47 type instance Sym Queryable = Sym_Queryable
48 class Sym_Queryable term where
49
50 instance Sym_Queryable Eval where
51 instance Sym_Queryable View where
52 instance (Sym_Queryable r1, Sym_Queryable r2) => Sym_Queryable (Dup r1 r2) where
53 instance (Sym_Queryable term, Sym_Lambda term) => Sym_Queryable (BetaT term)
54
55 instance FixityOf Queryable
56 instance NameTyOf Queryable where
57 nameTyOf _c = ["LCC"] `Mod` "Queryable"
58 instance ClassInstancesFor Queryable where
59 proveConstraintFor _c _q = Nothing
60 instance TypeInstancesFor Queryable
61
62 instance Gram_Term_AtomsFor src ss g Queryable
63 instance
64 ( Source src
65 , Typeable ss
66 , SymInj ss Queryable
67 ) => ModuleFor src ss Queryable where
68 moduleFor = ["LCC"] `moduleWhere`
69 [
70 ]
71
72 tyQueryable :: Source src => Type src vs db -> Type src vs a -> Type src vs (Queryable db a)
73 tyQueryable db a = tyConstLen @(K Queryable) @Queryable (lenVars db) `tyApp` db `tyApp` a