mirror of
https://github.com/github/semantic.git
synced 2024-11-29 11:02:26 +03:00
Move and export the exception type.
This commit is contained in:
parent
4c4329f295
commit
bbf3554bd7
@ -1,6 +1,7 @@
|
|||||||
{-# LANGUAGE DataKinds, GADTs, LambdaCase, ScopedTypeVariables, TypeOperators #-}
|
{-# LANGUAGE DataKinds, GADTs, LambdaCase, ScopedTypeVariables, TypeOperators #-}
|
||||||
module Parsing.TreeSitter
|
module Parsing.TreeSitter
|
||||||
( Duration(..)
|
( TSParseException (..)
|
||||||
|
, Duration(..)
|
||||||
, parseToAST
|
, parseToAST
|
||||||
, parseToPreciseAST
|
, parseToPreciseAST
|
||||||
) where
|
) where
|
||||||
@ -30,6 +31,12 @@ import qualified TreeSitter.Parser as TS
|
|||||||
import qualified TreeSitter.Tree as TS
|
import qualified TreeSitter.Tree as TS
|
||||||
import qualified TreeSitter.Unmarshal as TS
|
import qualified TreeSitter.Unmarshal as TS
|
||||||
|
|
||||||
|
data TSParseException
|
||||||
|
= ParserTimedOut
|
||||||
|
| IncompatibleVersions
|
||||||
|
| UnmarshalFailure String
|
||||||
|
deriving (Eq, Show, Generic)
|
||||||
|
|
||||||
-- | Parse a 'Blob' with the given 'TS.Language' and return its AST.
|
-- | Parse a 'Blob' with the given 'TS.Language' and return its AST.
|
||||||
-- Returns 'Nothing' if the operation timed out.
|
-- Returns 'Nothing' if the operation timed out.
|
||||||
parseToAST :: ( Bounded grammar
|
parseToAST :: ( Bounded grammar
|
||||||
@ -55,13 +62,6 @@ parseToPreciseAST parseTimeout language blob = runParse parseTimeout language bl
|
|||||||
runM (runFail (runReader cursor (runReader (Source.bytes (blobSource blob)) (TS.peekNode >>= TS.unmarshalNode))))
|
runM (runFail (runReader cursor (runReader (Source.bytes (blobSource blob)) (TS.peekNode >>= TS.unmarshalNode))))
|
||||||
>>= either (Control.Exception.throw . UnmarshalFailure) pure
|
>>= either (Control.Exception.throw . UnmarshalFailure) pure
|
||||||
|
|
||||||
|
|
||||||
data TSParseException
|
|
||||||
= ParserTimedOut
|
|
||||||
| IncompatibleVersions
|
|
||||||
| UnmarshalFailure String
|
|
||||||
deriving (Eq, Show, Generic)
|
|
||||||
|
|
||||||
instance Exception TSParseException where
|
instance Exception TSParseException where
|
||||||
displayException = \case
|
displayException = \case
|
||||||
ParserTimedOut -> "tree-sitter: parser timed out"
|
ParserTimedOut -> "tree-sitter: parser timed out"
|
||||||
|
Loading…
Reference in New Issue
Block a user