^Setup$
^\.setup-config$
^.installed-pkg-config$
+^report\.html$
^data/CompileMimeTypes$
^examples/HelloWorld$
main = withOpenSSL $
do (opts, sources, errors) <- return . getOpt Permute options =<< getArgs
- when (not $ null errors)
+ unless (null errors)
$ do mapM_ putStr errors
exitWith $ ExitFailure 1
- when (any (\ x -> x == OptHelp) opts)
+ when (any (== OptHelp) opts)
$ do printUsage
exitWith ExitSuccess
output <- openOutput opts
eTag <- getETag opts input
- let compParams = defaultCompressParams { compressLevel = BestCompression }
+ let compParams = defaultCompressParams { compressLevel = bestCompression }
gzippedData = compressWith compParams input
originalLen = L.length input
gzippedLen = L.length gzippedData
_ -> False) opts
-- モジュール名をピリオドで分割した時の最後の項目の先頭文字を
-- 小文字にしたものを使ふ。
- defaultSymName = mkDefault modName
- mkDefault = headToLower . getLastComp
- headToLower = \ str -> case str of
- [] -> error "module name must not be empty"
- (x:xs) -> toLower x : xs
- getLastComp = reverse . fst . break (== '.') . reverse
+ defaultSymName = mkDefault modName
+ mkDefault = headToLower . getLastComp
+ headToLower str = case str of
+ [] -> error "module name must not be empty"
+ (x:xs) -> toLower x : xs
+ getLastComp = reverse . fst . break (== '.') . reverse
in
case symNameOpts of
[] -> return defaultSymName
getLastModified :: FilePath -> IO UTCTime
getLastModified "-" = getCurrentTime
-getLastModified fpath = getFileStatus fpath
- >>= return . posixSecondsToUTCTime . fromRational . toRational . modificationTime
+getLastModified fpath = fmap (posixSecondsToUTCTime . fromRational . toRational . modificationTime)
+ $ getFileStatus fpath
getETag :: [CmdOpt] -> Lazy.ByteString -> IO String
_ -> False) opts
in
case eTagOpts of
- [] -> getDigestByName "SHA1" >>= return . mkETagFromInput . fromJust
+ [] -> fmap (mkETagFromInput . fromJust) (getDigestByName "SHA1")
(OptETag str):[] -> return str
_ -> error "too many --etag options."
where
mkETagFromInput :: Digest -> String
- mkETagFromInput sha1 = "SHA-1:" ++ (toHex $ digestLBS sha1 input)
+ mkETagFromInput sha1 = "SHA-1:" ++ toHex (digestLBS sha1 input)
- toHex :: [Char] -> String
- toHex [] = ""
- toHex (x:xs) = hexByte (fromEnum x) ++ toHex xs
+ toHex :: String -> String
+ toHex = foldr ((++) . hexByte . fromEnum) ""
hexByte :: Int -> String
hexByte n
- = hex4bit ((n `shiftR` 4) .&. 0x0F) : hex4bit (n .&. 0x0F) : []
+ = [ hex4bit ((n `shiftR` 4) .&. 0x0F)
+ , hex4bit ( n .&. 0x0F)
+ ]
hex4bit :: Int -> Char
hex4bit n
- | n < 10 = (chr $ ord '0' + n )
- | n < 16 = (chr $ ord 'a' + n - 10)
+ | n < 10 = chr $ ord '0' + n
+ | n < 16 = chr $ ord 'a' + n - 10
| otherwise = undefined
Nothing
-> let res' = res { resStatus = aboStatus abo }
res'' = foldl (.) id [setHeader name value
- | (name, value) <- fromHeaders $ aboHeaders abo]
- $ res'
+ | (name, value) <- fromHeaders $ aboHeaders abo] res'
in
getDefaultPage conf reqM res''
where
import Data.Char
+import Data.Ord
import Data.Maybe
import Network.HTTP.Lucu.Parser
import Network.HTTP.Lucu.Parser.Http
orderAcceptEncodings :: (String, Maybe Double) -> (String, Maybe Double) -> Ordering
orderAcceptEncodings (_, q1) (_, q2)
- = fromMaybe 0 q1 `compare` fromMaybe 0 q2
+ = comparing (fromMaybe 0) q1 q2
+
getDefaultPage :: Config -> Maybe Request -> Response -> String
-getDefaultPage conf req res
- = conf `seq` req `seq` res `seq`
- let msgA = getMsg req res
+getDefaultPage !conf !req !res
+ = let msgA = getMsg req res
in
unsafePerformIO $
do [xmlStr] <- runX ( mkDefaultPage conf (resStatus res) msgA
writeDefaultPage :: Interaction -> STM ()
-writeDefaultPage itr
- = itr `seq`
- -- Content-Type が正しくなければ補完できない。
- do res <- readItr itr itrResponse id
+writeDefaultPage !itr
+ -- Content-Type が正しくなければ補完できない。
+ = do res <- readItr itr itrResponse id
when (getHeader (C8.pack "Content-Type") res == Just defaultPageContentType)
$ do reqM <- readItr itr itrRequest id
mkDefaultPage :: (ArrowXml a) => Config -> StatusCode -> a b XmlTree -> a b XmlTree
-mkDefaultPage conf status msgA
- = conf `seq` status `seq` msgA `seq`
- let (# sCode, sMsg #) = statusCode status
+mkDefaultPage !conf !status !msgA
+ = let (# sCode, sMsg #) = statusCode status
sig = C8.unpack (cnfServerSoftware conf)
++ " at "
++ C8.unpack (cnfServerHost conf)
{-# SPECIALIZE mkDefaultPage :: Config -> StatusCode -> IOSArrow b XmlTree -> IOSArrow b XmlTree #-}
getMsg :: (ArrowXml a) => Maybe Request -> Response -> a b XmlTree
-getMsg req res
- = req `seq` res `seq`
- case resStatus res of
+getMsg !req !res
+ = case resStatus res of
-- 1xx は body を持たない
-- 2xx の body は補完しない
where
fmt' :: Int -> String
fmt' m
- | m < base = (intToChar upperCase m) : []
+ | m < base = [intToChar upperCase m]
| otherwise = (intToChar upperCase $! m `mod` base) : fmt' (m `div` base)
fmtDec2 :: Int -> String
fmtDec2 n
| n < 0 || n >= 100 = fmtInt 10 undefined 2 '0' False n -- fallback
- | n < 10 = '0'
- : intToChar undefined n
- : []
- | otherwise = intToChar undefined (n `div` 10)
- : intToChar undefined (n `mod` 10)
- : []
+ | n < 10 = [ '0'
+ , intToChar undefined n
+ ]
+ | otherwise = [ intToChar undefined (n `div` 10)
+ , intToChar undefined (n `mod` 10)
+ ]
fmtDec3 :: Int -> String
fmtDec3 n
| n < 0 || n >= 1000 = fmtInt 10 undefined 3 '0' False n -- fallback
- | n < 10 = '0' : '0'
- : intToChar undefined n
- : []
- | n < 100 = '0'
- : intToChar undefined ((n `div` 10) `mod` 10)
- : intToChar undefined ( n `mod` 10)
- : []
- | otherwise = intToChar undefined ((n `div` 100) `mod` 10)
- : intToChar undefined ((n `div` 10) `mod` 10)
- : intToChar undefined ( n `mod` 10)
- : []
+ | n < 10 = [ '0'
+ , '0'
+ , intToChar undefined n
+ ]
+ | n < 100 = [ '0'
+ , intToChar undefined ((n `div` 10) `mod` 10)
+ , intToChar undefined ( n `mod` 10)
+ ]
+ | otherwise = [ intToChar undefined ((n `div` 100) `mod` 10)
+ , intToChar undefined ((n `div` 10) `mod` 10)
+ , intToChar undefined ( n `mod` 10)
+ ]
fmtDec4 :: Int -> String
fmtDec4 n
| n < 0 || n >= 10000 = fmtInt 10 undefined 4 '0' False n -- fallback
- | n < 10 = '0' : '0' : '0'
- : intToChar undefined n
- : []
- | n < 100 = '0' : '0'
- : intToChar undefined ((n `div` 10) `mod` 10)
- : intToChar undefined ( n `mod` 10)
- : []
- | n < 1000 = '0'
- : intToChar undefined ((n `div` 100) `mod` 10)
- : intToChar undefined ((n `div` 10) `mod` 10)
- : intToChar undefined ( n `mod` 10)
- : []
- | otherwise = intToChar undefined ((n `div` 1000) `mod` 10)
- : intToChar undefined ((n `div` 100) `mod` 10)
- : intToChar undefined ((n `div` 10) `mod` 10)
- : intToChar undefined ( n `mod` 10)
- : []
+ | n < 10 = [ '0'
+ , '0'
+ , '0'
+ , intToChar undefined n
+ ]
+ | n < 100 = [ '0'
+ , '0'
+ , intToChar undefined ((n `div` 10) `mod` 10)
+ , intToChar undefined ( n `mod` 10)
+ ]
+ | n < 1000 = [ '0'
+ , intToChar undefined ((n `div` 100) `mod` 10)
+ , intToChar undefined ((n `div` 10) `mod` 10)
+ , intToChar undefined ( n `mod` 10)
+ ]
+ | otherwise = [ intToChar undefined ((n `div` 1000) `mod` 10)
+ , intToChar undefined ((n `div` 100) `mod` 10)
+ , intToChar undefined ((n `div` 10) `mod` 10)
+ , intToChar undefined ( n `mod` 10)
+ ]
fmtHex :: Bool -> Int -> Int -> String
import Data.List
import Data.Map (Map)
import qualified Data.Map as M
+import Data.Ord
import Data.Word
import Foreign.ForeignPtr
import Foreign.Ptr
| otherwise
= do c1 <- peek p1
c2 <- peek p2
- case toLower (w2c c1) `compare` toLower (w2c c2) of
+ case comparing (toLower . w2c) c1 c2 of
EQ -> noCaseCmp' (p1 `plusPtr` 1) (l1 - 1) (p2 `plusPtr` 1) (l2 - 1)
x -> return x
normalize :: String -> String
normalize = trimBody . trim isWhiteSpace
- trimBody = foldr (++) []
+ trimBody = concat
. map (\ s -> if head s == ' ' then
" "
else
newInteraction :: Config -> SockAddr -> Maybe X509 -> Maybe Request -> IO Interaction
newInteraction !conf !addr !cert !req
- = do request <- newTVarIO $ req
- responce <- newTVarIO $ Response {
+ = do request <- newTVarIO req
+ responce <- newTVarIO Response {
resVersion = HttpVersion 1 1
, resStatus = Ok
, resHeaders = toHeaders [(C8.pack "Content-Type", defaultPageContentType)]
wroteContinue <- newTVarIO False
wroteHeader <- newTVarIO False
- return $ Interaction {
+ return Interaction {
itrConfig = conf
, itrRemoteAddr = addr
, itrRemoteCert = cert
writeItr :: Interaction -> (Interaction -> TVar a) -> a -> STM ()
-writeItr itr accessor value
- = itr `seq` accessor `seq` value `seq`
- writeTVar (accessor itr) value
+writeItr !itr !accessor !value
+ = writeTVar (accessor itr) value
readItr :: Interaction -> (Interaction -> TVar a) -> (a -> b) -> STM b
-readItr itr accessor reader
- = itr `seq` accessor `seq` reader `seq`
- readTVar (accessor itr) >>= return . reader
+readItr !itr !accessor !reader
+ = fmap reader $ readTVar (accessor itr)
readItrF :: Functor f => Interaction -> (Interaction -> TVar (f a)) -> (a -> b) -> STM (f b)
-readItrF itr accessor reader
- = itr `seq` accessor `seq` reader `seq`
- readItr itr accessor (fmap reader)
+readItrF !itr !accessor !reader
+ = readItr itr accessor (fmap reader)
{-# SPECIALIZE readItrF :: Interaction -> (Interaction -> TVar (Maybe a)) -> (a -> b) -> STM (Maybe b) #-}
updateItr :: Interaction -> (Interaction -> TVar a) -> (a -> a) -> STM ()
-updateItr itr accessor updator
- = itr `seq` accessor `seq` updator `seq`
- do old <- readItr itr accessor id
+updateItr !itr !accessor !updator
+ = do old <- readItr itr accessor id
writeItr itr accessor (updator old)
updateItrF :: Functor f => Interaction -> (Interaction -> TVar (f a)) -> (a -> a) -> STM ()
-updateItrF itr accessor updator
- = itr `seq` accessor `seq` updator `seq`
- updateItr itr accessor (fmap updator)
+updateItrF !itr !accessor !updator
+ = updateItr itr accessor (fmap updator)
{-# SPECIALIZE updateItrF :: Interaction -> (Interaction -> TVar (Maybe a)) -> (a -> a) -> STM () #-}
\ No newline at end of file
return !x = Parser $! return $! Success x
fail _ = Parser $! return $! IllegalInput
+instance Functor Parser where
+ fmap f p = p >>= return . f
+
-- |@'failP'@ is just a synonym for @'Prelude.fail'
-- 'Prelude.undefined'@.
failP :: Parser a
-- |'text' accepts one character which doesn't satisfy 'isCtl'.
text :: Parser Char
-text = satisfy (\ c -> not (isCtl c))
+text = satisfy (not . isCtl)
-- |'separator' accepts one character which satisfies 'isSeparator'.
separator :: Parser Char
-}
postprocess :: Interaction -> STM ()
-postprocess itr
- = itr `seq`
- do reqM <- readItr itr itrRequest id
+postprocess !itr
+ = do reqM <- readItr itr itrRequest id
res <- readItr itr itrResponse id
let sc = resStatus res
- when (not $ any (\ p -> p sc) [isSuccessful, isRedirection, isError])
+ unless (any (\ p -> p sc) [isSuccessful, isRedirection, isError])
$ abortSTM InternalServerError []
$ Just ("The status code is not good for a final status: "
++ show sc)
conn <- readHeader (C8.pack "Connection")
case conn of
Nothing -> return ()
- Just value -> if value `noCaseEq` C8.pack "close" then
- writeItr itr itrWillClose True
- else
- return ()
+ Just value -> when (value `noCaseEq` C8.pack "close")
+ $ writeItr itr itrWillClose True
willClose <- readItr itr itrWillClose id
when willClose
$ writeTVar (itrWillDiscardBody itr) True
readHeader :: Strict.ByteString -> STM (Maybe Strict.ByteString)
- readHeader name
- = name `seq`
- readItr itr itrResponse $ getHeader name
+ readHeader !name
+ = readItr itr itrResponse $ getHeader name
updateRes :: (Response -> Response) -> STM ()
- updateRes updator
- = updator `seq`
- updateItr itr itrResponse updator
+ updateRes !updator
+ = updateItr itr itrResponse updator
completeUnconditionalHeaders :: Config -> Response -> IO Response
-completeUnconditionalHeaders conf res
- = conf `seq` res `seq`
- return res >>= compServer >>= compDate >>= return
+completeUnconditionalHeaders !conf !res
+ = compServer res >>= compDate
where
compServer res'
= case getHeader (C8.pack "Server") res' of
where
mostlyEq :: UTCTime -> UTCTime -> Bool
mostlyEq a b
- = if utctDay a == utctDay b then
- fromEnum (utctDayTime a) == fromEnum (utctDayTime b)
- else
- False
+ = (utctDay a == utctDay b)
+ &&
+ (fromEnum (utctDayTime a) == fromEnum (utctDayTime b))
portStr
= case port of
Just 80 -> Just ""
- Just n -> Just $ ":" ++ show n
+ Just n -> Just $ ':' : show n
Nothing -> Nothing
case portStr of
Just str -> updateAuthority host (C8.pack str)
-- いと思ふ。stderr?
Nothing -> setStatus InternalServerError
else
- do case getHeader (C8.pack "Host") req of
- Just str -> let (host, portStr) = parseHost str
- in updateAuthority host portStr
- Nothing -> setStatus BadRequest
+ case getHeader (C8.pack "Host") req of
+ Just str -> let (host, portStr) = parseHost str
+ in updateAuthority host portStr
+ Nothing -> setStatus BadRequest
parseHost :: Strict.ByteString -> (Strict.ByteString, Strict.ByteString)
case getHeader (C8.pack "Transfer-Encoding") req of
Nothing -> return ()
- Just value -> if value `noCaseEq` C8.pack "identity" then
- return ()
- else
- if value `noCaseEq` C8.pack "chunked" then
- writeItr itr itrRequestIsChunked True
- else
- setStatus NotImplemented
+ Just value -> unless (value `noCaseEq` C8.pack "identity")
+ $ if value `noCaseEq` C8.pack "chunked" then
+ writeItr itr itrRequestIsChunked True
+ else
+ setStatus NotImplemented
case getHeader (C8.pack "Content-Length") req of
Nothing -> return ()
case getHeader (C8.pack "Connection") req of
Nothing -> return ()
- Just value -> if value `noCaseEq` C8.pack "close" then
- writeItr itr itrWillClose True
- else
- return ()
+ Just value -> when (value `noCaseEq` C8.pack "close")
+ $ writeItr itr itrWillClose True
methodP :: Parser Method
-methodP = (let methods = [ ("OPTIONS", OPTIONS)
- , ("GET" , GET )
- , ("HEAD" , HEAD )
- , ("POST" , POST )
- , ("PUT" , PUT )
- , ("DELETE" , DELETE )
- , ("TRACE" , TRACE )
- , ("CONNECT", CONNECT)
- ]
- in foldl (<|>) failP $ map (\ (str, mth)
- -> string str >> return mth) methods)
+methodP = ( let methods = [ ("OPTIONS", OPTIONS)
+ , ("GET" , GET )
+ , ("HEAD" , HEAD )
+ , ("POST" , POST )
+ , ("PUT" , PUT )
+ , ("DELETE" , DELETE )
+ , ("TRACE" , TRACE )
+ , ("CONNECT", CONNECT)
+ ]
+ in choice $ map (\ (str, mth)
+ -> string str >> return mth) methods )
<|>
- token >>= return . ExtensionMethod
+ fmap ExtensionMethod token
uriP :: Parser URI
driftTo Done
) itr
)
- $ \ exc -> processException exc
+ processException
where
fork :: IO () -> IO ThreadId
- fork = if (resUsesNativeThread def)
+ fork = if resUsesNativeThread def
then forkOS
else forkIO
setHeader (C8.pack "Allow") (C8.pack $ joinWith ", " allowedMethods)
allowedMethods :: [String]
- allowedMethods = nub $ foldr (++) [] [ methods resGet ["GET"]
- , methods resHead ["GET", "HEAD"]
- , methods resPost ["POST"]
- , methods resPut ["PUT"]
- , methods resDelete ["DELETE"]
- ]
+ allowedMethods = nub $ concat [ methods resGet ["GET"]
+ , methods resHead ["GET", "HEAD"]
+ , methods resPost ["POST"]
+ , methods resPut ["PUT"]
+ , methods resDelete ["DELETE"]
+ ]
methods :: (ResourceDef -> Maybe a) -> [String] -> [String]
methods f xs = case f def of
if state <= DecidingHeader then
flip runRes itr
$ do setStatus $ aboStatus abo
- mapM_ (\ (name, value) -> setHeader name value) $ fromHeaders $ aboHeaders abo
+ mapM_ (uncurry setHeader) $ fromHeaders $ aboHeaders abo
output $ abortPage conf reqM res abo
else
when (cnfDumpTooLateAbortionToStderr $ itrConfig itr)
awaitSomethingToWrite :: IO ()
awaitSomethingToWrite
= {-# SCC "awaitSomethingToWrite" #-}
- do action
- <- atomically $!
- -- キューが空でなくなるまで待つ
- do queue <- readTVar tQueue
- -- GettingBody 状態にあり、Continue が期待され
- -- ã\81¦ã\82\90ã\81¦ã\80\81ã\81\9dã\82\8cã\81\8cã\81¾ã\81 é\80\81ä¿¡å\89\8dã\81ªã\81®ã\81§ã\81\82ã\82\8cã\81°ã\80\81
- -- Continue を送信する。
- case S.viewr queue of
- EmptyR -> retry
- _ :> itr -> do state <- readItr itr itrState id
+ join $!
+ atomically $!
+ -- キューが空でなくなるまで待つ
+ do queue <- readTVar tQueue
+ -- GettingBody 状態にあり、Continue が期待されてゐ
+ -- ã\81¦ã\80\81ã\81\9dã\82\8cã\81\8cã\81¾ã\81 é\80\81ä¿¡å\89\8dã\81ªã\81®ã\81§ã\81\82ã\82\8cã\81°ã\80\81Continue ã\82\92é\80\81
+ -- 信する。
+ case S.viewr queue of
+ EmptyR -> retry
+ _ :> itr -> do state <- readItr itr itrState id
- if state == GettingBody then
- writeContinueIfNecessary itr
- else
- if state >= DecidingBody then
- writeHeaderOrBodyIfNecessary itr
- else
- retry
- action
+ if state == GettingBody then
+ writeContinueIfNecessary itr
+ else
+ if state >= DecidingBody then
+ writeHeaderOrBodyIfNecessary itr
+ else
+ retry
writeContinueIfNecessary :: Interaction -> STM (IO ())
- writeContinueIfNecessary itr
+ writeContinueIfNecessary !itr
= {-# SCC "writeContinueIfNecessary" #-}
- itr `seq`
do expectedContinue <- readItr itr itrExpectedContinue id
if expectedContinue then
do wroteContinue <- readItr itr itrWroteContinue id
retry
writeHeaderOrBodyIfNecessary :: Interaction -> STM (IO ())
- writeHeaderOrBodyIfNecessary itr
+ writeHeaderOrBodyIfNecessary !itr
-- DecidingBody 以降の状態にあり、まだヘッダを出力する前であ
-- れば、ヘッダを出力する。ヘッダ出力後であり、bodyToSend が
-- 空でなければ、それを出力する。空である時は、もし状態が
-- Done であれば後処理をする。
= {-# SCC "writeHeaderOrBodyIfNecessary" #-}
- itr `seq`
do wroteHeader <- readItr itr itrWroteHeader id
if not wroteHeader then
return $! writeBodyChunk itr
writeContinue :: Interaction -> IO ()
- writeContinue itr
+ writeContinue !itr
= {-# SCC "writeContinue" #-}
- itr `seq`
do let cont = Response {
resVersion = HttpVersion 1 1
, resStatus = Continue
awaitSomethingToWrite
writeHeader :: Interaction -> IO ()
- writeHeader itr
+ writeHeader !itr
= {-# SCC "writeHeader" #-}
- itr `seq`
do res <- atomically $! do writeItr itr itrWroteHeader True
readItr itr itrResponse id
hPutResponse h res
awaitSomethingToWrite
writeBodyChunk :: Interaction -> IO ()
- writeBodyChunk itr
+ writeBodyChunk !itr
= {-# SCC "writeBodyChunk" #-}
- itr `seq`
do willDiscardBody <- atomically $! readItr itr itrWillDiscardBody id
willChunkBody <- atomically $! readItr itr itrWillChunkBody id
chunk <- atomically $! do chunk <- readItr itr itrBodyToSend id
awaitSomethingToWrite
finishBodyChunk :: Interaction -> IO ()
- finishBodyChunk itr
+ finishBodyChunk !itr
= {-# SCC "finishBodyChunk" #-}
- itr `seq`
do willDiscardBody <- atomically $! readItr itr itrWillDiscardBody id
willChunkBody <- atomically $! readItr itr itrWillChunkBody id
when (not willDiscardBody && willChunkBody)
$ hPutLBS h (C8.pack "0\r\n\r\n") >> hFlush h
finalize :: Interaction -> IO ()
- finalize itr
+ finalize !itr
= {-# SCC "finalize" #-}
- itr `seq`
do finishBodyChunk itr
willClose <- atomically $!
do queue <- readTVar tQueue
$ abort Forbidden [] Nothing
-- 讀める
tag <- liftIO $ generateETagFromFile path
- lastMod <- return $ posixSecondsToUTCTime $ fromRational $ toRational $ modificationTime stat
+ let lastMod = posixSecondsToUTCTime $ fromRational $ toRational $ modificationTime stat
foundEntity tag lastMod
-- MIME Type を推定
Just mime -> setContentType mime
-- 實際にファイルを讀んで送る
- (liftIO $ B.readFile path) >>= outputLBS
+ liftIO (B.readFile path) >>= outputLBS
else
abort Forbidden [] Nothing
else
splitBy :: (a -> Bool) -> [a] -> [[a]]
splitBy isSep src
= case break isSep src
- of (last , [] ) -> last : []
+ of (last , [] ) -> [last]
(first, _sep:rest) -> first : splitBy isSep rest
-- |> joinWith ":" ["ab", "c", "def"]
RM_RF ?= rm -rf
SUDO ?= sudo
AUTOCONF ?= autoconf
+HLINT ?= hlint
CONFIGURE_ARGS ?= --disable-optimization
test: build
./Setup test
-.PHONY: build build-hook setup-config setup-config-hook run clean clean-hook install doc sdist test
+lint:
+ $(HLINT) . --report \
+ --ignore="Use string literal" \
+ --ignore="Use concatMap"
+
+.PHONY: build build-hook setup-config setup-config-hook run clean clean-hook install doc sdist test lint