Skip to content
2 changes: 2 additions & 0 deletions .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,8 @@ out/
# Atom
.haskell-ghc-mod.json

#
knowledgebase/issues.csv
# Misc
.DS_Store
*.swp
Expand Down
7 changes: 3 additions & 4 deletions CI-NIX.md
Original file line number Diff line number Diff line change
Expand Up @@ -9,17 +9,16 @@ The pipeline that is executed is located in the .buildkite folder.

| File | How to Make | Description |
| --- | --- | --- |
| default.nix | Manually | Contains the primary nix expression used to build log-classifier. This is likely the only nix expression that a developer may need to modify. |
| cabal2nix.nix | `$ cabal2nix . > cabal2nix.nix` | The cabal2nix generated output from the log-classifier.cabal file. |
| fetch-nixpkgs.nix | [cardano sl](https://github.com/input-output-hk/cardano-sl) | Used for pinning a specific version of nixpkgs. Reads nixpkgs-src.json. |
| fetchNixpkgs.nix | [cardano sl](https://github.com/input-output-hk/cardano-sl) | Used for pinning a specific version of nixpkgs. Verifies and pulls nixpkgs. |
| lib.nix | [cardano sl](https://github.com/input-output-hk/cardano-sl) | Used for pinning a specific verison of nixpkgs. Checks for cardano sl pkgs and runs fetch-nixpkgs.nix otherwise. |
| shell.nix | Manually | Used by nix-shell to set nix environment. |
| universum.nix | `$ cabal2nix cabal://universum-1.1.0 > universum.nix` | Created by cabal2nix, essentially overrides the Universum in nixpkgs. |
| release.nix | Manually | Used by Hydra |
| nixpkgs-src.json | See Below | Where version of nixpkgs is defined. See below for instructions to update. |

## Developing / Building via Nix

Note: We are using stack for local builds again. Nix is being used via the CI, but only to run stack and weeder.

All the commands below are executed in the cloned log-classifier directory.

Build with test output:
Expand Down
22 changes: 8 additions & 14 deletions src/Lib.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,12 +45,12 @@ import DataSource (App, Attachment (..), AttachmentContent (..), Comme
runApp, tokenPath)

import Exceptions (ProcessTicketExceptions (..), ZipFileExceptions (..))
import LogAnalysis.Classifier (extractErrorCodes, extractIssuesFromLogs,
import LogAnalysis.Classifier (extractIssuesFromLogs,
prettyFormatAnalysis, prettyFormatLogReadError,
prettyFormatNoIssues, prettyFormatNoLogs)
import LogAnalysis.Exceptions (LogAnalysisException (..))
import LogAnalysis.KnowledgeCSVParser (parseKnowLedgeBase)
import LogAnalysis.Types (ErrorCode (..), Knowledge, renderErrorCode, setupAnalysis)
import LogAnalysis.Types (Knowledge, setupAnalysis)
import Statistics (showStatistics)
import Util (extractLogsFromZip)

Expand Down Expand Up @@ -537,14 +537,8 @@ inspectLocalZipAttachment filePath = do

case eitherAnalysisResult of
Right analysisResult -> do
let errorCodes = extractErrorCodes analysisResult

printText "Analysis result:"
void $ mapM (printText . show) analysisResult

printText "Error codes:"
void $ mapM printText errorCodes

Left (e :: LogAnalysisException) -> do
printText $ show e

Expand All @@ -562,7 +556,7 @@ inspectAttachment Config{..} ticketInfo@TicketInfo{..} attachment = do
pure $ ZendeskResponse
{ zrTicketId = tiId
, zrComment = prettyFormatLogReadError ticketInfo
, zrTags = TicketTags [renderErrorCode SentLogCorrupted]
, zrTags = TicketTags []--renderErrorCode SentLogCorrupted]
, zrIsPublic = cfgIsCommentPublic
}

Expand All @@ -573,13 +567,13 @@ inspectAttachment Config{..} ticketInfo@TicketInfo{..} attachment = do
case tryAnalysisResult of
Right analysisResult -> do
-- Known issue was found
let errorCodes = extractErrorCodes analysisResult
--let errorCodes = extractErrorCodes analysisResult
let commentRes = prettyFormatAnalysis analysisResult ticketInfo

pure $ ZendeskResponse
{ zrTicketId = tiId
, zrComment = commentRes
, zrTags = TicketTags errorCodes
, zrTags = TicketTags []--errorCodes
, zrIsPublic = cfgIsCommentPublic
}

Expand All @@ -590,15 +584,15 @@ inspectAttachment Config{..} ticketInfo@TicketInfo{..} attachment = do
pure $ ZendeskResponse
{ zrTicketId = tiId
, zrComment = prettyFormatLogReadError ticketInfo
, zrTags = TicketTags [renderErrorCode DecompressionFailure]
, zrTags = TicketTags []--renderErrorCode DecompressionFailure]
, zrIsPublic = cfgIsCommentPublic
}
-- No known issue was found
NoKnownIssueFound ->
pure $ ZendeskResponse
{ zrTicketId = tiId
, zrComment = prettyFormatNoIssues ticketInfo
, zrTags = TicketTags [renderTicketStatus NoKnownIssue]
, zrTags = TicketTags []--renderTicketStatus NoKnownIssue]
, zrIsPublic = cfgIsCommentPublic
}

Expand All @@ -609,7 +603,7 @@ responseNoLogs TicketInfo{..} = do
pure ZendeskResponse
{ zrTicketId = tiId
, zrComment = prettyFormatNoLogs
, zrTags = TicketTags [renderTicketStatus NoLogAttached]
, zrTags = TicketTags []--renderTicketStatus NoLogAttached]
, zrIsPublic = cfgIsCommentPublic
}

