image-backup/src/MyLib.hs

119 lines
4.3 KiB
Haskell
Raw Normal View History

2023-02-12 14:47:48 +02:00
{-# LANGUAGE TypeOperators #-}
2023-02-15 20:34:05 +02:00
{-# LANGUAGE NumericUnderscores #-}
2023-02-13 17:05:32 +02:00
{-# LANGUAGE OverloadedStrings #-}
2023-02-12 14:47:48 +02:00
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE DeriveGeneric #-}
2023-02-13 17:05:32 +02:00
{-# LANGUAGE DataKinds #-}
2023-02-15 20:34:05 +02:00
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TupleSections #-}
2023-02-13 17:05:32 +02:00
module MyLib where
2023-02-12 14:19:45 +02:00
2023-02-12 14:47:48 +02:00
import Network.Wai.Metrics (metrics, registerWaiMetrics)
import System.Metrics
(Store, newStore, registerGcMetrics)
import Servant.Metrics.Prometheus
import Network.Wai.Handler.Warp (runSettings, defaultSettings, setPort)
import Servant
import GHC.Generics (Generic)
2023-02-13 17:05:32 +02:00
import Conduit (runConduit, (.|), MonadUnliftIO, liftIO, ConduitT, MonadResource)
import System.FilePath (isExtensionOf, takeBaseName)
import qualified Data.Conduit.Combinators as C
import Crypto.Hash (HashAlgorithm, Digest, SHA256)
import qualified Crypto.Hash as Crypto
import Amazonka (newEnv, Region(..), Env, Env'(..), setEndpoint, runResourceT, send, chunkedFile, defaultChunkSize)
import Amazonka.Auth (discover)
import qualified Amazonka.S3 as S3
import qualified Data.Text as T
2023-02-15 20:34:05 +02:00
import Control.Lens (view, set, (&), re)
import Data.Generics.Labels ()
import Control.Monad (void, forever)
2023-02-13 17:05:32 +02:00
import Data.HashMap.Strict (HashMap)
import Data.Text (Text)
import qualified Data.HashMap.Strict as HM
2023-02-15 20:34:05 +02:00
import System.Environment (getEnv)
import qualified Dhall
import Config (Config)
import Data.Text.Strict.Lens (utf8)
import Config.Watcher (Seconds)
import Control.Concurrent (threadDelay)
import UnliftIO (forConcurrently_)
import Data.Word (Word64)
import Image.Fingerprint (dhash)
import Data.Maybe (catMaybes)
2023-02-12 14:47:48 +02:00
newtype Routes route
= Routes { _getMetrics :: route :- MetricsRoute }
deriving (Generic)
type API = NamedRoutes Routes
app :: Store -> Application
app store = serve (Proxy @API) Routes { _getMetrics = metricsServer store }
2023-02-13 17:05:32 +02:00
hash :: (HashAlgorithm a, MonadUnliftIO m) => FilePath -> m (Digest a)
hash path = C.withSourceFile path $ \source ->
Crypto.hashFinalize <$> runConduit (source .| C.foldl Crypto.hashUpdate Crypto.hashInit)
data Image = Image
{ imagePath :: !FilePath
, imageHash :: !(Digest SHA256)
2023-02-15 20:34:05 +02:00
, imageFingerprint :: !(Maybe Word64)
2023-02-13 17:05:32 +02:00
}
deriving Show
imageToMetadata :: Image -> HashMap Text Text
2023-02-15 20:34:05 +02:00
imageToMetadata img = HM.fromList $ catMaybes
[ Just ("sha256", T.pack . show . imageHash $ img)
, ("fingerprint", ) . T.pack . show <$> imageFingerprint img
]
2023-02-13 17:05:32 +02:00
uploadImage :: Env -> S3.BucketName -> Image -> IO S3.PutObjectResponse
uploadImage env bucket img = do
obj <- chunkedFile defaultChunkSize (imagePath img)
runResourceT $ do
2023-02-15 20:34:05 +02:00
let putObj = S3.newPutObject bucket key obj & set #metadata mt & set #contentType (Just "image/jpeg")
2023-02-13 17:05:32 +02:00
key = S3.ObjectKey (T.pack . takeBaseName . imagePath $ img)
mt = imageToMetadata img
send env putObj
scan :: (MonadResource m) => FilePath -> (FilePath -> Bool) -> ConduitT () FilePath m ()
scan root predicate = C.sourceDirectoryDeep False root .| C.filter predicate
analyze :: (MonadUnliftIO m) => ConduitT FilePath Image m ()
2023-02-15 20:34:05 +02:00
analyze = C.mapM (\p -> Image p <$> hash p <*> fingerprint p)
where
fingerprint = fmap (either (const Nothing) Just) . liftIO . dhash
watcher :: Env -> S3.BucketName -> FilePath -> Seconds -> IO ()
watcher env bucket path delay = forever $ do
runResourceT $ runConduit $ scan path (isExtensionOf ".jpg")
.| analyze
.| C.iterM (liftIO . print)
.| C.mapM_ (void . liftIO . uploadImage env bucket)
threadDelay (fromIntegral (view #seconds delay) * 100_000)
2023-02-13 17:05:32 +02:00
2023-02-12 14:19:45 +02:00
someFunc :: IO ()
2023-02-12 14:47:48 +02:00
someFunc = do
2023-02-15 20:34:05 +02:00
confPath <- getEnv "CONFIG_PATH"
conf <- Dhall.inputFile (Dhall.auto @Config) confPath
2023-02-13 17:05:32 +02:00
discoveredEnv <- newEnv discover
let env = discoveredEnv
2023-02-15 20:34:05 +02:00
{ region = Region' $ view (#s3 . #region) conf
, overrides = setEndpoint True (view (#s3 . #endpoint . re utf8) conf) 443
2023-02-13 17:05:32 +02:00
}
2023-02-15 20:34:05 +02:00
bucket = S3.BucketName (view (#s3 . #bucket) conf)
2023-02-12 14:47:48 +02:00
store <- newStore
waiMetrics <- registerWaiMetrics store
registerGcMetrics store
2023-02-15 20:34:05 +02:00
let watchers = [watcher env bucket path (view (#watcher . #period) conf) | path <- view (#watcher . #directories) conf]
actions = ( runSettings settings (metrics waiMetrics $ app store) ) : watchers
forConcurrently_ actions id
-- runSettings settings (metrics waiMetrics $ app store)
2023-02-12 14:47:48 +02:00
where
settings =
defaultSettings &
setPort 8099
-- setOnException onException