4a5a63ad08513cfe5e59c6e831db8bbb806edde7
[clean-tests.git] / gengen / Data / GenType / CType.icl
1 implementation module Data.GenType.CType
2
3 import Control.Applicative
4 import Control.Monad
5 import Control.Monad.Fail
6 import Control.Monad.Reader
7 import Control.Monad.State
8 import Control.Monad.Trans
9 import Control.Monad.Writer
10 import Data.Either
11 import Data.Func
12 import Data.Functor
13 import Data.GenType
14 import Data.List
15 import qualified Data.Map
16 from Data.Map import :: Map(..)
17 import Data.Maybe
18 import Data.Tuple
19 import StdEnv
20 import qualified Text
21 from Text import class Text(concat), instance Text String
22
23 instance MonadFail (Either String) where fail s = Left s
24
25 safe :: String -> String
26 safe s = concat [fromMaybe {c} $ lookup c cs\\c <-:s]
27 where
28 cs = [('~', "Tld"), ('@', "At"), ('#', "Hsh"), ('$', "Dlr"), ('%', "Prc")
29 ,('^', "Hat"), ('?', "Qtn"), ('!', "Bng"), (':', "Cln"), ('+', "Pls")
30 ,('-', "Min"), ('*', "Ast"), ('<', "Les"), ('>', "Gre"), ('\\', "Bsl")
31 ,('/', "Slh"), ('|', "Pip"), ('&', "Amp"), ('=', "Eq"), ('.', "Dot")]
32
33 prefix :: Type -> String
34 prefix (TyRecord _ _) = "struct "
35 prefix (TyObject _ fs)
36 | and [t =: [] \\ (_, t)<-fs] = "enum "
37 | fs =: [(_, [_])] = ""
38 | fs =: [_] = "struct "
39 = "struct "
40 prefix _ = ""
41
42 consName :: GenericTypeDefDescriptor -> String
43 consName s = "enum " +++ safe s.gtd_name +++ "_cons"
44
45 iindent = mapWriterT $ mapStateT $ local inc
46 indent c = liftT (liftT ask) >>= \i->tell [createArray i '\t':c]
47
48 :: FTMonad :== WriterT [String] (StateT [(String, [String])] (ReaderT Int (Either String))) ()
49 flatTypedef :: Type -> Either String [String]
50 flatTypedef t = (\(w, es)->flatten (map snd es) ++ w)
51 <$> runReaderT (runStateT (execWriterT (ftd t True )) []) 0
52 where
53 ftd :: Type Bool -> FTMonad
54 ftd (TyRef s) tl = indent [s]
55 ftd (TyBasic t) tl
56 | tl = pure ()
57 = case t of
58 BTInt = indent ["int64_t"]
59 BTChar = indent ["char"]
60 BTReal = indent ["double"]
61 BTBool = indent ["bool"]
62 t = fail $ "flatTypedef: there is no basic type for " +++ toString t
63 ftd (TyArrow l r) tl = fail "flatTypedef: functions cannot be serialized"
64 ftd (TyNewType ti ci a) tl = ftd a tl
65 ftd (TyArray _ a) tl = indent ["*"] >>| ftd a tl
66 ftd (TyRecord ti fs) tl
67 = indent ["struct ", if tl (safe ti.grd_name) "", " {\n"
68 ] >>| mapM_ (iindent o fmtField) [(fi.gfd_name, ty)\\(fi, ty)<-fs]
69 >>| indent ["}\n"]
70 //Enumeration
71 ftd (TyObject ti fs) tl
72 | and [t =: [] \\ (_, t)<-fs]
73 | tl = pure ()
74 = indent [] >>| enum ti fs
75 //Single constructor, single field (box)
76 ftd (TyObject ti [(ci, [ty])]) tl = ftd ty tl
77 //Single constructor
78 ftd (TyObject ti [(ci, ts)]) tl
79 = indent ["struct ", if tl (safe ti.gtd_name) "", " {\n"]
80 >>| mapM_ (iindent o fmtField) [("f" +++ toString i, ty)\\i<-[0..] & ty<-ts]
81 >>| indent ["}"]
82 //Complex adt
83 ftd (TyObject ti fs) tl
84 = indent ["struct ", if tl (safe ti.gtd_name) "", " {\n"]
85 >>| iindent (indent []) >>| enum ti fs >>| tell [" cons;\n"]
86 >>| iindent (indent ["struct {\n"])
87 >>| mapM_ (iindent o iindent o fmtCons) fs
88 >>| iindent (indent ["} data;\n"])
89 >>| indent ["}", if tl ";" ""]
90 where
91 fmtCons (ci, []) = pure ()
92 fmtCons (ci, [t]) = ftd t False >>| tell [" ", safe ci.gcd_name, ";\n"]
93 fmtCons (ci, ts)
94 = indent ["struct {\n"]
95 >>| mapM_ (iindent o fmtField) [("f" +++ toString i, ty)\\i<-[0..] & ty<-ts]
96 >>| indent ["} ", safe ci.gcd_name, ";\n"]
97 ftd t tl = fail $ "cannot flatTypedef: " +++ toString t
98
99 enum :: GenericTypeDefDescriptor [(GenericConsDescriptor, [Type])] -> FTMonad
100 enum ti fs = liftT (gets (lookup ti.gtd_name)) >>= \e->case e of
101 ?None = liftT (modify \s->[(ti.gtd_name, [consName ti, " {", 'Text'.join ", " [safe ci.gcd_name\\(ci, _)<-fs], "};\n"]):s]) >>| enum ti fs
102 ?Just _ = tell [consName ti]
103
104 fmtField :: (String, Type) -> FTMonad
105 fmtField (name, ty) = ftd ty False >>| tell [" ", name, ";\n"]
106
107 :: TDMonad :== WriterT [String] (StateT TDState (Either String)) ()
108 :: TDState :== 'Data.Map'.Map String (String, Bool)
109 typedefs :: [[Type]] -> Either String [String]
110 typedefs ts = evalStateT (execWriterT (mapM_ typedefgroup ts)) 'Data.Map'.newMap
111 where
112 typedefgroup :: [Type] -> TDMonad
113 typedefgroup ts
114 = liftT (modify ('Data.Map'.putList [(typeName ty, (prefix ty, False))\\ty<-ts]))
115 >>| mapM_ (\x->printTypeName x >>| tell [";\n"]) (if (ts=:[_,_:_]) (map typeName ts) [])
116 >>| liftT (modify (flip (foldr $ 'Data.Map'.alter (fmap (fmap \_->True)) o typeName) ts))
117 >>| mapM_ (\t->typedef t >>| tell ["\n"]) ts
118
119 printTypeName :: String -> TDMonad
120 printTypeName tname
121 = liftT (gets (\s->maybe [safe tname, " "] (\(p, b)->[p, safe tname, if b " *" " "]) $ 'Data.Map'.get tname s))
122 >>= tell
123
124 typedef :: Type -> TDMonad
125 typedef (TyRef s) = printTypeName s
126 typedef (TyBasic t) = case t of
127 BTInt = tell ["typedef uint64_t Int;\n"]
128 BTChar = tell ["typedef char Char;\n"]
129 BTReal = tell ["typedef double Real;\n"]
130 BTBool = tell ["typedef bool Bool;\n"]
131 t = fail $ "basic type: " +++ toString t +++ " not implemented"
132 typedef (TyArray _ a) = tell ["*"] >>| typedef a
133 typedef t=:(TyNewType ti ci a)
134 = tydef ti.gtd_name ci.gcd_type
135 typedef t=:(TyRecord ti fs)
136 = tell ["struct ", safe ti.grd_name, " {\n"]
137 >>| fmtFields 1 ti.grd_type [fi.gfd_name\\(fi, _)<-fs]
138 >>| tell ["};\n"]
139 //Enumeration
140 typedef t=:(TyObject ti fs)
141 | and [t =: [] \\ (_, t)<-fs] = tell
142 [consName ti, " {", 'Text'.join ", " [safe ci.gcd_name\\(ci, _)<-fs], "};\n"]
143 //Single constructor, single field (box)
144 typedef t=:(TyObject ti [(ci, [ty])]) = tydef ti.gtd_name ci.gcd_type
145 //Single constructor
146 typedef t=:(TyObject ti [(ci, ts)])
147 = tell ["struct ", safe ti.gtd_name, " {\n"]
148 >>| fmtFields 1 ci.gcd_type ["f" +++ toString i\\i<-indexList ts]
149 >>| tell ["};\n"]
150 //Complex adt
151 typedef t=:(TyObject ti fs) = tell
152 ["struct ", safe ti.gtd_name, " {\n"
153 , "\t", consName ti, " {", 'Text'.join ", " [safe ci.gcd_name\\(ci, _)<-fs], "} cons;\n"
154 , "\tstruct {\n"]
155 >>| mapM_ fmtCons fs
156 >>| tell ["\t} data;\n};\n"]
157 where
158 fmtCons :: (GenericConsDescriptor, [Type]) -> TDMonad
159 fmtCons (ci, []) = pure ()
160 fmtCons (ci, [t]) = fmtFields 2 ci.gcd_type [safe ci.gcd_name]
161 fmtCons (ci, ts) = tell ["\t\tstruct {\n"]
162 >>| fmtFields 3 ci.gcd_type ["f" +++ toString i\\i<-indexList ts]
163 >>| tell ["\t\t} ", safe ci.gcd_name, ";\n"]
164 typedef t = fail $ toString t +++ " not implemented"
165
166 tydef :: String GenType -> TDMonad
167 tydef name (GenTypeArrow l r) = tell ["typedef "] >>| fmtField "" l >>| tell [safe name,";\n"]
168
169 fmtFields :: Int GenType [String] -> TDMonad
170 fmtFields i _ [] = pure ()
171 fmtFields i (GenTypeArrow l r) [x:xs]
172 = tell [createArray i '\t'] >>| fmtField x l >>| tell [";\n"] >>| fmtFields i r xs
173
174 fmtField :: String GenType -> TDMonad
175 fmtField x (GenTypeCons a) = printTypeName a >>| tell [x]
176 fmtField x (GenTypeVar a) = tell ["void *",x]
177 fmtField x (GenTypeApp l r) = fmtField x l
178 fmtField x t=:(GenTypeArrow _ _)
179 = mapM (fmap (concat o snd) o listen o fmtField "") (collectArgs t [])
180 >>= \[r:as]->tell [r, " (*",x,")(",'Text'.join ", " as, ")"]
181 where
182 collectArgs (GenTypeArrow l r) c = collectArgs r (c ++ [l])
183 collectArgs t c = [t:c]