Expand Down
8 changes: 2 additions & 6 deletions src/LogAnalysis/Classifier.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,7 @@
{-# LANGUAGE RecordWildCards #-}

module LogAnalysis.Classifier
( extractErrorCodes
, extractIssuesFromLogs
( extractIssuesFromLogs
, prettyFormatAnalysis
, prettyFormatLogReadError
, prettyFormatNoIssues
Expand All @@ -19,7 +18,7 @@ import Data.Text.Encoding.Error (ignore)

import DataSource.Types (TicketInfo (..), ZendeskAPIUrl (..), showURL)
import LogAnalysis.Exceptions (LogAnalysisException (..))
import LogAnalysis.Types (Analysis, Knowledge (..), renderErrorCode)
import LogAnalysis.Types (Analysis, Knowledge (..))

-- | Number of error texts it should show
numberOfErrorText :: Int
Expand Down Expand Up @@ -63,9 +62,6 @@ filterAnalysis as = do
then throwM NoKnownIssueFound
else pure $ Map.map (take numberOfErrorText) filteredAnalysis

extractErrorCodes :: Analysis -> [Text]
extractErrorCodes as = map (\(Knowledge{..}, _) -> renderErrorCode kErrorCode) $ Map.toList as

prettyHeader :: Text
prettyHeader =
"Dear user," <>
Expand Down
88 changes: 58 additions & 30 deletions src/LogAnalysis/KnowledgeCSVParser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ import Universum

import Data.Attoparsec.Text (Parser, char, endOfLine, takeTill, string)

import LogAnalysis.Types (ErrorCode (..), Knowledge (..))
import LogAnalysis.Types (Knowledge (..))


{-
Expand All @@ -27,44 +27,72 @@ quotedText = do
_ <- char '"'
pure result

--- | Parse ErrorCode
parseErrorCode :: Parser ErrorCode
parseErrorCode =
(string "ShortStorage" >> return ShortStorage)
<|> (string "UserNameError" >> return UserNameError)
<|> (string "TimeSync" >> return TimeSync)
<|> (string "FileNotFound" >> return FileNotFound)
<|> (string "StaleLockFile" >> return StaleLockFile)
<|> (string "DBPath" >> return DBPath)
<|> (string "CannotGetDBSize" >> return CannotGetDBSize)
<|> (string "DBError" >> return DBError)
<|> (string "BalanceError" >> return BalanceError)
<|> (string "NetworkError" >> return NetworkError)
<|> (string "ConnectionRefused" >> return ConnectionRefused)
<|> (string "ResourceVanished" >> return ResourceVanished)
<|> (string "Unknown" >> return Unknown)
<|> (string "Error" >> return Error)

-- | Parse each csv records
parseKnowledge :: Parser Knowledge -- not really clean code..

parseKnowledge :: Parser Knowledge
parseKnowledge = do
e <- quotedText
_ <- char ','
_ <- char '"'
c <- parseErrorCode
issueProj <- takeTill (=='-')
_ <- char '-'
issueID <- takeTill (=='"')
_ <- char '"'
_ <- char ','
p <- quotedText
project <- quotedText
_ <- char ','
tags <- quotedText
_ <- char ','
summary <- quotedText
_ <- char ','
reporter <- quotedText
_ <- char ','
created <- quotedText
_ <- char ','
updated <- quotedText
_ <- char ','
resolved <- quotedText
_ <- char ','
priority <- quotedText
_ <- char ','
typeCat <- quotedText
_ <- char ','
state <- quotedText
_ <- char ','
assignee <- quotedText
_ <- char ','
subsystem <- quotedText
_ <- char ','
s <- quotedText
fixVer <- quotedText
_ <- char ','
f <- quotedText
affVer <- quotedText
_ <- char ','
tarVer <- quotedText
_ <- char ','
group <- quotedText
_ <- char ','
resolution <- quotedText
_ <- char ','
platform <- quotedText
_ <- char ','
numUserAff <- quotedText
_ <- char ','
zenDebugger <- quotedText
_ <- char ','
zenTicketStat <- quotedText
_ <- char ','
zenFAQNum <- quotedText
_ <- char ','
zenIdentText <- quotedText
_ <- char ','
zenProbURL <- quotedText
_ <- char ','
zenDebSol <- quotedText
_ <- char ','
zenDebStatus <- quotedText

return $ Knowledge
{ kErrorText = e
, kErrorCode = c
, kProblem = p
, kSolution = s
, kFAQNumber = f
{ kErrorText = zenIdentText
, kIssueID = (IssueID issueProj issueID)
}

-- | Parse CSV file and create knowledgebase
Expand Down
73 changes: 10 additions & 63 deletions src/LogAnalysis/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,85 +2,37 @@

module LogAnalysis.Types
( Analysis
, ErrorCode (..)
, Knowledge (..)
, setupAnalysis
, renderErrorCode
, toComment
) where

import Universum
import Prelude (Show (..))

import qualified Data.Map.Strict as Map

-- | Identifier for each error
data ErrorCode
= ShortStorage -- ^ Not enough space on hard drive to store block data
| UserNameError -- ^ User is using non-latin characters for username
| TimeSync -- ^ User's PC's time is out of sync
| FileNotFound -- ^ Some of the files were not installed properly
| StaleLockFile -- ^ Open.lock file is corrupted
| SentLogCorrupted -- ^ Log file sent to the Zendesk is corrupted
| DBError -- ^ Local block data is corrupted
| DBPath -- ^ Daedalus cannot find certain files
| CannotGetDBSize -- ^ Error message of Couidn't pack log files shows up
| BalanceError -- ^ Daedalus shows wrong Ada amount
| NetworkError -- ^ Firewall is blocking the connection
| ConnectionRefused -- ^ Firewall is blocking the connection
| ResourceVanished -- ^ Network error
| DecompressionFailure -- ^ The classifier failed to decompress the log file
| Unknown -- ^ Unknown error (currently not used)
| Error -- ^ Error (currently not used)
deriving (Eq, Ord, Show)

-- | Record identifying the issue
data IssueID = IssueID Text Int deriving (Eq, Ord)

data Knowledge = Knowledge
{ kErrorText :: !Text
-- ^ Text used for matching error lines
, kErrorCode :: !ErrorCode
-- ^ Identity for error code
, kProblem :: !Text
-- ^ Text describing what is the problem
, kSolution :: !Text
-- ^ Text describing how to solve the issue
, kFAQNumber :: !Text
-- ^ The FAQ number that will be displayed on the official Cardano FAQ page
}
, kIssueID :: !IssueID
-- ^ IssueID
} deriving (Eq, Ord)

--type CSVHeader = [Text]
instance Show IssueID where
show (IssueID proj issueID) = Prelude.show proj ++ "-" ++ Prelude.show issueID

instance Show Knowledge where
show Knowledge{..} =
"{ errorText = " <> Prelude.show kErrorText <>
", errorCode = " <> Prelude.show kErrorCode <>
", problem = " <> Prelude.show kProblem <>
", solution = " <> Prelude.show kSolution <>
", FAQNumber = " <> Prelude.show kFAQNumber <>
", issueID = " <> Prelude.show kIssueID <>
"}"

-- | Sorted accoring to knowledgebase.
-- Tag needs to be in lowercase since Zendesk automatically convert any uppercase
-- lowercase
renderErrorCode :: ErrorCode -> Text
renderErrorCode DBError = "db-corrupted"
renderErrorCode StaleLockFile = "stale-lock-file"
renderErrorCode FileNotFound = "directory-not-found"
renderErrorCode ShortStorage = "short-storage"
renderErrorCode NetworkError = "network-error"
renderErrorCode BalanceError = "incorrect-balance"
renderErrorCode ResourceVanished = "resource-vanished"
renderErrorCode UserNameError = "user-name-error"
renderErrorCode ConnectionRefused = "connection-refused"
renderErrorCode TimeSync = "time-out-of-sync"
renderErrorCode SentLogCorrupted = "sent-log-corrupted"
renderErrorCode DBPath = "db-path-error"
renderErrorCode CannotGetDBSize = "cannot-get-db-size"
renderErrorCode DecompressionFailure = "decompression-failure"
renderErrorCode Unknown = "unknown"
renderErrorCode Error = "error"

toComment :: ErrorCode -> Text
toComment SentLogCorrupted = "Log file is corrupted"
toComment _ = "Error"

-- | Map used to collect error lines
type Analysis = Map Knowledge [Text]
Expand All @@ -89,8 +41,3 @@ type Analysis = Map Knowledge [Text]
setupAnalysis :: [Knowledge] -> Analysis
setupAnalysis kbase = Map.fromList $ map (\kn -> (kn, [])) kbase

instance Eq Knowledge where
e1 == e2 = kErrorCode e1 == kErrorCode e2

instance Ord Knowledge where
e1 <= e2 = kErrorCode e1 <= kErrorCode e2