]> Git — Sourcephile - comptalang.git/blob - lcc/Hcompta/LCC/Sym/Date.hs
Rewrite hcompta-lcc to use symantic-grammar.
[comptalang.git] / lcc / Hcompta / LCC / Sym / Date.hs
1 {-# LANGUAGE UndecidableInstances #-}
2 {-# OPTIONS_GHC -fno-warn-orphans #-}
3 -- | Symantic for 'Date'.
4 module Hcompta.LCC.Sym.Date where
5
6 import Control.Monad (liftM2)
7 import Data.Eq (Eq)
8 import Data.Function (($))
9 import Data.Maybe (Maybe(..))
10 import Data.Monoid (Monoid(..))
11 import Data.Proxy
12 import Prelude (undefined)
13 import Text.Show (Show)
14 import qualified Prelude ()
15
16 import Hcompta.LCC.Posting (Date)
17 import Hcompta.Quantity
18 import Language.Symantic
19 import qualified Language.Symantic.Lib as Sym
20
21 -- * Class 'Sym_Date'
22 class Sym_Date (term:: * -> *) where
23
24 type instance Sym_of_Iface (Proxy Date) = Sym_Date
25 type instance TyConsts_of_Iface (Proxy Date) = Proxy Date ': TyConsts_imported_by (Proxy Date)
26 type instance TyConsts_imported_by (Proxy Date) = '[]
27
28 instance Sym_Date HostI where
29 instance Sym_Date TextI where
30 instance (Sym_Date r1, Sym_Date r2) => Sym_Date (DupI r1 r2) where
31
32 instance
33 ( Read_TyNameR TyName cs rs
34 , Inj_TyConst cs Date
35 ) => Read_TyNameR TyName cs (Proxy Date ': rs) where
36 read_TyNameR _cs (TyName "Date") k = k (ty @Date)
37 read_TyNameR _rs raw k = read_TyNameR (Proxy @rs) raw k
38 instance Show_TyConst cs => Show_TyConst (Proxy Date ': cs) where
39 show_TyConst TyConstZ{} = "Date"
40 show_TyConst (TyConstS c) = show_TyConst c
41
42 instance Proj_TyFamC cs Sym.TyFam_MonoElement Date
43
44 instance Proj_TyConC cs (Proxy Date)
45 data instance TokenT meta (ts::[*]) (Proxy Date)
46 = Token_Term_Date_add (EToken meta ts)
47 deriving instance (Eq meta, Eq_Token meta ts) => Eq (TokenT meta ts (Proxy Date))
48 deriving instance (Show meta, Show_Token meta ts) => Show (TokenT meta ts (Proxy Date))
49
50 instance -- CompileI
51 ( Inj_TyConst cs Date
52 , Inj_TyConst cs (->)
53 , Proj_TyCon cs
54 , Compile cs is
55 ) => CompileI cs is (Proxy Date) where
56 compileI tok _ctx _k =
57 case tok of
58 _ -> undefined
59 instance -- TokenizeT
60 Inj_Token meta ts Date =>
61 TokenizeT meta ts (Proxy Date)
62 instance Gram_Term_AtomsT meta ts (Proxy Date) g