Add basic code completion mechanism

This commit is contained in:
Kirill Andreev 2020-08-05 20:31:54 +04:00
parent 08a0eb55d1
commit 107018e6f3
No known key found for this signature in database
GPG Key ID: CF7DA79DE4785A47
9 changed files with 82 additions and 17 deletions

View File

@ -4,7 +4,8 @@
module AST (module M) where
import AST.Types as M
import AST.Parser as M
import AST.Scope as M
import AST.Find as M
import AST.Types as M
import AST.Parser as M
import AST.Scope as M
import AST.Find as M
import AST.Completion as M

View File

@ -0,0 +1,52 @@
module AST.Completion where
import Data.Text (Text)
import qualified Data.Text as Text
import Data.Maybe (listToMaybe)
import Data.List (isSubsequenceOf, nub)
import Duplo.Tree
import Duplo.Lattice
import Duplo.Pretty
import AST.Types
import AST.Scope
import AST.Parser
import Range
import Product
import Debug.Trace
complete
:: ( Eq (Product xs)
, Modifies (Product xs)
, Contains Range xs
, Contains [ScopedDecl] xs
, Contains (Maybe Category) xs
)
=> Range
-> LIGO (Product xs)
-> Maybe [Text]
complete r tree = do
let l = spineTo (leq r . getElem) tree
word <- listToMaybe l
let scope = getElem (extract word)
let cat = getElem (extract word)
return
$ filter (isSubseqOf (ppToText word))
$ nub
$ map (ppToText . _sdName)
$ filter (fits cat . catFromType)
$ scope
isSubseqOf :: Text -> Text -> Bool
isSubseqOf l r = isSubsequenceOf (Text.unpack l) (Text.unpack r)
fits :: Maybe Category -> Category -> Bool
fits Nothing _ = True
fits (Just c) c' = c == c'
catFromType :: ScopedDecl -> Category
catFromType = maybe Variable (either (const Variable) (const Type)) . _sdType

View File

@ -0,0 +1,3 @@
module AST.Folding where

View File

@ -45,7 +45,8 @@ import Debug.Trace
-- example = "../../../src/test/contracts/blockless.ligo"
-- example = "../../../src/test/contracts/bytes_arithmetic.ligo"
-- example = "../../../src/test/contracts/chain_id.ligo"
example = "../../../src/test/contracts/closure-3.ligo"
-- example = "../../../src/test/contracts/closure-3.ligo"
example = "../../../src/test/contracts/coase.ligo"
sample' :: FilePath -> IO (LIGO Info)
sample' f

View File

@ -102,11 +102,11 @@ ofCategory _ _ = False
type Info' = Product [[ScopedDecl], Maybe Category, [Text], Range, ShowRange]
instance Modifies (Product '[[ScopedDecl], Maybe Category, [Text], Range, a]) where
ascribe (ds :> _ :> _ :> r :> _) d =
color 3 (fsep (map (pp . _sdName) ds))
$$ pp r
$$ d
-- instance Modifies (Product '[[ScopedDecl], Maybe Category, [Text], Range, a]) where
-- ascribe (ds :> _ :> _ :> r :> _) d =
-- color 3 (fsep (map (pp . _sdName) ds))
-- $$ pp r
-- $$ d
addLocalScopes
:: forall xs

View File

@ -70,7 +70,7 @@ srcToBytestring = \case
type RawTree = Tree '[ParseTree] RawInfo
type RawInfo = Product [Range, Text]
instance Modifies RawInfo where
instance {-# OVERLAPS #-} Modifies RawInfo where
ascribe (r :> n :> _) d = color 3 (pp n) <+> pp r `indent` pp d
-- | The tree tree-sitter produces.

View File

@ -111,8 +111,16 @@ instance Pretty ShowRange where
type Info = Product [[Text], Range, ShowRange]
type PreInfo = Product [Range, ShowRange]
instance Modifies Info where
ascribe (comms :> r :> pin :> _) = ascribeRange r pin . ascribeComms comms
instance
( Contains Range xs
, Contains [Text] xs
, Contains ShowRange xs
)
=> Modifies (Product xs)
where
ascribe xs
= ascribeRange (getElem @Range xs) (getElem xs)
. ascribeComms (getElem xs)
ascribeComms comms
| null comms = id

View File

@ -15,7 +15,7 @@ extra-deps:
- semilattices-0.0.0.4@sha256:333707e460923711d1edbdd02ebe1c3957d4e0808eab9886747b52ee3e443639,1909
- fastsum-0.1.1.1
- git: https://github.com/serokell/duplo.git
commit: 0cc243e90bc497989ec48417a6b5a5ce6a01759f
commit: 60983e6e1fd21eba57af83da7d541fe555678cc8
nix:
packages: [zlib]

View File

@ -45,11 +45,11 @@ packages:
git: https://github.com/serokell/duplo.git
pantry-tree:
size: 557
sha256: e8618a84baa4c24a1cabc47008cc12bbb7bd52b6fd8acaff6c4871201509c2ac
commit: 0cc243e90bc497989ec48417a6b5a5ce6a01759f
sha256: b00e0db1d2c3c0db58e90a69415f6cdc4d416ff6e50789f2de841fc60e2f2ffb
commit: 60983e6e1fd21eba57af83da7d541fe555678cc8
original:
git: https://github.com/serokell/duplo.git
commit: 0cc243e90bc497989ec48417a6b5a5ce6a01759f
commit: 60983e6e1fd21eba57af83da7d541fe555678cc8
snapshots:
- completed:
size: 493124