|
1 |
| -{-# LANGUAGE ExistentialQuantification #-} |
2 |
| -{-# LANGUAGE FlexibleContexts #-} |
3 |
| -{-# LANGUAGE FlexibleInstances #-} |
4 |
| -{-# LANGUAGE LambdaCase #-} |
5 |
| -{-# LANGUAGE MultiParamTypeClasses #-} |
6 | 1 | {-# LANGUAGE RankNTypes #-}
|
7 |
| -{-# LANGUAGE TypeApplications #-} |
8 | 2 | {-# LANGUAGE UndecidableInstances #-}
|
9 | 3 | module Analysis.Syntax
|
10 |
| -( -- * Terms |
| 4 | +( -- * Syntax |
11 | 5 | Term(..)
|
12 | 6 | , subterms
|
13 |
| - -- * Abstract interpretation |
14 |
| -, eval0 |
15 |
| -, eval |
16 |
| - -- * Macro-expressible syntax |
17 |
| -, let' |
18 |
| -, letrec |
19 |
| - -- * Parsing |
20 |
| -, parseFile |
21 |
| -, parseGraph |
22 |
| -, parseNode |
23 |
| - -- * Debugging |
24 |
| -, analyzeFile |
25 |
| -, parseToTerm |
| 7 | +, foldTerm |
| 8 | +, paraTerm |
| 9 | +, mendlerTerm |
| 10 | +, mendlerParaTerm |
26 | 11 | ) where
|
27 | 12 |
|
28 |
| -import qualified Analysis.Carrier.Statement.State as S |
29 |
| -import Analysis.Effect.Domain |
30 |
| -import Analysis.Effect.Env (Env, bind, lookupEnv) |
31 |
| -import Analysis.Effect.Store |
32 |
| -import Analysis.File |
33 |
| -import Analysis.Name (Name, name) |
34 |
| -import Analysis.Reference as Ref |
35 |
| -import Control.Applicative (Alternative (..), liftA2, liftA3) |
36 |
| -import Control.Carrier.Throw.Either (runThrow) |
37 |
| -import Control.Effect.Labelled |
38 |
| -import Control.Effect.Reader |
39 |
| -import Control.Effect.Throw (Throw, throwError) |
40 |
| -import Control.Exception |
41 |
| -import Control.Monad (guard) |
42 |
| -import Control.Monad.IO.Class |
43 |
| -import qualified Data.Aeson as A |
44 |
| -import qualified Data.Aeson.Parser as A |
45 |
| -import qualified Data.Aeson.Types as A |
46 |
| -import qualified Data.ByteString.Lazy as B |
47 |
| -import Data.Foldable (fold, foldl') |
48 |
| -import Data.Function (fix) |
49 |
| -import qualified Data.IntMap as IntMap |
50 |
| -import Data.List (sortOn) |
51 |
| -import Data.List.NonEmpty (NonEmpty, fromList) |
52 |
| -import Data.Maybe (listToMaybe) |
53 |
| -import Data.Monoid (First (..)) |
54 | 13 | import qualified Data.Set as Set
|
55 |
| -import Data.String (IsString (..)) |
56 |
| -import Data.Text (Text) |
57 |
| -import qualified Data.Vector as V |
58 |
| -import qualified Source.Source as Source |
59 |
| -import Source.Span |
60 |
| -import System.FilePath |
61 | 14 |
|
62 |
| -data Term |
63 |
| - = Var Name |
64 |
| - | Noop |
65 |
| - | Iff Term Term Term |
66 |
| - | Bool Bool |
67 |
| - | String Text |
68 |
| - | Throw Term |
69 |
| - | Let Name Term Term |
70 |
| - | Term :>> Term |
71 |
| - | Import (NonEmpty Text) |
72 |
| - | Function Name [Name] Term |
73 |
| - | Call Term [Term] |
74 |
| - | Locate Span Term |
75 |
| - deriving (Eq, Ord, Show) |
| 15 | +-- Syntax |
76 | 16 |
|
77 |
| -infixl 1 :>> |
| 17 | +-- | (Currently) untyped term representations. |
| 18 | +data Term sig v |
| 19 | + = Var v |
| 20 | + | Term (sig (Term sig v)) |
78 | 21 |
|
79 |
| -subterms :: Term -> Set.Set Term |
80 |
| -subterms t = Set.singleton t <> case t of |
81 |
| - Var _ -> mempty |
82 |
| - Noop -> mempty |
83 |
| - Iff c t e -> subterms c <> subterms t <> subterms e |
84 |
| - Bool _ -> mempty |
85 |
| - String _ -> mempty |
86 |
| - Throw t -> subterms t |
87 |
| - Let _ v b -> subterms v <> subterms b |
88 |
| - a :>> b -> subterms a <> subterms b |
89 |
| - Import _ -> mempty |
90 |
| - Function _ _ b -> subterms b |
91 |
| - Call f as -> subterms f <> foldMap subterms as |
92 |
| - Locate _ b -> subterms b |
| 22 | +instance (Eq (sig (Term sig v)), Eq v) => Eq (Term sig v) where |
| 23 | + Var v1 == Var v2 = v1 == v2 |
| 24 | + Term s1 == Term s2 = s1 == s2 |
| 25 | + _ == _ = False |
93 | 26 |
|
| 27 | +instance (Ord (sig (Term sig v)), Ord v) => Ord (Term sig v) where |
| 28 | + compare (Var v1) (Var v2) = compare v1 v2 |
| 29 | + compare (Var _) _ = LT |
| 30 | + compare (Term s1) (Term s2) = compare s1 s2 |
| 31 | + compare _ _ = GT |
94 | 32 |
|
95 |
| --- Abstract interpretation |
96 | 33 |
|
97 |
| -eval0 :: (Has (Env addr) sig m, HasLabelled Store (Store addr val) sig m, Has (Dom val) sig m, Has (Reader Reference) sig m, Has S.Statement sig m) => Term -> m val |
98 |
| -eval0 = fix eval |
| 34 | +subterms :: (Ord (sig (Term sig v)), Ord v, Foldable sig) => Term sig v -> Set.Set (Term sig v) |
| 35 | +subterms = mendlerParaTerm (Set.singleton . Var) (\ k -> foldMap (uncurry Set.insert . k)) |
99 | 36 |
|
100 |
| -eval |
101 |
| - :: (Has (Env addr) sig m, HasLabelled Store (Store addr val) sig m, Has (Dom val) sig m, Has (Reader Reference) sig m, Has S.Statement sig m) |
102 |
| - => (Term -> m val) |
103 |
| - -> (Term -> m val) |
104 |
| -eval eval = \case |
105 |
| - Var n -> lookupEnv n >>= maybe (dvar n) fetch |
106 |
| - Noop -> dunit |
107 |
| - Iff c t e -> do |
108 |
| - c' <- eval c |
109 |
| - dif c' (eval t) (eval e) |
110 |
| - Bool b -> dbool b |
111 |
| - String s -> dstring s |
112 |
| - Throw e -> eval e >>= ddie |
113 |
| - Let n v b -> do |
114 |
| - v' <- eval v |
115 |
| - let' n v' (eval b) |
116 |
| - t :>> u -> do |
117 |
| - t' <- eval t |
118 |
| - u' <- eval u |
119 |
| - t' >>> u' |
120 |
| - Import ns -> S.simport ns >> dunit |
121 |
| - Function n ps b -> letrec n (dabs ps (foldr (\ (p, a) m -> let' p a m) (eval b) . zip ps)) |
122 |
| - Call f as -> do |
123 |
| - f' <- eval f |
124 |
| - as' <- traverse eval as |
125 |
| - dapp f' as' |
126 |
| - Locate s t -> local (setSpan s) (eval t) |
127 |
| - where |
128 |
| - setSpan s r = r{ refSpan = s } |
129 |
| - |
130 |
| - |
131 |
| --- Macro-expressible syntax |
132 |
| - |
133 |
| -let' :: (Has (Env addr) sig m, HasLabelled Store (Store addr val) sig m) => Name -> val -> m a -> m a |
134 |
| -let' n v m = do |
135 |
| - addr <- alloc n |
136 |
| - addr .= v |
137 |
| - bind n addr m |
138 |
| - |
139 |
| -letrec :: (Has (Env addr) sig m, HasLabelled Store (Store addr val) sig m) => Name -> m val -> m val |
140 |
| -letrec n m = do |
141 |
| - addr <- alloc n |
142 |
| - v <- bind n addr m |
143 |
| - addr .= v |
144 |
| - pure v |
145 |
| - |
146 |
| - |
147 |
| --- Parsing |
148 |
| - |
149 |
| -parseFile :: (Has (Throw String) sig m, MonadIO m) => FilePath -> FilePath -> m (Source.Source, File Term) |
150 |
| -parseFile srcPath jsonPath = do |
151 |
| - contents <- liftIO (B.readFile jsonPath) |
152 |
| - -- FIXME: get this from the JSON itself (cf https://github.com/tree-sitter/tree-sitter-graph/issues/69) |
153 |
| - let sourcePath = replaceExtensions jsonPath "py" |
154 |
| - sourceContents <- Source.fromUTF8 . B.toStrict <$> liftIO (B.readFile srcPath) |
155 |
| - let span = decrSpan (Source.totalSpan sourceContents) |
156 |
| - case A.eitherDecodeWith A.json' (A.iparse parseGraph) contents of |
157 |
| - Left (_, err) -> throwError err |
158 |
| - Right (_, Nothing) -> throwError "no root node found" |
159 |
| - Right (_, Just root) -> pure (sourceContents, File (Reference sourcePath span) root) |
160 |
| - where |
161 |
| - decrSpan (Span (Pos sl sc) (Pos el ec)) = Span (Pos (sl - 1) (sc - 1)) (Pos (el - 1) (ec - 1)) |
162 |
| - |
163 |
| -newtype Graph = Graph { terms :: IntMap.IntMap Term } |
164 |
| - |
165 |
| --- | Parse a @Value@ into an entire graph of terms, as well as a root node, if any exists. |
166 |
| -parseGraph :: A.Value -> A.Parser (Graph, Maybe Term) |
167 |
| -parseGraph = A.withArray "nodes" $ \ nodes -> do |
168 |
| - (untied, First root) <- fold <$> traverse parseNode (V.toList nodes) |
169 |
| - -- @untied@ is an intmap, where the keys are graph node IDs and the values are functions from the final graph to the representations of said graph nodes. Likewise, @root@ is a function of the same variety, wrapped in a @Maybe@. |
170 |
| - -- |
171 |
| - -- We define @tied@ as the fixpoint of the former to yield the former as a graph of type @Graph@, and apply the latter to said graph to yield the entry point, if any, from which to evaluate. |
172 |
| - let tied = fix (\ tied -> ($ Graph tied) <$> untied) |
173 |
| - pure (Graph tied, ($ Graph tied) <$> root) |
| 37 | +foldTerm :: Functor sig => (v -> r) -> (sig r -> r) -> (Term sig v -> r) |
| 38 | +foldTerm var sig = mendlerTerm var (\ k -> sig . fmap k) |
174 | 39 |
|
175 |
| --- | Parse a node from a JSON @Value@ into a pair of a partial graph of unfixed terms and optionally an unfixed term representing the root node. |
176 |
| --- |
177 |
| --- The partial graph is represented as an adjacency map relating node IDs to unfixed terms—terms which may make reference to a completed graph to find edges, and which therefore can't be inspected until the full graph is known. |
178 |
| -parseNode :: A.Value -> A.Parser (IntMap.IntMap (Graph -> Term), First (Graph -> Term)) |
179 |
| -parseNode = A.withObject "node" $ \ o -> do |
180 |
| - edges <- o A..: fromString "edges" |
181 |
| - index <- o A..: fromString "id" |
182 |
| - o A..: fromString "attrs" >>= A.withObject "attrs" (\ attrs -> do |
183 |
| - ty <- attrs A..: fromString "type" |
184 |
| - node <- parseTerm attrs edges ty |
185 |
| - pure (IntMap.singleton index node, node <$ First (guard (ty == "module")))) |
| 40 | +paraTerm :: Functor sig => (v -> r) -> (sig (Term sig v, r) -> r) -> (Term sig v -> r) |
| 41 | +paraTerm var sig = mendlerParaTerm var (\ k -> sig . fmap k) |
186 | 42 |
|
187 |
| -parseTerm :: A.Object -> [A.Value] -> String -> A.Parser (Graph -> Term) |
188 |
| -parseTerm attrs edges = locate attrs . \case |
189 |
| - "string" -> const . String <$> attrs A..: fromString "text" |
190 |
| - "true" -> pure (const (Bool True)) |
191 |
| - "false" -> pure (const (Bool False)) |
192 |
| - "throw" -> fmap Throw <$> maybe empty resolve (listToMaybe edges) |
193 |
| - "if" -> liftA3 Iff <$> findEdgeNamed edges "condition" <*> findEdgeNamed edges "consequence" <*> findEdgeNamed edges "alternative" <|> pure (const Noop) |
194 |
| - "block" -> children edges |
195 |
| - "module" -> children edges |
196 |
| - "identifier" -> const . Var . name <$> attrs A..: fromString "text" |
197 |
| - "import" -> const . Import . fromList . map snd . sortOn fst <$> traverse (resolveWith (const moduleNameComponent)) edges |
198 |
| - "function" -> liftA3 Function . pure . name <$> attrs A..: fromString "name" <*> pure (pure []) <*> findEdgeNamed edges "body" |
199 |
| - "call" -> liftA2 Call . const . Var . name <$> attrs A..: fromString "function" <*> (sequenceA <$> traverse resolve edges) |
200 |
| - "noop" -> pure (pure Noop) |
201 |
| - t -> A.parseFail ("unrecognized type: " <> t <> " attrs: " <> show attrs <> " edges: " <> show edges) |
202 |
| - |
203 |
| -findEdgeNamed :: (Foldable t, A.FromJSON a, Eq a) => t A.Value -> a -> A.Parser (Graph -> Term) |
204 |
| -findEdgeNamed edges name = foldMap (resolveWith (\ rep attrs -> attrs A..: fromString "type" >>= (rep <$) . guard . (== name))) edges |
205 |
| - |
206 |
| --- | Map a list of edges to a list of child nodes. |
207 |
| -children :: [A.Value] -> A.Parser (Graph -> Term) |
208 |
| -children edges = fmap chain . traverse snd . sortOn fst <$> traverse (resolveWith child) edges |
| 43 | +mendlerTerm :: (v -> r) -> (forall r' . (r' -> r) -> sig r'-> r) -> (Term sig v -> r) |
| 44 | +mendlerTerm var sig = go |
209 | 45 | where
|
210 |
| - child :: (Graph -> Term) -> A.Object -> A.Parser (Int, Graph -> Term) |
211 |
| - child term attrs = (,) <$> attrs A..: fromString "index" <*> pure term |
212 |
| - |
213 |
| - chain :: [Term] -> Term |
214 |
| - chain [] = Noop |
215 |
| - chain (t:ts) = foldl' (:>>) t ts |
216 |
| - |
217 |
| -moduleNameComponent :: A.Object -> A.Parser (Int, Text) |
218 |
| -moduleNameComponent attrs = (,) <$> attrs A..: fromString "index" <*> attrs A..: fromString "text" |
219 |
| - |
220 |
| -resolve :: A.Value -> A.Parser (Graph -> Term) |
221 |
| -resolve = resolveWith (const . pure) |
222 |
| - |
223 |
| -resolveWith :: ((Graph -> Term) -> A.Object -> A.Parser a) -> A.Value -> A.Parser a |
224 |
| -resolveWith f = resolveWith' (f . flip ((IntMap.!) . terms)) |
| 46 | + go (Var v) = var v |
| 47 | + go (Term s) = sig go s |
225 | 48 |
|
226 |
| -resolveWith' :: (IntMap.Key -> A.Object -> A.Parser a) -> A.Value -> A.Parser a |
227 |
| -resolveWith' f = A.withObject "edge" (\ edge -> do |
228 |
| - sink <- edge A..: fromString "sink" |
229 |
| - attrs <- edge A..: fromString "attrs" |
230 |
| - f sink attrs) |
231 |
| - |
232 |
| -locate :: A.Object -> A.Parser (Graph -> Term) -> A.Parser (Graph -> Term) |
233 |
| -locate attrs p = do |
234 |
| - span <- span |
235 |
| - <$> attrs A..:? fromString "start-line" |
236 |
| - <*> attrs A..:? fromString "start-col" |
237 |
| - <*> attrs A..:? fromString "end-line" |
238 |
| - <*> attrs A..:? fromString "end-col" |
239 |
| - t <- p |
240 |
| - case span of |
241 |
| - Nothing -> pure t |
242 |
| - Just s -> pure (Locate s <$> t) |
| 49 | +mendlerParaTerm :: (v -> r) -> (forall r' . (r' -> (Term sig v, r)) -> sig r'-> r) -> (Term sig v -> r) |
| 50 | +mendlerParaTerm var sig = go |
243 | 51 | where
|
244 |
| - span sl sc el ec = Span <$> (Pos <$> sl <*> sc) <*> (Pos <$> el <*> ec) |
245 |
| - |
246 |
| - |
247 |
| --- Debugging |
248 |
| - |
249 |
| -analyzeFile |
250 |
| - :: (Algebra sig m, MonadIO m) |
251 |
| - => FilePath |
252 |
| - -> FilePath |
253 |
| - -> ( forall term |
254 |
| - . Ord term |
255 |
| - => ( forall sig m |
256 |
| - . (Has (Env addr) sig m, HasLabelled Store (Store addr val) sig m, Has (Dom val) sig m, Has (Reader Reference) sig m, Has S.Statement sig m) |
257 |
| - => (term -> m val) |
258 |
| - -> (term -> m val) ) |
259 |
| - -> Source.Source |
260 |
| - -> File term |
261 |
| - -> m b ) |
262 |
| - -> m b |
263 |
| -analyzeFile srcPath jsonPath analyze = do |
264 |
| - (src, file) <- parseToTerm srcPath jsonPath |
265 |
| - analyze eval src file |
266 |
| - |
267 |
| -parseToTerm :: (Algebra sig m, MonadIO m) => FilePath -> FilePath -> m (Source.Source, File Term) |
268 |
| -parseToTerm srcPath jsonPath = do |
269 |
| - parsed <- runThrow @String (parseFile srcPath jsonPath) |
270 |
| - either (liftIO . throwIO . ErrorCall) pure parsed |
| 52 | + go (Var v) = var v |
| 53 | + go (Term s) = sig ((,) <*> go) s |
0 commit comments