]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Compiling/Applicative.hs
Add Gram_Term.
[haskell/symantic.git] / Language / Symantic / Compiling / Applicative.hs
1 {-# LANGUAGE UndecidableInstances #-}
2 {-# OPTIONS_GHC -fno-warn-orphans #-}
3 -- | Symantic for 'Applicative'.
4 module Language.Symantic.Compiling.Applicative where
5
6 import Control.Applicative (Applicative)
7 import qualified Control.Applicative as Applicative
8 import Control.Monad (liftM, liftM2)
9 import qualified Data.Function as Fun
10 import Data.Proxy
11 import Data.Type.Equality ((:~:)(Refl))
12 import Prelude hiding (Functor(..), (<$>), Applicative(..), id, const)
13
14 import Language.Symantic.Parsing
15 import Language.Symantic.Parsing.Grammar
16 import Language.Symantic.Typing
17 import Language.Symantic.Compiling.Term
18 import Language.Symantic.Compiling.Lambda
19 import Language.Symantic.Compiling.Functor (Sym_Functor(..), (<$>))
20 import Language.Symantic.Interpreting
21 import Language.Symantic.Transforming.Trans
22
23 -- * Class 'Sym_Applicative'
24 class Sym_Functor term => Sym_Applicative term where
25 pure :: Applicative f => term a -> term (f a)
26 (<*>) :: Applicative f => term (f (a -> b)) -> term (f a) -> term (f b)
27
28 default pure :: (Trans t term, Applicative f) => t term a -> t term (f a)
29 default (<*>) :: (Trans t term, Applicative f)
30 => t term (f (a -> b)) -> t term (f a) -> t term (f b)
31
32 pure = trans_map1 pure
33 (<*>) = trans_map2 (<*>)
34 (*>) :: Applicative f => term (f a) -> term (f b) -> term (f b)
35 (<*) :: Applicative f => term (f a) -> term (f b) -> term (f a)
36 x *> y = (lam Fun.id <$ x) <*> y
37 x <* y = (lam (lam . Fun.const) <$> x) <*> y
38
39 infixl 4 *>
40 infixl 4 <*
41 infixl 4 <*>
42
43 type instance Sym_of_Iface (Proxy Applicative) = Sym_Applicative
44 type instance Consts_of_Iface (Proxy Applicative) = Proxy Applicative ': Consts_imported_by Applicative
45 type instance Consts_imported_by Applicative = '[]
46
47 instance Sym_Applicative HostI where
48 pure = liftM Applicative.pure
49 (<*>) = liftM2 (Applicative.<*>)
50 instance Sym_Applicative TextI where
51 pure = textI1 "pure"
52 (<*>) = textI_infix "<*>" (infixL 4)
53 (<* ) = textI_infix "<*" (infixL 4)
54 ( *>) = textI_infix "*>" (infixL 4)
55 instance (Sym_Applicative r1, Sym_Applicative r2) => Sym_Applicative (DupI r1 r2) where
56 pure = dupI1 (Proxy @Sym_Applicative) pure
57 (<*>) = dupI2 (Proxy @Sym_Applicative) (<*>)
58
59 instance
60 ( Read_TypeNameR Type_Name cs rs
61 , Inj_Const cs Applicative
62 ) => Read_TypeNameR Type_Name cs (Proxy Applicative ': rs) where
63 read_typenameR _cs (Type_Name "Applicative") k = k (ty @Applicative)
64 read_typenameR _rs raw k = read_typenameR (Proxy @rs) raw k
65 instance Show_Const cs => Show_Const (Proxy Applicative ': cs) where
66 show_const ConstZ{} = "Applicative"
67 show_const (ConstS c) = show_const c
68
69 instance Proj_ConC cs (Proxy Applicative)
70 data instance TokenT meta (ts::[*]) (Proxy Applicative)
71 = Token_Term_Applicative_pure (EToken meta '[Proxy Token_Type]) (EToken meta ts)
72 | Token_Term_Applicative_app (EToken meta ts)
73 | Token_Term_Applicative_tsnoc (EToken meta ts) (EToken meta ts)
74 | Token_Term_Applicative_const (EToken meta ts) (EToken meta ts)
75 deriving instance (Eq meta, Eq_Token meta ts) => Eq (TokenT meta ts (Proxy Applicative))
76 deriving instance (Show meta, Show_Token meta ts) => Show (TokenT meta ts (Proxy Applicative))
77 instance -- CompileI
78 ( Read_TypeName Type_Name (Consts_of_Ifaces is)
79 , Inj_Const (Consts_of_Ifaces is) Applicative
80 , Inj_Const (Consts_of_Ifaces is) (->)
81 , Proj_Con (Consts_of_Ifaces is)
82 , Compile is
83 ) => CompileI is (Proxy Applicative) where
84 compileI tok ctx k =
85 case tok of
86 Token_Term_Applicative_pure tok_ty_f tok_a ->
87 -- pure :: Applicative f => a -> f a
88 compile_type tok_ty_f $ \(ty_f::Type (Consts_of_Ifaces is) f) ->
89 check_kind
90 (At Nothing $ SKiType `SKiArrow` SKiType)
91 (At (Just tok_ty_f) $ kind_of ty_f) $ \Refl ->
92 check_con (At (Just tok_ty_f) (ty @Applicative :$ ty_f)) $ \Con ->
93 compileO tok_a ctx $ \ty_a (TermO a) ->
94 k (ty_f :$ ty_a) $ TermO $
95 \c -> pure (a c)
96 Token_Term_Applicative_app tok_fa2b ->
97 -- (<*>) :: Applicative f => f (a -> b) -> f a -> f b
98 compileO tok_fa2b ctx $ \ty_fa2b (TermO fa2b) ->
99 check_con1 (ty @Applicative)
100 (At (Just tok_fa2b) ty_fa2b) $ \Refl Con ty_fa2b_f ty_fa2b_a2b ->
101 check_type2 (ty @(->)) (At (Just tok_fa2b) ty_fa2b_a2b) $ \Refl ty_fa2b_a ty_fa2b_b ->
102 k (ty_fa2b_f :$ ty_fa2b_a ~> ty_fa2b_f :$ ty_fa2b_b) $ TermO $
103 \c -> lam $ \fa -> (<*>) (fa2b c) fa
104 Token_Term_Applicative_const tok_fa tok_fb ->
105 -- (<*) :: Applicative f => f a -> f b -> f a
106 compileO tok_fa ctx $ \ty_fa (TermO fa) ->
107 compileO tok_fb ctx $ \ty_fb (TermO fb) ->
108 check_con1 (ty @Applicative)
109 (At (Just tok_fa) ty_fa) $ \Refl Con ty_fa_f _ty_fa_a ->
110 check_type1 ty_fa_f (At (Just tok_fb) ty_fb) $ \Refl _ty_fb_b ->
111 k ty_fa $ TermO $
112 \c -> (<*) (fa c) (fb c)
113 Token_Term_Applicative_tsnoc tok_fa tok_fb ->
114 -- (*>) :: Applicative f => f a -> f b -> f b
115 compileO tok_fa ctx $ \ty_fa (TermO fa) ->
116 compileO tok_fb ctx $ \ty_fb (TermO fb) ->
117 check_con1 (ty @Applicative)
118 (At (Just tok_fa) ty_fa) $ \Refl Con ty_fa_f _ty_fa_a ->
119 check_type1 ty_fa_f (At (Just tok_fb) ty_fb) $ \Refl _ty_fb_b ->
120 k ty_fb $ TermO $
121 \c -> (*>) (fa c) (fb c)
122 instance -- TokenizeT
123 Inj_Token meta ts Applicative =>
124 TokenizeT meta ts (Proxy Applicative) where
125 tokenizeT _t = mempty
126 { tokenizers_infix = tokenizeTMod []
127 [ tokenize1 "<*>" (infixL 4) Token_Term_Applicative_app
128 , tokenize2 "<*" (infixL 4) Token_Term_Applicative_const
129 , tokenize2 "*>" (infixL 4) Token_Term_Applicative_tsnoc
130 ]
131 }
132 instance Gram_Term_AtomsT meta ts (Proxy Applicative) g