{-# LANGUAGE DataKinds #-}
module Krank.Types
( GithubKey (..),
GitlabHost (..),
GitlabKey (..),
Violation (..),
ViolationLevel (..),
KrankConfig (..),
SourcePos (..),
Localized (..),
MonadKrank (..),
)
where
import Control.Exception.Safe (MonadCatch)
import Data.Aeson (FromJSON)
import Data.ByteString
import Data.Map (Map)
import Data.Text (Text)
import qualified Network.HTTP.Req as Req
newtype GithubKey = GithubKey Text deriving (Show)
newtype GitlabKey = GitlabKey Text deriving (Show)
newtype GitlabHost = GitlabHost Text deriving (Show, Ord, Eq)
data ViolationLevel = Info | Warning | Error deriving (Show)
data SourcePos
= SourcePos
{ file :: FilePath,
lineNumber :: Int,
colNumber :: Int
}
deriving (Show, Eq, Ord)
data Localized t
= Localized
{ getLocation :: SourcePos,
unLocalized :: t
}
deriving (Show, Eq)
data Violation
= Violation
{
checker :: Text,
level :: ViolationLevel,
message :: Text,
location :: SourcePos
}
deriving (Show)
data KrankConfig
= KrankConfig
{
githubKey :: Maybe GithubKey,
gitlabKeys :: Map GitlabHost GitlabKey,
dryRun :: Bool,
useColors :: Bool
}
deriving (Show)
class (Monad m, MonadCatch m) => MonadKrank m where
krankRunRESTRequest :: FromJSON t => Req.Url 'Req.Https -> Req.Option 'Req.Https -> m t
krankAsks :: (KrankConfig -> b) -> m b
krankMapConcurrently :: (a -> m b) -> [a] -> m [b]
krankForConcurrently :: [a] -> (a -> m b) -> m [b]
krankForConcurrently = flip krankMapConcurrently
krankReadFile :: FilePath -> m ByteString
krankPutStrLnStderr :: Text -> m ()
krankPutStr :: Text -> m ()