mirror of
https://github.com/github/semantic.git
synced 2024-12-20 05:11:44 +03:00
Run type errors using a specialized handler.
This commit is contained in:
parent
7e065a9693
commit
3e0a544cb9
@ -1,7 +1,8 @@
|
||||
{-# LANGUAGE GADTs, TypeFamilies, UndecidableInstances #-}
|
||||
{-# LANGUAGE GADTs, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
module Data.Abstract.Type
|
||||
( Type (..)
|
||||
, TypeError (..)
|
||||
, runTypeError
|
||||
, unify
|
||||
) where
|
||||
|
||||
@ -59,6 +60,9 @@ instance Eq1 TypeError where
|
||||
liftEq eq (UnificationError a b) (UnificationError c d) = a `eq` c && b `eq` d
|
||||
liftEq _ _ _ = False
|
||||
|
||||
runTypeError :: Evaluator location term value (Resumable TypeError ': effects) a -> Evaluator location term value effects (Either (SomeExc TypeError) a)
|
||||
runTypeError = raiseHandler runError
|
||||
|
||||
-- | Unify two 'Type's.
|
||||
unify :: (Effectful m, Applicative (m effects), Member (Resumable TypeError) effects) => Type location -> Type location -> m effects (Type location)
|
||||
unify (a1 :-> b1) (a2 :-> b2) = (:->) <$> unify a1 a2 <*> unify b1 b2
|
||||
|
@ -11,11 +11,11 @@ import Analysis.Abstract.Caching
|
||||
import Analysis.Abstract.Collecting
|
||||
import Analysis.Abstract.Erroring
|
||||
import Analysis.Abstract.Evaluating as X
|
||||
import Analysis.Abstract.TypeChecking
|
||||
import Control.Abstract.Evaluator
|
||||
import Data.Abstract.Address
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.Abstract.Value
|
||||
import Data.Abstract.Type
|
||||
import Data.Blob
|
||||
import Data.File
|
||||
import qualified Data.Language as Language
|
||||
@ -60,7 +60,7 @@ checking
|
||||
. runResolutionError
|
||||
. runEvalError
|
||||
. runAddressError
|
||||
. typeChecking
|
||||
. runTypeError
|
||||
. caching @[]
|
||||
|
||||
evalGoProject path = justEvaluating <$> evaluateProject goParser Language.Go Nothing path
|
||||
|
Loading…
Reference in New Issue
Block a user