]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Compiling/IO.hs
Add Parsing.Token.
[haskell/symantic.git] / Language / Symantic / Compiling / IO.hs
1 {-# LANGUAGE UndecidableInstances #-}
2 {-# OPTIONS_GHC -fno-warn-orphans #-}
3 {-# OPTIONS_GHC -fconstraint-solver-iterations=5 #-}
4 -- | Symantic for 'IO'.
5 module Language.Symantic.Compiling.IO where
6
7 import Control.Monad (liftM, liftM2)
8 import Data.Proxy
9 import Data.Text (Text)
10 import Data.Type.Equality ((:~:)(Refl))
11 import qualified System.IO as IO
12
13 import Language.Symantic.Parsing
14 import Language.Symantic.Typing
15 import Language.Symantic.Compiling.Term
16 import Language.Symantic.Interpreting
17 import Language.Symantic.Transforming.Trans
18
19 -- * Class 'Sym_IO'
20 class Sym_IO term where
21 io_hClose :: term IO.Handle -> term (IO ())
22 io_openFile :: term IO.FilePath -> term IO.IOMode -> term (IO IO.Handle)
23
24 default io_hClose :: Trans t term => t term IO.Handle -> t term (IO ())
25 default io_openFile :: Trans t term => t term IO.FilePath -> t term IO.IOMode -> t term (IO IO.Handle)
26
27 io_hClose = trans_map1 io_hClose
28 io_openFile = trans_map2 io_openFile
29
30 type instance Sym_of_Iface (Proxy IO) = Sym_IO
31 type instance Consts_of_Iface (Proxy IO) = Proxy IO ': Consts_imported_by IO
32 type instance Consts_imported_by IO =
33 [ Proxy IO.Handle
34 , Proxy IO.IOMode
35 , Proxy IO.FilePath
36 , Proxy Applicative
37 , Proxy Functor
38 , Proxy Monad
39 ]
40 type instance Consts_imported_by IO.Handle =
41 '[ Proxy Eq
42 ]
43 type instance Consts_imported_by IO.IOMode =
44 [ Proxy Enum
45 , Proxy Eq
46 , Proxy Ord
47 ]
48
49 instance Sym_IO HostI where
50 io_hClose = liftM IO.hClose
51 io_openFile = liftM2 IO.openFile
52 instance Sym_IO TextI where
53 io_hClose = textI_app1 "IO.hClose"
54 io_openFile = textI_app2 "IO.openFile"
55 instance (Sym_IO r1, Sym_IO r2) => Sym_IO (DupI r1 r2) where
56 io_hClose = dupI1 (Proxy @Sym_IO) io_hClose
57 io_openFile = dupI2 (Proxy @Sym_IO) io_openFile
58
59 instance Const_from Text cs => Const_from Text (Proxy IO ': cs) where
60 const_from "IO" k = k (ConstZ kind)
61 const_from s k = const_from s $ k . ConstS
62 instance Const_from Text cs => Const_from Text (Proxy IO.Handle ': cs) where
63 const_from "IO.Handle" k = k (ConstZ kind)
64 const_from s k = const_from s $ k . ConstS
65 instance Const_from Text cs => Const_from Text (Proxy IO.IOMode ': cs) where
66 const_from "IO.IOMode" k = k (ConstZ kind)
67 const_from s k = const_from s $ k . ConstS
68
69 instance Show_Const cs => Show_Const (Proxy IO ': cs) where
70 show_const ConstZ{} = "IO"
71 show_const (ConstS c) = show_const c
72 instance Show_Const cs => Show_Const (Proxy IO.Handle ': cs) where
73 show_const ConstZ{} = "IO.Handle"
74 show_const (ConstS c) = show_const c
75 instance Show_Const cs => Show_Const (Proxy IO.IOMode ': cs) where
76 show_const ConstZ{} = "IO.IOMode"
77 show_const (ConstS c) = show_const c
78
79 instance -- Proj_ConC IO
80 ( Proj_Const cs IO
81 , Proj_Consts cs (Consts_imported_by IO)
82 ) => Proj_ConC cs (Proxy IO) where
83 proj_conC _ (TyConst q :$ TyConst c)
84 | Just Refl <- eq_skind (kind_of_const c) (SKiType `SKiArrow` SKiType)
85 , Just Refl <- proj_const c (Proxy::Proxy IO)
86 = case () of
87 _ | Just Refl <- proj_const q (Proxy::Proxy Applicative) -> Just Con
88 | Just Refl <- proj_const q (Proxy::Proxy Functor) -> Just Con
89 | Just Refl <- proj_const q (Proxy::Proxy Monad) -> Just Con
90 _ -> Nothing
91 proj_conC _c _q = Nothing
92 instance -- Proj_ConC IO.Handle
93 ( Proj_Const cs IO.Handle
94 , Proj_Consts cs (Consts_imported_by IO.Handle)
95 ) => Proj_ConC cs (Proxy IO.Handle) where
96 proj_conC _ (TyConst q :$ TyConst c)
97 | Just Refl <- eq_skind (kind_of_const c) SKiType
98 , Just Refl <- proj_const c (Proxy::Proxy IO.Handle)
99 = case () of
100 _ | Just Refl <- proj_const q (Proxy::Proxy Eq) -> Just Con
101 _ -> Nothing
102 proj_conC _c _q = Nothing
103 instance -- Proj_ConC IO.IOMode
104 ( Proj_Const cs IO.IOMode
105 , Proj_Consts cs (Consts_imported_by IO.IOMode)
106 ) => Proj_ConC cs (Proxy IO.IOMode) where
107 proj_conC _ (TyConst q :$ TyConst c)
108 | Just Refl <- eq_skind (kind_of_const c) SKiType
109 , Just Refl <- proj_const c (Proxy::Proxy IO.IOMode)
110 = case () of
111 _ | Just Refl <- proj_const q (Proxy::Proxy Enum) -> Just Con
112 | Just Refl <- proj_const q (Proxy::Proxy Eq) -> Just Con
113 | Just Refl <- proj_const q (Proxy::Proxy Ord) -> Just Con
114 _ -> Nothing
115 proj_conC _c _q = Nothing
116 data instance TokenT meta (ts::[*]) (Proxy IO)
117 = Token_Term_IO_hClose (EToken meta ts)
118 | Token_Term_IO_openFile (EToken meta ts)
119 deriving instance Eq_Token meta ts => Eq (TokenT meta ts (Proxy IO))
120 deriving instance Show_Token meta ts => Show (TokenT meta ts (Proxy IO))
121 instance -- Term_fromI
122 ( Inj_Const (Consts_of_Ifaces is) IO
123 , Inj_Const (Consts_of_Ifaces is) IO.Handle
124 , Inj_Const (Consts_of_Ifaces is) IO.FilePath
125 , Inj_Const (Consts_of_Ifaces is) IO.IOMode
126 , Inj_Const (Consts_of_Ifaces is) (->)
127 , Inj_Const (Consts_of_Ifaces is) ()
128 , Term_from is
129 ) => Term_fromI is (Proxy IO) where
130 term_fromI tok ctx k =
131 case tok of
132 Token_Term_IO_hClose tok_h ->
133 -- hClose :: Handle -> IO ()
134 term_from tok_h ctx $ \ty_h (TermLC h) ->
135 check_type
136 (At Nothing (ty @IO.Handle))
137 (At (Just tok_h) ty_h) $ \Refl ->
138 k (ty @IO :$ ty @()) $ TermLC $
139 io_hClose . h
140 Token_Term_IO_openFile tok_fp ->
141 -- openFile :: FilePath -> IOMode -> IO Handle
142 term_from tok_fp ctx $ \ty_fp (TermLC fp) ->
143 check_type
144 (At Nothing (ty @IO.FilePath))
145 (At (Just tok_fp) ty_fp) $ \Refl ->
146 k (ty @IO.IOMode ~> ty @IO :$ ty @IO.Handle) $ TermLC $
147 \c -> lam $ io_openFile (fp c)