module Language.Haskell.ErrorAnalyze
( ErrorPackage, ErrorVersion, ErrorModule, ErrorIdentifier, ErrorType
, ErrorCause(..)
, PackageRef(..)
, ModuleSuggestion(..)
, IdentifierSuggestion(..)
, errorCauses
) where
import Data.Char
import Data.Maybe
import qualified Data.Text as T
type ErrorPackage = T.Text
type ErrorVersion = T.Text
type ErrorModule = T.Text
type ErrorIdentifier = T.Text
type ErrorType = T.Text
data PackageRef = Referenced | Unreferenced
deriving (Show,Read,Eq,Ord,Bounded,Enum)
data ModuleSuggestion = ModuleSuggestion ErrorPackage ErrorVersion PackageRef ErrorModule
deriving (Show,Read,Eq,Ord)
data IdentifierSuggestion = IdentifierSuggestion ErrorModule ErrorIdentifier
deriving (Show,Read,Eq,Ord)
data ErrorCause
= UnknownPackage ErrorPackage ErrorVersion
| UnreferencedPackage ErrorPackage
| MissingType T.Text
| MispelledModule T.Text [ModuleSuggestion]
| MispelledIdentifier ErrorIdentifier [IdentifierSuggestion]
| UselessImport ErrorModule
| UselessImportElement ErrorModule T.Text
| MissingOption T.Text
| MissingExtension T.Text
| ConstructorImported ErrorModule ErrorType ErrorIdentifier
| IncorrectCabalVersion T.Text
deriving (Show,Read,Eq,Ord)
errorCauses :: T.Text -> [ErrorCause]
errorCauses msg = let
low = T.toLower msg
in concatMap ($ (msg,low)) analyzers
where analyzers =
[ unknownPackageAnalyzer
, moduleErrorAnalyzer
, overloadedStringAnalyzer
, missingTypeAnalyzer
, uselessImportAnalyzer
, discardedDoAnalyzer
, mispelledIdentifierAnalyzer
, constructorImportedAnalyzer
, missingExtensionAnalyzer
, cabalVersionAnalyzer]
type Analyzer = (T.Text,T.Text) -> [ErrorCause]
unknownPackageAnalyzer :: Analyzer
unknownPackageAnalyzer (msg,_)
| (_,aft) <- T.breakOn "the following dependencies are missing" msg
, not $ T.null aft
, (_,ln) <- T.breakOn "\n" aft
, not $ T.null ln
, ls <- T.strip ln
, not $ T.null ls
, pkgs <- map T.strip $ T.splitOn "," ls
, nameVersions <- map (T.splitOn " ") pkgs
= map toUP nameVersions
| otherwise = []
where
toUP (n:[]) = UnknownPackage n "-any"
toUP (n:v:_) = UnknownPackage n v
toUP [] = error "should not happen: empty list in toUP"
moduleErrorAnalyzer :: Analyzer
moduleErrorAnalyzer (msg,_)
| T.isInfixOf couldNot msg
, (bef,aft) <- T.breakOnEnd "you need to add" msg
, not $ T.null bef
, (bsp,_) <- T.breakOn " " $ T.stripStart aft
= [UnreferencedPackage $ unquote bsp]
| (_,aft) <- T.breakOn couldNot msg
, not $ T.null aft
, (ln1,aftln) <- T.breakOn "\n" $ T.drop (T.length couldNot) aft
, not $ T.null ln1
, modl <- unquote $ T.strip ln1
= [MispelledModule modl (suggs $ T.strip aftln)]
| otherwise = []
where
couldNot ="Could not find module"
suggs aftln
| T.isPrefixOf "Perhaps you meant" aftln
, lns <- filter (not . T.isInfixOf "Use -v") $ map (unquote . T.strip) $ tail $ T.lines aftln
= catMaybes $ map sugg lns
| otherwise = []
sugg ln
| (bef,aft) <- T.breakOn " " ln
, not $ T.null bef
, Just brkts <- brackets aft
, Just (pkg,vers,ref) <- suggPkg brkts
= Just $ ModuleSuggestion pkg vers ref (T.strip bef)
| otherwise = Nothing
suggPkg brk
| (bef,aft) <- T.breakOnEnd "from " brk
, not $ T.null bef
= pkgCut aft Referenced
| (bef,aft) <- T.breakOnEnd "needs flag -package-key " brk
, not $ T.null bef
= pkgCut aft Unreferenced
| otherwise = Nothing
pkgCut pv ref
| (bef,aft) <- T.breakOnEnd "-" pv
, not $ T.null bef
, (befAt,_) <- T.breakOn "@" aft
= Just (T.init bef,befAt,ref)
| otherwise = Nothing
overloadedStringAnalyzer :: Analyzer
overloadedStringAnalyzer (_,low)
| uq <- unquote low
, T.isInfixOf "with actual type [char]" uq
|| T.isInfixOf "with [char]" uq
= [MissingExtension "OverloadedStrings"]
| otherwise = []
missingTypeAnalyzer :: Analyzer
missingTypeAnalyzer (msg,_)
| (bef,aft) <- T.breakOnEnd "Top-level binding with no type signature:" msg
, not $ T.null bef
= beautifyTypes aft
| (bef,aft) <- T.breakOnEnd "definition but no type signature" msg
, not $ T.null bef
, (bef1, aft1) <- T.breakOnEnd "inferred type:" aft
, not $ T.null bef1
= beautifyTypes aft1
| otherwise = []
where cleanType typ =
let typs = T.splitOn "::" typ
noPkg = map (replaceCharArray . removePackage) typs
in T.intercalate "::" noPkg
removePackage t =
let (b,a) = T.breakOnEnd ":" t
in T.append (T.takeWhile (\c->c `elem` [' ','(']) b) a
replaceCharArray = T.replace "[Char]" "String"
beautifyTypes aft =
let typ = T.strip aft
(nam,rtyp) = T.breakOn "::" typ
(_,sname) = T.breakOnEnd "." nam
cleanTypes = T.intercalate " " $ map cleanType $ T.splitOn " " rtyp
in [MissingType (T.concat [sname,cleanTypes])]
uselessImportAnalyzer :: Analyzer
uselessImportAnalyzer (msg,low)
| T.isInfixOf "imported, but nothing from it is used" low
, (bef,aft) <- T.breakOnEnd "Module" msg
, not $ T.null bef
, (modl,_) <- T.breakOn " " $ T.stripStart aft
= [UselessImport (unquote modl)]
| (bef,aft) <- T.breakOn "is redundant" msg
, not $ T.null aft
, (bef1,modl) <- T.breakOnEnd "import of" bef
, not $ T.null bef1
, (befM,aftM) <- T.breakOn "from module" modl
= if T.null aftM
then [UselessImport (unquote $ T.strip modl)]
else [UselessImportElement (unquote $ T.strip $ T.drop 11 aftM) (unquote $ T.strip befM)]
| otherwise = []
discardedDoAnalyzer :: Analyzer
discardedDoAnalyzer (_,low)
| T.isInfixOf "a do-notation statement discarded a result" low
= [MissingOption "-fno-warn-unused-do-bind"]
| otherwise = []
mispelledIdentifierAnalyzer :: Analyzer
mispelledIdentifierAnalyzer (msg,_)
| (bef,aft) <- T.breakOnEnd "Not in scope:" msg
, not $ T.null bef
, (_,aftType) <- T.breakOnEnd "type constructor or class" aft
, (_,aftData) <- T.breakOnEnd "data constructor" aftType
, (ident:lns) <- T.lines aftData
= [MispelledIdentifier (unquoteIfNeeded ident) (suggs lns)]
|otherwise = []
where
suggs ("Perhaps you meant one of these:":lns) = suggs' lns
suggs [t]
| (bef,aft) <- T.breakOnEnd "Perhaps you meant" t
, not $ T.null bef
= suggs' [aft]
suggs _ = []
suggs' = catMaybes . map sugg1
sugg1 ln
| (ident,modlImp) <- T.breakOn " " $ T.stripStart ln
, not $ T.null modlImp
, Just imp <- brackets $ T.strip modlImp
, (bef1,modl) <- T.breakOnEnd "imported from" imp
, not $ T.null bef1
= Just $ IdentifierSuggestion (T.strip modl) (unquoteIfNeeded ident)
| otherwise = Nothing
constructorImportedAnalyzer :: Analyzer
constructorImportedAnalyzer (msg,_)
| (bef,aft) <- T.breakOn dataCons msg
, not $ T.null aft
, (befM,aftM) <- T.breakOnEnd ":" bef
, not $ T.null aftM
, (befM1,aftM1) <- T.breakOnEnd " " (T.init befM)
, not $ T.null befM1
, (befLn,aftLn) <- T.breakOn "\n" (T.drop (T.length dataCons) aft)
, not $ T.null aftLn
= [ConstructorImported (unquoteIfNeeded aftM1) (unquoteIfNeeded befLn) (unquoteIfNeeded aftM)]
| otherwise = []
where dataCons = "is a data constructor of"
missingExtensionAnalyzer :: Analyzer
missingExtensionAnalyzer (msg,low)
| T.isInfixOf "naked expression at top level" low
= [MissingExtension "TemplateHaskell"]
| T.isInfixOf "parse error on input case" (unquote low)
= [MissingExtension "LambdaCase"]
| T.isInfixOf "naked lambda expression" low
= [MissingExtension "LambdaCase"]
| T.isInfixOf "enable explicit-forall syntax" low
= [MissingExtension "RankNTypes",MissingExtension "ScopedTypeVariables",MissingExtension "ExistentialQuantification"]
| T.isInfixOf "rigid type variable" low
= [MissingExtension "ScopedTypeVariables"]
| (bef,aft) <- T.breakOnEnd "(Use " msg
, not $ T.null bef
, (bef1,aft1) <- T.breakOn " " $ aft
, not $ T.null aft1
= toExtension bef1
| (bef,aft) <- T.breakOnEnd "intended to use " msg
, not $ T.null bef
, (bef1,_) <- T.breakOn " " $ aft
= toExtension bef1
| (bef,aft) <- T.breakOnEnd "you need " msg
, not $ T.null bef
, (bef1,_) <- T.breakOn " " $ aft
= toExtension bef1
| otherwise = []
where
stripX t
| T.isPrefixOf "-X" t = T.drop 2 t
| otherwise = t
toExtension t
| st <- stripX $ T.strip t
, not $ T.null st
, isUpper $ T.head st
= [MissingExtension st]
| otherwise = []
cabalVersionAnalyzer :: Analyzer
cabalVersionAnalyzer (msg,_)
| (bef,aft) <- T.breakOnEnd "cabal-version:" msg
, not $ T.null bef
, (v,aftV) <- T.break isQuote aft
, not $ T.null aftV
= [IncorrectCabalVersion (T.strip v)]
| otherwise = []
unquote :: T.Text -> T.Text
unquote = T.concatMap addNonQuote
where addNonQuote c
| isQuote c = T.empty
| otherwise = T.singleton c
unquoteIfNeeded :: T.Text -> T.Text
unquoteIfNeeded ident =
let st=T.strip ident
in if (not $ T.null st) && isQuote (T.head st)
then unquote st
else st
isQuote :: Char -> Bool
isQuote c= c `elem` ['\'', '`','‘','’' ]
brackets :: T.Text -> Maybe T.Text
brackets t
| (_,aft) <- T.breakOn "(" t
, not $ T.null aft
, (bef1,aft1) <- T.breakOn ")" $ T.tail aft
, not $ T.null aft1
= Just $ T.strip bef1
|otherwise = Nothing