Update AST.Scope to new framework
This commit is contained in:
parent
226b7264aa
commit
6bd5d9ef84
@ -24,6 +24,8 @@ import Language.Haskell.LSP.VFS
|
|||||||
import System.Exit
|
import System.Exit
|
||||||
import qualified System.Log as L
|
import qualified System.Log as L
|
||||||
|
|
||||||
|
import Duplo.Pretty
|
||||||
|
|
||||||
import Parser
|
import Parser
|
||||||
import ParseTree
|
import ParseTree
|
||||||
import Range
|
import Range
|
||||||
@ -36,7 +38,7 @@ main :: IO ()
|
|||||||
main = do
|
main = do
|
||||||
return ()
|
return ()
|
||||||
for_ [1.. 100] \_ -> do
|
for_ [1.. 100] \_ -> do
|
||||||
print . length . show =<< sample' "../../../src/test/contracts/loop.ligo"
|
print . length . show . pp =<< sample' "../../../src/test/contracts/loop.ligo"
|
||||||
-- errCode <- mainLoop
|
-- errCode <- mainLoop
|
||||||
-- exit errCode
|
-- exit errCode
|
||||||
|
|
||||||
|
@ -47,11 +47,11 @@ import Debug.Trace
|
|||||||
-- example = "../../../src/test/contracts/chain_id.ligo"
|
-- example = "../../../src/test/contracts/chain_id.ligo"
|
||||||
example = "../../../src/test/contracts/closure-3.ligo"
|
example = "../../../src/test/contracts/closure-3.ligo"
|
||||||
|
|
||||||
sample' :: FilePath -> IO Doc
|
sample' :: FilePath -> IO (LIGO Info)
|
||||||
sample' f
|
sample' f
|
||||||
= toParseTree (Path f)
|
= toParseTree (Path f)
|
||||||
>>= runParserM . recognise
|
>>= runParserM . recognise
|
||||||
>>= return . pp . fst
|
>>= return . fst
|
||||||
|
|
||||||
source' :: FilePath -> IO ()
|
source' :: FilePath -> IO ()
|
||||||
source' f
|
source' f
|
||||||
@ -70,7 +70,7 @@ source
|
|||||||
>>= print . pp
|
>>= print . pp
|
||||||
|
|
||||||
recognise :: RawTree -> ParserM (LIGO Info)
|
recognise :: RawTree -> ParserM (LIGO Info)
|
||||||
recognise = descent (error . show . pp . fst) $ map usingScope
|
recognise = descent (\_ -> error . show . pp) $ map usingScope
|
||||||
[ -- Contract
|
[ -- Contract
|
||||||
Descent
|
Descent
|
||||||
[ boilerplate \case
|
[ boilerplate \case
|
||||||
|
@ -13,7 +13,7 @@ module AST.Scope
|
|||||||
-- )
|
-- )
|
||||||
where
|
where
|
||||||
|
|
||||||
import Control.Arrow (second)
|
import Control.Arrow (first, second)
|
||||||
import Control.Monad.State
|
import Control.Monad.State
|
||||||
|
|
||||||
import qualified Data.List as List
|
import qualified Data.List as List
|
||||||
@ -26,11 +26,12 @@ import Data.Text (Text)
|
|||||||
import Duplo.Lattice
|
import Duplo.Lattice
|
||||||
import Duplo.Pretty
|
import Duplo.Pretty
|
||||||
import Duplo.Tree
|
import Duplo.Tree
|
||||||
|
import Duplo.Error
|
||||||
|
|
||||||
-- import AST.Parser
|
import AST.Parser
|
||||||
import AST.Types
|
import AST.Types
|
||||||
-- import Comment
|
-- import Comment
|
||||||
-- import Parser
|
import Parser
|
||||||
import Product
|
import Product
|
||||||
import Range
|
import Range
|
||||||
|
|
||||||
@ -42,6 +43,7 @@ type FullEnv = Product ["vars" := Env, "types" := Env]
|
|||||||
type Env = Map Range [ScopedDecl]
|
type Env = Map Range [ScopedDecl]
|
||||||
|
|
||||||
data Category = Variable | Type
|
data Category = Variable | Type
|
||||||
|
deriving Eq
|
||||||
|
|
||||||
-- | The type/value declaration.
|
-- | The type/value declaration.
|
||||||
data ScopedDecl = ScopedDecl
|
data ScopedDecl = ScopedDecl
|
||||||
@ -88,65 +90,74 @@ ofCategory Variable _ = True
|
|||||||
ofCategory Type ScopedDecl { _sdType = Just (Right Star) } = True
|
ofCategory Type ScopedDecl { _sdType = Just (Right Star) } = True
|
||||||
ofCategory _ _ = False
|
ofCategory _ _ = False
|
||||||
|
|
||||||
-- addLocalScopes
|
instance Modifies (Product '[[ScopedDecl], Maybe Category, [Text], Range, a]) where
|
||||||
-- :: Contains Range xs
|
ascribe (ds :> _) d =
|
||||||
-- => LIGO (Product xs)
|
color 2 (fsep (map (pp . _sdName) ds))
|
||||||
-- -> LIGO (Product ([ScopedDecl] : Maybe Category : xs))
|
$$ d
|
||||||
-- addLocalScopes tree =
|
|
||||||
-- fmap (\xs -> Cons (fullEnvAt envWithREfs (getRange xs)) xs) tree1
|
|
||||||
-- where
|
|
||||||
-- tree1 = addNameCategories tree
|
|
||||||
-- envWithREfs = getEnvTree tree
|
|
||||||
|
|
||||||
-- addNameCategories
|
addLocalScopes
|
||||||
-- :: Contains Range xs
|
:: (Contains Range xs, Eq (Product xs))
|
||||||
-- => LIGO (Product xs)
|
=> LIGO (Product xs)
|
||||||
-- -> LIGO (Product (Maybe Category : xs))
|
-> LIGO (Product ([ScopedDecl] : Maybe Category : xs))
|
||||||
-- addNameCategories tree = flip evalState emptyEnv do
|
addLocalScopes tree =
|
||||||
-- traverseMany
|
fmap (\xs -> fullEnvAt envWithREfs (getRange xs) :> xs) tree1
|
||||||
-- [ Visit \r (Name t) -> do
|
where
|
||||||
-- modify $ getRange r `addRef` (Variable, t)
|
tree1 = addNameCategories tree
|
||||||
-- return $ (Cons (Just Variable) r, Name t)
|
envWithREfs = getEnvTree tree
|
||||||
|
|
||||||
-- , Visit \r (TypeName t) -> do
|
addNameCategories
|
||||||
-- modify $ getRange r `addRef` (Type, t)
|
:: (Contains Range xs, Eq (Product xs))
|
||||||
-- return $ (Cons (Just Type) r, TypeName t)
|
=> LIGO (Product xs)
|
||||||
-- ]
|
-> LIGO (Product (Maybe Category : xs))
|
||||||
-- (Cons Nothing)
|
addNameCategories tree = flip evalState emptyEnv do
|
||||||
-- tree
|
descent (changeInfo (Nothing :>))
|
||||||
|
[ Descent
|
||||||
|
[ \(r, Name t) -> do
|
||||||
|
-- modify $ getRange r `addRef` (Variable, t)
|
||||||
|
return $ Just $ (Just Variable :> r, Name t)
|
||||||
|
]
|
||||||
|
|
||||||
-- getEnvTree
|
, Descent
|
||||||
-- :: ( Apply (Scoped b CollectM (Tree fs b)) fs
|
[ \(r, TypeName t) -> do
|
||||||
-- , Apply Foldable fs
|
-- modify $ getRange r `addRef` (Type, t)
|
||||||
-- , Apply Functor fs
|
return $ Just $ (Just Type :> r, TypeName t)
|
||||||
-- , Apply Traversable fs
|
]
|
||||||
-- , HasRange b
|
]
|
||||||
-- , Element Name fs
|
tree
|
||||||
-- , Element TypeName fs
|
|
||||||
-- )
|
|
||||||
-- => Tree fs b
|
|
||||||
-- -> FullEnv
|
|
||||||
-- getEnvTree tree = envWithREfs
|
|
||||||
-- where
|
|
||||||
-- envWithREfs = flip execState env do
|
|
||||||
-- descent return
|
|
||||||
-- [ usingScope $ Descent
|
|
||||||
-- [ \(r, Name t) -> do
|
|
||||||
-- modify $ getRange r `addRef` (Variable, t)
|
|
||||||
-- return $ (r, Name t)
|
|
||||||
-- ]
|
|
||||||
|
|
||||||
-- , usingScope $ Descent
|
getEnvTree
|
||||||
-- [ \(r, TypeName t) -> do
|
:: ( Apply (Scoped b CollectM (Tree fs b)) fs
|
||||||
-- modify $ getRange r `addRef` (Type, t)
|
, Apply Foldable fs
|
||||||
-- return $ (r, TypeName t)
|
, Apply Functor fs
|
||||||
-- ]
|
, Apply Traversable fs
|
||||||
-- ]
|
, Lattice b
|
||||||
-- tree
|
, HasRange b
|
||||||
|
, Element Name fs
|
||||||
|
, Element TypeName fs
|
||||||
|
)
|
||||||
|
=> Tree fs b
|
||||||
|
-> FullEnv
|
||||||
|
getEnvTree tree = envWithREfs
|
||||||
|
where
|
||||||
|
envWithREfs = flip execState env do
|
||||||
|
descent leaveBe
|
||||||
|
[ Descent
|
||||||
|
[ \(r, Name t) -> do
|
||||||
|
modify $ getRange r `addRef` (Variable, t)
|
||||||
|
return $ Just (r, Name t)
|
||||||
|
]
|
||||||
|
|
||||||
-- env
|
, Descent
|
||||||
-- = execCollectM
|
[ \(r, TypeName t) -> do
|
||||||
-- $ traverseTree pure tree
|
modify $ getRange r `addRef` (Type, t)
|
||||||
|
return $ Just (r, TypeName t)
|
||||||
|
]
|
||||||
|
]
|
||||||
|
tree
|
||||||
|
|
||||||
|
env
|
||||||
|
= execCollectM
|
||||||
|
$ descent (usingScope' leaveBe) [] tree
|
||||||
|
|
||||||
fullEnvAt :: FullEnv -> Range -> [ScopedDecl]
|
fullEnvAt :: FullEnv -> Range -> [ScopedDecl]
|
||||||
fullEnvAt fe r
|
fullEnvAt fe r
|
||||||
@ -265,6 +276,10 @@ instance Contains Range xs => Scoped (Product xs) CollectM (LIGO (Product xs)) C
|
|||||||
before r _ = enter r
|
before r _ = enter r
|
||||||
after _ _ = skip
|
after _ _ = skip
|
||||||
|
|
||||||
|
instance Contains Range xs => Scoped (Product xs) CollectM (LIGO (Product xs)) RawContract where
|
||||||
|
before r _ = enter r
|
||||||
|
after _ _ = skip
|
||||||
|
|
||||||
instance Contains Range xs => Scoped (Product xs) CollectM (LIGO (Product xs)) Binding where
|
instance Contains Range xs => Scoped (Product xs) CollectM (LIGO (Product xs)) Binding where
|
||||||
before r = \case
|
before r = \case
|
||||||
Function recur name _args ty body -> do
|
Function recur name _args ty body -> do
|
||||||
@ -335,3 +350,8 @@ instance Scoped a CollectM (LIGO a) Path
|
|||||||
instance Scoped a CollectM (LIGO a) Name
|
instance Scoped a CollectM (LIGO a) Name
|
||||||
instance Scoped a CollectM (LIGO a) TypeName
|
instance Scoped a CollectM (LIGO a) TypeName
|
||||||
instance Scoped a CollectM (LIGO a) FieldName
|
instance Scoped a CollectM (LIGO a) FieldName
|
||||||
|
|
||||||
|
instance Scoped a CollectM (LIGO a) (Err Text)
|
||||||
|
instance Scoped a CollectM (LIGO a) Language
|
||||||
|
instance Scoped a CollectM (LIGO a) Parameters
|
||||||
|
instance Scoped a CollectM (LIGO a) Ctor
|
@ -41,7 +41,7 @@ extra-deps:
|
|||||||
- semilattices-0.0.0.4@sha256:333707e460923711d1edbdd02ebe1c3957d4e0808eab9886747b52ee3e443639,1909
|
- semilattices-0.0.0.4@sha256:333707e460923711d1edbdd02ebe1c3957d4e0808eab9886747b52ee3e443639,1909
|
||||||
- fastsum-0.1.1.1
|
- fastsum-0.1.1.1
|
||||||
- git: https://github.com/serokell/duplo.git
|
- git: https://github.com/serokell/duplo.git
|
||||||
commit: 325aefe2a0e6c7a6bdd08935be669da308ed0cb1
|
commit: 3bb313af0c78c669c1b39ab2f912508b148e8aae
|
||||||
# - acme-missiles-0.3
|
# - acme-missiles-0.3
|
||||||
# - git: https://github.com/commercialhaskell/stack.git
|
# - git: https://github.com/commercialhaskell/stack.git
|
||||||
# commit: e7b331f14bcffb8367cd58fbfc8b40ec7642100a
|
# commit: e7b331f14bcffb8367cd58fbfc8b40ec7642100a
|
||||||
|
@ -45,11 +45,11 @@ packages:
|
|||||||
git: https://github.com/serokell/duplo.git
|
git: https://github.com/serokell/duplo.git
|
||||||
pantry-tree:
|
pantry-tree:
|
||||||
size: 557
|
size: 557
|
||||||
sha256: adf7b6a5ae51a4ffa8a8db534bc030fb61209cc0be28c3bf82864267e40346c7
|
sha256: d8258e8fa560d07da3bf4a5e7f956494a8d1b374e67c3af1b7b6875f8175a309
|
||||||
commit: 325aefe2a0e6c7a6bdd08935be669da308ed0cb1
|
commit: 3bb313af0c78c669c1b39ab2f912508b148e8aae
|
||||||
original:
|
original:
|
||||||
git: https://github.com/serokell/duplo.git
|
git: https://github.com/serokell/duplo.git
|
||||||
commit: 325aefe2a0e6c7a6bdd08935be669da308ed0cb1
|
commit: 3bb313af0c78c669c1b39ab2f912508b148e8aae
|
||||||
snapshots:
|
snapshots:
|
||||||
- completed:
|
- completed:
|
||||||
size: 493124
|
size: 493124
|
||||||
|
Loading…
Reference in New Issue
Block a user