Tie all up

This commit is contained in:
Kirill Andreev 2020-08-03 21:31:24 +04:00
parent 9f29dab195
commit 31274e1507
No known key found for this signature in database
GPG Key ID: CF7DA79DE4785A47
8 changed files with 287 additions and 277 deletions

View File

@ -1,12 +1,13 @@
import Control.Concurrent import Control.Concurrent
import Control.Arrow
import Control.Concurrent.STM import Control.Concurrent.STM
import Control.Exception as E import Control.Exception as E
import Control.Lens import Control.Lens
import Control.Monad import Control.Monad
import Data.Default import Data.Default
import Data.Foldable -- import Data.Foldable
import qualified Data.Text as Text import qualified Data.Text as Text
import Data.Text (Text) import Data.Text (Text)
import Data.String (fromString) import Data.String (fromString)
@ -25,6 +26,8 @@ import System.Exit
import qualified System.Log as L import qualified System.Log as L
import Duplo.Pretty import Duplo.Pretty
import Duplo.Error
import Duplo.Tree (collect)
import Parser import Parser
import ParseTree import ParseTree
@ -36,229 +39,229 @@ import qualified AST.Find as Find
main :: IO () main :: IO ()
main = do main = do
return ()
for_ [1.. 100] \_ -> do
print . length . show . pp =<< sample' "../../../src/test/contracts/loop.ligo"
-- errCode <- mainLoop
-- exit errCode
-- mainLoop :: IO Int
-- mainLoop = do
-- chan <- atomically newTChan :: IO (TChan FromClientMessage)
-- let
-- callbacks = Core.InitializeCallbacks
-- { Core.onInitialConfiguration = const $ Right ()
-- , Core.onConfigurationChange = const $ Right ()
-- , Core.onStartup = \lFuns -> do
-- _ <- forkIO $ eventLoop lFuns chan
-- return Nothing
-- }
-- Core.setupLogger (Just "log.txt") [] L.INFO
-- CTRL.run callbacks (lspHandlers chan) lspOptions (Just "log.txt")
-- `catches`
-- [ Handler \(e :: SomeException) -> do
-- print e
-- return 1
-- ]
-- syncOptions :: J.TextDocumentSyncOptions
-- syncOptions = J.TextDocumentSyncOptions
-- { J._openClose = Just True
-- , J._change = Just J.TdSyncIncremental
-- , J._willSave = Just False
-- , J._willSaveWaitUntil = Just False
-- , J._save = Just $ J.SaveOptions $ Just False
-- }
-- lspOptions :: Core.Options
-- lspOptions = def
-- { Core.textDocumentSync = Just syncOptions
-- , Core.executeCommandCommands = Just ["lsp-hello-command"]
-- }
-- lspHandlers :: TChan FromClientMessage -> Core.Handlers
-- lspHandlers rin = def
-- { Core.initializedHandler = Just $ passHandler rin NotInitialized
-- , Core.definitionHandler = Just $ passHandler rin ReqDefinition
-- , Core.referencesHandler = Just $ passHandler rin ReqFindReferences
-- , Core.didOpenTextDocumentNotificationHandler = Just $ passHandler rin NotDidOpenTextDocument
-- , Core.didSaveTextDocumentNotificationHandler = Just $ passHandler rin NotDidSaveTextDocument
-- , Core.didChangeTextDocumentNotificationHandler = Just $ passHandler rin NotDidChangeTextDocument
-- , Core.didCloseTextDocumentNotificationHandler = Just $ passHandler rin NotDidCloseTextDocument
-- , Core.cancelNotificationHandler = Just $ passHandler rin NotCancelRequestFromClient
-- , Core.responseHandler = Just $ responseHandlerCb rin
-- , Core.codeActionHandler = Just $ passHandler rin ReqCodeAction
-- , Core.executeCommandHandler = Just $ passHandler rin ReqExecuteCommand
-- }
-- passHandler :: TChan FromClientMessage -> (a -> FromClientMessage) -> Core.Handler a
-- passHandler rin c notification = do
-- atomically $ writeTChan rin (c notification)
-- responseHandlerCb :: TChan FromClientMessage -> Core.Handler J.BareResponseMessage
-- responseHandlerCb _rin resp = do
-- U.logs $ "******** got ResponseMessage, ignoring:" ++ show resp
-- send :: Core.LspFuncs () -> FromServerMessage -> IO ()
-- send = Core.sendFunc
-- nextID :: Core.LspFuncs () -> IO J.LspId
-- nextID = Core.getNextReqId
-- eventLoop :: Core.LspFuncs () -> TChan FromClientMessage -> IO ()
-- eventLoop funs chan = do
-- forever do
-- msg <- atomically (readTChan chan)
-- U.logs [i|Client: ${msg}|]
-- case msg of
-- RspFromClient {} -> do
-- return () -- return ()
-- for_ [1.. 100] \_ -> do
-- print . length . show . pp =<< sample' "../../../src/test/recognises/loop.ligo"
errCode <- mainLoop
exit errCode
-- NotInitialized _notif -> do mainLoop :: IO Int
-- let mainLoop = do
-- registration = J.Registration chan <- atomically newTChan :: IO (TChan FromClientMessage)
-- "lsp-haskell-registered"
-- J.WorkspaceExecuteCommand
-- Nothing
-- registrations = J.RegistrationParams $ J.List [registration]
-- rid <- nextID funs let
-- send funs callbacks = Core.InitializeCallbacks
-- $ ReqRegisterCapability { Core.onInitialConfiguration = const $ Right ()
-- $ fmServerRegisterCapabilityRequest rid registrations , Core.onConfigurationChange = const $ Right ()
, Core.onStartup = \lFuns -> do
_ <- forkIO $ eventLoop lFuns chan
return Nothing
}
-- NotDidOpenTextDocument notif -> do Core.setupLogger (Just "log.txt") [] L.INFO
-- let CTRL.run callbacks (lspHandlers chan) lspOptions (Just "log.txt")
-- doc = notif `catches`
-- ^.J.params [ Handler \(e :: SomeException) -> do
-- .J.textDocument print e
-- .J.uri return 1
]
-- ver = notif syncOptions :: J.TextDocumentSyncOptions
-- ^.J.params syncOptions = J.TextDocumentSyncOptions
-- .J.textDocument { J._openClose = Just True
-- .J.version , J._change = Just J.TdSyncIncremental
, J._willSave = Just False
, J._willSaveWaitUntil = Just False
, J._save = Just $ J.SaveOptions $ Just False
}
-- collectErrors funs lspOptions :: Core.Options
-- (J.toNormalizedUri doc) lspOptions = def
-- (J.uriToFilePath doc) { Core.textDocumentSync = Just syncOptions
-- (Just ver) , Core.executeCommandCommands = Just ["lsp-hello-command"]
}
-- NotDidChangeTextDocument notif -> do lspHandlers :: TChan FromClientMessage -> Core.Handlers
-- let lspHandlers rin = def
-- doc = notif { Core.initializedHandler = Just $ passHandler rin NotInitialized
-- ^.J.params , Core.definitionHandler = Just $ passHandler rin ReqDefinition
-- .J.textDocument , Core.referencesHandler = Just $ passHandler rin ReqFindReferences
-- .J.uri , Core.didOpenTextDocumentNotificationHandler = Just $ passHandler rin NotDidOpenTextDocument
, Core.didSaveTextDocumentNotificationHandler = Just $ passHandler rin NotDidSaveTextDocument
, Core.didChangeTextDocumentNotificationHandler = Just $ passHandler rin NotDidChangeTextDocument
, Core.didCloseTextDocumentNotificationHandler = Just $ passHandler rin NotDidCloseTextDocument
, Core.cancelNotificationHandler = Just $ passHandler rin NotCancelRequestFromClient
, Core.responseHandler = Just $ responseHandlerCb rin
, Core.codeActionHandler = Just $ passHandler rin ReqCodeAction
, Core.executeCommandHandler = Just $ passHandler rin ReqExecuteCommand
}
-- collectErrors funs passHandler :: TChan FromClientMessage -> (a -> FromClientMessage) -> Core.Handler a
-- (J.toNormalizedUri doc) passHandler rin c notification = do
-- (J.uriToFilePath doc) atomically $ writeTChan rin (c notification)
-- (Just 0)
-- ReqDefinition req -> do responseHandlerCb :: TChan FromClientMessage -> Core.Handler J.BareResponseMessage
-- stopDyingAlready funs req do responseHandlerCb _rin resp = do
-- let uri = req^.J.params.J.textDocument.J.uri U.logs $ "******** got ResponseMessage, ignoring:" ++ show resp
-- let pos = posToRange $ req^.J.params.J.position
-- tree <- loadByVFS funs uri
-- case Find.definitionOf pos tree of
-- Just defPos -> do
-- respondWith funs req RspDefinition $ J.MultiLoc [J.Location uri $ rangeToLoc defPos]
-- Nothing -> do
-- respondWith funs req RspDefinition $ J.MultiLoc []
-- ReqFindReferences req -> do send :: Core.LspFuncs () -> FromServerMessage -> IO ()
-- stopDyingAlready funs req do send = Core.sendFunc
-- let uri = req^.J.params.J.textDocument.J.uri
-- let pos = posToRange $ req^.J.params.J.position
-- tree <- loadFromVFS funs uri
-- case Find.referencesOf pos tree of
-- Just refs -> do
-- let locations = J.Location uri . rangeToLoc <$> refs
-- respondWith funs req RspFindReferences $ J.List locations
-- Nothing -> do
-- respondWith funs req RspFindReferences $ J.List []
-- _ -> U.logs "unknown msg" nextID :: Core.LspFuncs () -> IO J.LspId
nextID = Core.getNextReqId
-- respondWith eventLoop :: Core.LspFuncs () -> TChan FromClientMessage -> IO ()
-- :: Core.LspFuncs () eventLoop funs chan = do
-- -> J.RequestMessage J.ClientMethod req rsp forever do
-- -> (J.ResponseMessage rsp -> FromServerMessage) msg <- atomically (readTChan chan)
-- -> rsp
-- -> IO ()
-- respondWith funs req wrap rsp = Core.sendFunc funs $ wrap $ Core.makeResponseMessage req rsp
-- stopDyingAlready :: Core.LspFuncs () -> J.RequestMessage m a b -> IO () -> IO () U.logs [i|Client: ${msg}|]
-- stopDyingAlready funs req = flip catch \(e :: SomeException) -> do
-- Core.sendErrorResponseS (Core.sendFunc funs) (req^.J.id.to J.responseId) J.InternalError
-- $ fromString
-- $ "this happened: " ++ show e
-- posToRange :: J.Position -> Range case msg of
-- posToRange (J.Position l c) = Range (l + 1, c + 1, 0) (l + 1, c + 1, 0) "" RspFromClient {} -> do
return ()
-- rangeToLoc :: Range -> J.Range NotInitialized _notif -> do
-- rangeToLoc (Range (a, b, _) (c, d, _) _) = let
-- J.Range registration = J.Registration
-- (J.Position (a - 1) (b - 1)) "lsp-haskell-registered"
-- (J.Position (c - 1) (d - 1)) J.WorkspaceExecuteCommand
Nothing
registrations = J.RegistrationParams $ J.List [registration]
-- loadFromVFS rid <- nextID funs
-- :: Core.LspFuncs () send funs
-- -> J.Uri $ ReqRegisterCapability
-- -> IO (Pascal (Product [[ScopedDecl], Maybe Category, Range, [Text]])) $ fmServerRegisterCapabilityRequest rid registrations
-- loadFromVFS funs uri = do
-- Just vf <- Core.getVirtualFileFunc funs $ J.toNormalizedUri uri
-- let txt = virtualFileText vf
-- let Just fin = J.uriToFilePath uri
-- (tree, _) <- runParser contract (Text fin txt)
-- return $ addLocalScopes tree
-- loadByURI NotDidOpenTextDocument notif -> do
-- :: J.Uri let
-- -> IO (Pascal (Product [[ScopedDecl], Maybe Category, Range, [Text]])) doc = notif
-- loadByURI uri = do ^.J.params
-- case J.uriToFilePath uri of .J.textDocument
-- Just fin -> do .J.uri
-- (tree, _) <- runParser contract (Path fin)
-- return $ addLocalScopes tree
-- Nothing -> do
-- error $ "uriToFilePath " ++ show uri ++ " has failed. We all are doomed."
-- collectErrors ver = notif
-- :: Core.LspFuncs () ^.J.params
-- -> J.NormalizedUri .J.textDocument
-- -> Maybe FilePath .J.version
-- -> Maybe Int
-- -> IO ()
-- collectErrors funs uri path version = do
-- case path of
-- Just fin -> do
-- (tree, errs) <- runParser contract (Path fin)
-- Core.publishDiagnosticsFunc funs 100 uri version
-- $ partitionBySource
-- $ map errorToDiag (errs <> errors tree)
-- Nothing -> error "TODO: implement URI file loading" collectErrors funs
(J.toNormalizedUri doc)
(J.uriToFilePath doc)
(Just ver)
-- errorToDiag :: Error ASTInfo -> J.Diagnostic NotDidChangeTextDocument notif -> do
-- errorToDiag (Expected what _ (getRange -> (Range (sl, sc, _) (el, ec, _) _))) = let
-- J.Diagnostic doc = notif
-- (J.Range begin end) ^.J.params
-- (Just J.DsError) .J.textDocument
-- Nothing .J.uri
-- (Just "ligo-lsp")
-- (Text.pack [i|Expected #{what}|])
-- (Just $ J.List[])
-- where
-- begin = J.Position (sl - 1) (sc - 1)
-- end = J.Position (el - 1) (ec - 1)
-- exit :: Int -> IO () collectErrors funs
-- exit 0 = exitSuccess (J.toNormalizedUri doc)
-- exit n = exitWith (ExitFailure n) (J.uriToFilePath doc)
(Just 0)
ReqDefinition req -> do
stopDyingAlready funs req do
let uri = req^.J.params.J.textDocument.J.uri
let pos = posToRange $ req^.J.params.J.position
tree <- loadFromVFS funs uri
case Find.definitionOf pos tree of
Just defPos -> do
respondWith funs req RspDefinition $ J.MultiLoc [J.Location uri $ rangeToLoc defPos]
Nothing -> do
respondWith funs req RspDefinition $ J.MultiLoc []
ReqFindReferences req -> do
stopDyingAlready funs req do
let uri = req^.J.params.J.textDocument.J.uri
let pos = posToRange $ req^.J.params.J.position
tree <- loadFromVFS funs uri
case Find.referencesOf pos tree of
Just refs -> do
let locations = J.Location uri . rangeToLoc <$> refs
respondWith funs req RspFindReferences $ J.List locations
Nothing -> do
respondWith funs req RspFindReferences $ J.List []
_ -> U.logs "unknown msg"
respondWith
:: Core.LspFuncs ()
-> J.RequestMessage J.ClientMethod req rsp
-> (J.ResponseMessage rsp -> FromServerMessage)
-> rsp
-> IO ()
respondWith funs req wrap rsp = Core.sendFunc funs $ wrap $ Core.makeResponseMessage req rsp
stopDyingAlready :: Core.LspFuncs () -> J.RequestMessage m a b -> IO () -> IO ()
stopDyingAlready funs req = flip catch \(e :: SomeException) -> do
Core.sendErrorResponseS (Core.sendFunc funs) (req^.J.id.to J.responseId) J.InternalError
$ fromString
$ "this happened: " ++ show e
posToRange :: J.Position -> Range
posToRange (J.Position l c) = Range (l + 1, c + 1, 0) (l + 1, c + 1, 0) ""
rangeToLoc :: Range -> J.Range
rangeToLoc (Range (a, b, _) (c, d, _) _) =
J.Range
(J.Position (a - 1) (b - 1))
(J.Position (c - 1) (d - 1))
loadFromVFS
:: Core.LspFuncs ()
-> J.Uri
-> IO (LIGO Info')
loadFromVFS funs uri = do
Just vf <- Core.getVirtualFileFunc funs $ J.toNormalizedUri uri
let txt = virtualFileText vf
let Just fin = J.uriToFilePath uri
(tree, _) <- runParserM . recognise =<< toParseTree (Text fin txt)
return $ addLocalScopes tree
loadByURI
:: J.Uri
-> IO (LIGO Info')
loadByURI uri = do
case J.uriToFilePath uri of
Just fin -> do
(tree, _) <- runParserM . recognise =<< toParseTree (Path fin)
return $ addLocalScopes tree
Nothing -> do
error $ "uriToFilePath " ++ show uri ++ " has failed. We all are doomed."
collectErrors
:: Core.LspFuncs ()
-> J.NormalizedUri
-> Maybe FilePath
-> Maybe Int
-> IO ()
collectErrors funs uri path version = do
case path of
Just fin -> do
(tree, errs) <- runParserM . recognise =<< toParseTree (Path fin)
Core.publishDiagnosticsFunc funs 100 uri version
$ partitionBySource
$ map errorToDiag (errs <> map (getElem *** void) (collect tree))
Nothing -> error "TODO: implement URI file loading"
errorToDiag :: (Range, Err Text a) -> J.Diagnostic
errorToDiag (getRange -> (Range (sl, sc, _) (el, ec, _) _), Err what) =
J.Diagnostic
(J.Range begin end)
(Just J.DsError)
Nothing
(Just "ligo-lsp")
(Text.pack [i|Expected #{what}|])
(Just $ J.List[])
where
begin = J.Position (sl - 1) (sc - 1)
end = J.Position (el - 1) (ec - 1)
exit :: Int -> IO ()
exit 0 = exitSuccess
exit n = exitWith (ExitFailure n)

View File

@ -1,70 +1,75 @@
module AST.Find where module AST.Find where
-- import Control.Monad import Control.Monad
-- import AST.Types import Data.Maybe (listToMaybe)
-- import AST.Scope
-- import AST.Parser
-- import Tree import Duplo.Tree
-- import Range import Duplo.Pretty
-- import Pretty import Duplo.Lattice
-- import Product
-- import Data.Text (Text) import Data.Text (Text)
-- -- import Debug.Trace
-- type CanSearch xs = import AST.Types
-- ( Contains [ScopedDecl] xs import AST.Scope
-- , Contains Range xs
-- , Contains (Maybe Category) xs
-- , Contains [Text] xs
-- , Pretty (Product xs)
-- )
-- findScopedDecl import Product
-- :: CanSearch xs import Range
-- => Range
-- -> Pascal (Product xs)
-- -> Maybe ScopedDecl
-- findScopedDecl pos tree = do
-- pt <- lookupTree pos tree
-- let info = infoOf pt
-- let fullEnv = getElem info
-- do
-- categ <- getElem info
-- let filtered = filter (ofCategory categ) fullEnv
-- lookupEnv (ppToText $ void pt) filtered
-- definitionOf -- import Debug.Trace
-- :: CanSearch xs
-- => Range
-- -> Pascal (Product xs)
-- -> Maybe Range
-- definitionOf pos tree =
-- _sdOrigin <$> findScopedDecl pos tree
-- typeOf type CanSearch xs =
-- :: CanSearch xs ( Contains [ScopedDecl] xs
-- => Range , Contains Range xs
-- -> Pascal (Product xs) , Contains (Maybe Category) xs
-- -> Maybe (Either (Pascal ()) Kind) , Contains [Text] xs
-- typeOf pos tree = , Pretty (Product xs)
-- _sdType =<< findScopedDecl pos tree , Eq (Product xs)
)
-- implementationOf findScopedDecl
-- :: CanSearch xs :: CanSearch xs
-- => Range => Range
-- -> Pascal (Product xs) -> LIGO (Product xs)
-- -> Maybe Range -> Maybe ScopedDecl
-- implementationOf pos tree = findScopedDecl pos tree = do
-- _sdBody =<< findScopedDecl pos tree pt <- listToMaybe $ spineTo (\i -> pos `leq` getElem i) tree
let info = extract pt
let fullEnv = getElem info
do
categ <- getElem info
let filtered = filter (ofCategory categ) fullEnv
lookupEnv (ppToText $ void pt) filtered
-- referencesOf definitionOf
-- :: CanSearch xs :: CanSearch xs
-- => Range => Range
-- -> Pascal (Product xs) -> LIGO (Product xs)
-- -> Maybe [Range] -> Maybe Range
-- referencesOf pos tree = definitionOf pos tree =
-- _sdRefs <$> findScopedDecl pos tree _sdOrigin <$> findScopedDecl pos tree
typeOf
:: CanSearch xs
=> Range
-> LIGO (Product xs)
-> Maybe (Either (LIGO ()) Kind)
typeOf pos tree =
_sdType =<< findScopedDecl pos tree
implementationOf
:: CanSearch xs
=> Range
-> LIGO (Product xs)
-> Maybe Range
implementationOf pos tree =
_sdBody =<< findScopedDecl pos tree
referencesOf
:: CanSearch xs
=> Range
-> LIGO (Product xs)
-> Maybe [Range]
referencesOf pos tree =
_sdRefs <$> findScopedDecl pos tree

View File

@ -56,6 +56,12 @@ data ScopedDecl = ScopedDecl
} }
deriving Show via PP ScopedDecl deriving Show via PP ScopedDecl
instance Eq ScopedDecl where
sd == sd1 = and
[ pp (_sdName sd) == pp (_sdName sd1)
, _sdOrigin sd == _sdOrigin sd1
]
-- | The kind. -- | The kind.
data Kind = Star data Kind = Star
deriving Show via PP Kind deriving Show via PP Kind
@ -91,6 +97,8 @@ ofCategory Variable _ = True
ofCategory Type ScopedDecl { _sdType = Just (Right Star) } = True ofCategory Type ScopedDecl { _sdType = Just (Right Star) } = True
ofCategory _ _ = False ofCategory _ _ = False
type Info' = Product [[ScopedDecl], Maybe Category, [Text], Range, ShowRange]
instance Modifies (Product '[[ScopedDecl], Maybe Category, [Text], Range, a]) where instance Modifies (Product '[[ScopedDecl], Maybe Category, [Text], Range, a]) where
ascribe (ds :> _ :> _ :> r :> _) d = ascribe (ds :> _ :> _ :> r :> _) d =
color 3 (fsep (map (pp . _sdName) ds)) color 3 (fsep (map (pp . _sdName) ds))

View File

@ -25,7 +25,7 @@ type RawLigoList =
[ Name, Path, QualifiedName, Pattern, Constant, FieldAssignment, Assignment [ Name, Path, QualifiedName, Pattern, Constant, FieldAssignment, Assignment
, MapBinding, LHS, Alt, Expr, TField, Variant, Type, Mutable, VarDecl, Binding , MapBinding, LHS, Alt, Expr, TField, Variant, Type, Mutable, VarDecl, Binding
, RawContract, TypeName, FieldName, Language , RawContract, TypeName, FieldName, Language
, Err Text, Parameters, Ctor , Err Text, Parameters, Ctor, Contract
] ]
data Undefined it data Undefined it

View File

@ -21,7 +21,6 @@ module ParseTree
where where
import Data.ByteString (ByteString) import Data.ByteString (ByteString)
import Data.IORef
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
import qualified Data.Text as Text import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text import qualified Data.Text.Encoding as Text
@ -101,20 +100,13 @@ toParseTree = unsafePerformIO $ debounced inner
src <- srcToBytestring fin src <- srcToBytestring fin
idCounter <- newIORef 0
BS.useAsCStringLen src \(str, len) -> do BS.useAsCStringLen src \(str, len) -> do
tree <- ts_parser_parse_string parser nullPtr str len tree <- ts_parser_parse_string parser nullPtr str len
withRootNode tree (peek >=> go src idCounter) withRootNode tree (peek >=> go src)
where where
nextID :: IORef Int -> IO Int go :: ByteString -> Node -> IO RawTree
nextID ref = do go src node = do
modifyIORef' ref (+ 1)
readIORef ref
go :: ByteString -> IORef Int -> Node -> IO RawTree
go src idCounter node = do
let count = fromIntegral $ nodeChildCount node let count = fromIntegral $ nodeChildCount node
allocaArray count \children -> do allocaArray count \children -> do
alloca \tsNodePtr -> do alloca \tsNodePtr -> do
@ -124,7 +116,7 @@ toParseTree = unsafePerformIO $ debounced inner
peekElemOff children i peekElemOff children i
trees <- for nodes \node' -> do trees <- for nodes \node' -> do
(only -> (r :> _, tree :: ParseTree RawTree)) <- go src idCounter node' (only -> (r :> _, tree :: ParseTree RawTree)) <- go src node'
field <- field <-
if nodeFieldName node' == nullPtr if nodeFieldName node' == nullPtr
then return "" then return ""
@ -138,9 +130,6 @@ toParseTree = unsafePerformIO $ debounced inner
finish2D = nodeEndPoint node finish2D = nodeEndPoint node
i = fromIntegral i = fromIntegral
treeID <- nextID idCounter
fID <- nextID idCounter
let let
range = Range range = Range
{ rStart = { rStart =

View File

@ -29,7 +29,7 @@ import Debug.Trace
4) On leaving, move move comments from 2 to 1. 4) On leaving, move move comments from 2 to 1.
-} -}
runParserM :: ParserM a -> IO (a, [Err Text ()]) runParserM :: ParserM a -> IO (a, [Msg])
runParserM p = (\(a, _, errs) -> (a, errs)) <$> runRWST p () ([], []) runParserM p = (\(a, _, errs) -> (a, errs)) <$> runRWST p () ([], [])
runParserM1 :: [RawTree] -> ParserM1 a -> ParserM (Maybe a) runParserM1 :: [RawTree] -> ParserM1 a -> ParserM (Maybe a)
@ -40,22 +40,23 @@ runParserM1 cs p = do
put s1 put s1
return a return a
type ParserM = RWST () [Err Text ()] ([Text], [Text]) IO type Msg = (Range, Err Text ())
type ParserM1 = MaybeT (RWST [RawTree] [Err Text ()] ([Text], [Text]) IO) type ParserM = RWST () [Msg] ([Text], [Text]) IO
type ParserM1 = MaybeT (RWST [RawTree] [Msg] ([Text], [Text]) IO)
data Failure = Failure String data Failure = Failure String
deriving stock (Show) deriving stock (Show)
deriving anyclass (Exception) deriving anyclass (Exception)
instance Scoped (Product [Range, Text]) ParserM RawTree ParseTree where instance Scoped (Product [Range, Text]) ParserM RawTree ParseTree where
before (_ :> _ :> _) (ParseTree ty cs s) = do before (r :> _ :> _) (ParseTree ty cs s) = do
let (comms, rest) = allComments cs let (comms, rest) = allComments cs
let (comms1, _) = allComments $ reverse rest let (comms1, _) = allComments $ reverse rest
modify $ first (++ comms) modify $ first (++ comms)
modify $ second (++ reverse comms1) modify $ second (++ reverse comms1)
let errs = allErrors cs let errs = allErrors cs
tell $ fmap Err errs tell $ fmap (\t -> (r, Err t)) errs
after _ _ = do after _ _ = do
modify \(x, y) -> (y, []) modify \(x, y) -> (y, [])
@ -112,6 +113,10 @@ data ShowRange
= Y | N = Y | N
deriving stock Eq deriving stock Eq
instance Pretty ShowRange where
pp Y = "Yau"
pp N = "Nah"
type Info = Product [[Text], Range, ShowRange] type Info = Product [[Text], Range, ShowRange]
type PreInfo = Product [Range, ShowRange] type PreInfo = Product [Range, ShowRange]

View File

@ -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: 3bb313af0c78c669c1b39ab2f912508b148e8aae commit: e6e2e382bb381ce629e71ab3d08274396e686ba3
# - 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

View File

@ -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: d8258e8fa560d07da3bf4a5e7f956494a8d1b374e67c3af1b7b6875f8175a309 sha256: bdd68d3e171c6a2311ca101cc654a5cca984a1e8ce745e928287a40fa8f5a0ff
commit: 3bb313af0c78c669c1b39ab2f912508b148e8aae commit: e6e2e382bb381ce629e71ab3d08274396e686ba3
original: original:
git: https://github.com/serokell/duplo.git git: https://github.com/serokell/duplo.git
commit: 3bb313af0c78c669c1b39ab2f912508b148e8aae commit: e6e2e382bb381ce629e71ab3d08274396e686ba3
snapshots: snapshots:
- completed: - completed:
size: 493124 size: 493124