Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype GithubKey = GithubKey Text
- newtype GitlabHost = GitlabHost Text
- newtype GitlabKey = GitlabKey Text
- data Violation = Violation {}
- data ViolationLevel
- data KrankConfig = KrankConfig {}
- data SourcePos = SourcePos {}
- data Localized t = Localized {
- getLocation :: SourcePos
- unLocalized :: t
- class (Monad m, MonadCatch m) => MonadKrank m where
- krankRunRESTRequest :: FromJSON t => Url 'Https -> Option 'Https -> m t
- krankAsks :: (KrankConfig -> b) -> m b
- krankMapConcurrently :: (a -> m b) -> [a] -> m [b]
- krankForConcurrently :: [a] -> (a -> m b) -> m [b]
- krankReadFile :: FilePath -> m ByteString
- krankPutStrLnStderr :: Text -> m ()
- krankPutStr :: Text -> m ()
Documentation
newtype GitlabHost Source #
Instances
Eq GitlabHost Source # | |
Defined in Krank.Types (==) :: GitlabHost -> GitlabHost -> Bool # (/=) :: GitlabHost -> GitlabHost -> Bool # | |
Ord GitlabHost Source # | |
Defined in Krank.Types compare :: GitlabHost -> GitlabHost -> Ordering # (<) :: GitlabHost -> GitlabHost -> Bool # (<=) :: GitlabHost -> GitlabHost -> Bool # (>) :: GitlabHost -> GitlabHost -> Bool # (>=) :: GitlabHost -> GitlabHost -> Bool # max :: GitlabHost -> GitlabHost -> GitlabHost # min :: GitlabHost -> GitlabHost -> GitlabHost # | |
Show GitlabHost Source # | |
Defined in Krank.Types showsPrec :: Int -> GitlabHost -> ShowS # show :: GitlabHost -> String # showList :: [GitlabHost] -> ShowS # |
Violation | |
|
data ViolationLevel Source #
Instances
Show ViolationLevel Source # | |
Defined in Krank.Types showsPrec :: Int -> ViolationLevel -> ShowS # show :: ViolationLevel -> String # showList :: [ViolationLevel] -> ShowS # |
data KrankConfig Source #
Instances
Show KrankConfig Source # | |
Defined in Krank.Types showsPrec :: Int -> KrankConfig -> ShowS # show :: KrankConfig -> String # showList :: [KrankConfig] -> ShowS # |
Represents a localized chunk of information in a file
Localized | |
|
class (Monad m, MonadCatch m) => MonadKrank m where Source #
This monad represents all the effect that Krank needs
krankRunRESTRequest, krankAsks, krankMapConcurrently, krankReadFile, krankPutStrLnStderr, krankPutStr
krankRunRESTRequest :: FromJSON t => Url 'Https -> Option 'Https -> m t Source #
Run a REST requet
krankAsks :: (KrankConfig -> b) -> m b Source #
Read the configuration
krankMapConcurrently :: (a -> m b) -> [a] -> m [b] Source #
Apply a function on many item in a concurrent way
krankForConcurrently :: [a] -> (a -> m b) -> m [b] Source #
krankReadFile :: FilePath -> m ByteString Source #
Read a file from filesystem
krankPutStrLnStderr :: Text -> m () Source #
Log an error (with trailing n)
krankPutStr :: Text -> m () Source #
Log a message (without trailing n)
Instances
MonadKrank Krank Source # | The real monad implementation for Krank |
Defined in Krank krankRunRESTRequest :: FromJSON t => Url 'Https -> Option 'Https -> Krank t Source # krankAsks :: (KrankConfig -> b) -> Krank b Source # krankMapConcurrently :: (a -> Krank b) -> [a] -> Krank [b] Source # krankForConcurrently :: [a] -> (a -> Krank b) -> Krank [b] Source # krankReadFile :: FilePath -> Krank ByteString Source # krankPutStrLnStderr :: Text -> Krank () Source # krankPutStr :: Text -> Krank () Source # |