4
4
{-# language NamedFieldPuns #-}
5
5
{-# language OverloadedStrings #-}
6
6
{-# language TemplateHaskell #-}
7
+ {-# language ViewPatterns #-}
7
8
{-|
8
9
Description : Quasi-quoters for Protocol Buffers schemas
9
10
@@ -18,17 +19,20 @@ module Mu.Quasi.ProtoBuf (
18
19
, protobufToDecls
19
20
) where
20
21
21
- import Control.Monad (when )
22
+ import Control.Monad (when , foldM )
22
23
import Control.Monad.IO.Class
23
24
import qualified Data.ByteString as B
24
25
import Data.Int
25
26
import qualified Data.List as L
26
- import Data.List.NonEmpty (NonEmpty (.. ))
27
+ import qualified Data.Map.Strict as M
28
+ import Data.Maybe (maybe )
29
+ import Data.List.NonEmpty (NonEmpty (.. ), toList )
27
30
import qualified Data.Text as T
28
31
import Data.Word
29
32
import Language.Haskell.TH
30
33
import Language.ProtocolBuffers.Parser
31
34
import qualified Language.ProtocolBuffers.Types as P
35
+ import System.FilePath (takeDirectory , (</>) )
32
36
33
37
import Mu.Adapter.ProtoBuf
34
38
import Mu.Schema.Annotations
@@ -44,13 +48,31 @@ protobuf schemaName fp
44
48
Left e
45
49
-> fail (" could not parse protocol buffers spec: " ++ show e)
46
50
Right p
47
- -> protobufToDecls schemaName p
51
+ -> protobufToDecls schemaName p =<< loadImports fp p
52
+
53
+ loadImports :: FilePath -> P. ProtoBuf -> Q [P. ProtoBuf ]
54
+ loadImports rootFp p = M. elems <$> loadImports' M. empty rootFp p
55
+ where
56
+ loadImports' :: M. Map FilePath P. ProtoBuf -> FilePath -> P. ProtoBuf -> Q (M. Map FilePath P. ProtoBuf )
57
+ loadImports' m fp p' = foldM (loadImport fp) m $ P. imports p'
58
+ loadImport :: FilePath -> M. Map FilePath P. ProtoBuf -> (P. ImportType , T. Text ) -> Q (M. Map FilePath P. ProtoBuf )
59
+ loadImport parentFp m (_, relFP) = do
60
+ let fp = takeDirectory parentFp </> T. unpack relFP
61
+ if fp `M.member` m
62
+ then pure m
63
+ else do
64
+ r <- liftIO $ parseProtoBufFile fp
65
+ case r of
66
+ Left e -> do
67
+ reportError $ " Include " <> fp <> " of " <> parentFp <> " not found: " <> show e
68
+ pure m
69
+ Right proto -> loadImports' (M. insert fp proto m) fp proto
48
70
49
71
-- | Shared portion of Protocol Buffers and gRPC quasi-quoters.
50
- protobufToDecls :: String -> P. ProtoBuf -> Q [Dec ]
51
- protobufToDecls schemaName p
72
+ protobufToDecls :: String -> P. ProtoBuf -> [ P. ProtoBuf ] -> Q [Dec ]
73
+ protobufToDecls schemaName p imps
52
74
= do let schemaName' = mkName schemaName
53
- (schTy, annTy) <- schemaFromProtoBuf p
75
+ (schTy, annTy) <- schemaFromProtoBuf p imps
54
76
schemaDec <- tySynD schemaName' [] (pure schTy)
55
77
#if MIN_VERSION_template_haskell(2,15,0)
56
78
annDec <- tySynInstD (tySynEqn Nothing
@@ -62,29 +84,38 @@ protobufToDecls schemaName p
62
84
#endif
63
85
pure [schemaDec, annDec]
64
86
65
- schemaFromProtoBuf :: P. ProtoBuf -> Q (Type , Type )
66
- schemaFromProtoBuf P. ProtoBuf {P. types = tys} = do
67
- let decls = flattenDecls ((" " , tys) :| [] ) tys
87
+ schemaFromProtoBuf :: P. ProtoBuf -> [ P. ProtoBuf ] -> Q (Type , Type )
88
+ schemaFromProtoBuf P. ProtoBuf {P. types = tys} imps = do
89
+ let decls = flattenDecls ((" " , tys) :| [] ) tys <> flattenImportDecls imps
68
90
(schTys, anns) <- unzip <$> mapM (pbTypeDeclToType $ shouldOptional decls) decls
69
91
pure (typesToList schTys, typesToList (concat anns))
70
92
where
71
93
shouldOptional :: [P. TypeDeclaration ] -> P. TypeName -> Bool
72
- shouldOptional [] _ = error " this should never happen "
94
+ shouldOptional [] this = error $ T. unpack $ " no declaration for type " <> T. intercalate " . " this
73
95
shouldOptional (P. DMessage nm _ _ _ _ : _) this
74
96
| nm == last this = True
75
97
shouldOptional (P. DEnum nm _ _ : _) this
76
98
| nm == last this = False
77
99
shouldOptional (_ : rest) this
78
100
= shouldOptional rest this
79
101
102
+ flattenImportDecls :: [P. ProtoBuf ] -> [P. TypeDeclaration ]
103
+ flattenImportDecls = concatMap flattenImportDecls'
104
+ where
105
+ flattenImportDecls' :: P. ProtoBuf -> [P. TypeDeclaration ]
106
+ flattenImportDecls' P. ProtoBuf { P. types = tys, P. package = getPackageName -> pkg } =
107
+ flattenDecls ((pkg, tys) :| [] ) tys
108
+ getPackageName :: Maybe P. FullIdentifier -> T. Text
109
+ getPackageName = maybe " " (T. intercalate " ." )
110
+
80
111
flattenDecls :: NonEmpty (P. Identifier , [P. TypeDeclaration ]) -> [P. TypeDeclaration ] -> [P. TypeDeclaration ]
81
112
flattenDecls (currentScope :| higherScopes) = concatMap flattenDecl
82
113
where
83
114
flattenDecl (P. DEnum name o f) = [P. DEnum (prependCurrentScope name) o f]
84
115
flattenDecl (P. DMessage name o r fs decls) =
85
116
let newScopeName = prependCurrentScope name
86
117
newScopes = (newScopeName, decls) :| (currentScope : higherScopes)
87
- in P. DMessage newScopeName o r (scopeFieldType newScopes <$> fs) [] : flattenDecls newScopes decls
118
+ in P. DMessage newScopeName o r (scopeFieldType (toList newScopes) <$> fs) [] : flattenDecls newScopes decls
88
119
89
120
scopeFieldType scopes (P. NormalField frep ftype fname fnum fopts) =
90
121
P. NormalField frep (qualifyType scopes ftype) fname fnum fopts
@@ -95,17 +126,15 @@ flattenDecls (currentScope :| higherScopes) = concatMap flattenDecl
95
126
qualifyType scopes (P. TOther ts) = P. TOther (qualifyTOther scopes ts)
96
127
qualifyType _scopes t = t
97
128
98
- qualifyTOther _scopes [] = error " This shouldn't be possible"
99
- qualifyTOther ((_, _) :| [] ) ts =
100
- [T. intercalate " ." ts] -- Top level scope, no need to search anything, use
101
- -- the name as is. Maybe we should search and fail
102
- -- if a type is not found even from top level, but
103
- -- that could be a lot of work as this function is
104
- -- pure right now.
105
- qualifyTOther ((scopeName, decls) :| (restFirst : restTail)) ts =
129
+ qualifyTOther _ [] = error " This shouldn't be possible"
130
+ qualifyTOther [] ts = [T. intercalate " ." ts]
131
+ qualifyTOther ((scopeName, decls) : rest) ts =
106
132
if L. any (hasDeclFor ts) decls
107
- then [T. intercalate " ." (scopeName: ts)]
108
- else qualifyTOther (restFirst :| restTail) ts
133
+ then [qualifyName scopeName ts]
134
+ else qualifyTOther rest ts
135
+ where
136
+ qualifyName " " ts = T. intercalate " ." ts
137
+ qualifyName scopeName ts = qualifyName " " (scopeName: ts)
109
138
110
139
hasDeclFor [] _ = True
111
140
hasDeclFor [t] (P. DEnum enumName _ _) = t == enumName
@@ -120,7 +149,7 @@ flattenDecls (currentScope :| higherScopes) = concatMap flattenDecl
120
149
prependCurrentScope x =
121
150
case fst currentScope of
122
151
" " -> x
123
- _ -> fst currentScope <> " ." <> x
152
+ sn -> sn <> " ." <> x
124
153
125
154
pbTypeDeclToType :: (P. TypeName -> Bool ) -> P. TypeDeclaration -> Q (Type , [Type ])
126
155
pbTypeDeclToType _ (P. DEnum name _ fields) = do
@@ -179,7 +208,7 @@ pbTypeDeclToType shouldOptional (P.DMessage name _ _ fields _) = do
179
208
pbFieldTypeToType P. TBool = [t |'TPrimitive Bool|]
180
209
pbFieldTypeToType P. TString = [t |'TPrimitive T.Text|]
181
210
pbFieldTypeToType P. TBytes = [t |'TPrimitive B.ByteString|]
182
- pbFieldTypeToType (P. TOther t) = [t |'TSchematic $(textToStrLit (last t))|]
211
+ pbFieldTypeToType (P. TOther t) = [t |'TSchematic $(textToStrLit (T.intercalate "." t))|]
183
212
184
213
hasFieldNumber P. NormalField {} = True
185
214
hasFieldNumber P. MapField {} = True
0 commit comments