Split to multiproject

This commit is contained in:
2022-05-16 21:42:11 +03:00
parent 0266d4b06b
commit 03b4cfb3bf
35 changed files with 70 additions and 8 deletions

View File

@ -0,0 +1,80 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE TypeOperators #-}
module Data.Config where
import Control.Lens
import Data.Text (Text)
import Dhall (FromDhall, Generic, ToDhall, auto, inputFile)
import Dhall.Deriving
import Numeric.Natural (Natural)
import Data.SubReddit (SubReddit)
data Password
= Password Text
| File FilePath
deriving stock (Generic, Show)
deriving (FromDhall, ToDhall)
via (Codec AsIs Password)
data AMQP = AMQP
{ amqpVhost :: Text
, amqpUsername :: Text
, amqpPassword :: Password
, amqpHost :: Text
}
deriving stock (Generic, Show)
deriving (FromDhall, ToDhall)
via (Codec (Field (CamelCase <<< DropPrefix "amqp"))) AMQP
host :: Lens' AMQP Text
host = lens amqpHost (\ am txt -> am{amqpHost=txt})
vhost :: Lens' AMQP Text
vhost = lens amqpVhost (\ am txt -> am{amqpVhost=txt})
username :: Lens' AMQP Text
username = lens amqpUsername (\ am txt -> am{amqpUsername=txt})
password :: Lens' AMQP Password
password = lens amqpPassword (\ am txt -> am{amqpPassword=txt})
data Fetcher = Fetcher
{ fetcherSubreddit :: SubReddit
, fetcherEntries :: Natural
, fetcherQualifier :: Maybe Qualifier
}
deriving stock (Show, Generic)
deriving (FromDhall, ToDhall) via Codec (Field (CamelCase <<< DropPrefix "fetcher")) Fetcher
subreddit :: Lens' Fetcher SubReddit
subreddit = lens fetcherSubreddit (\ fe sr -> fe{fetcherSubreddit=sr})
entries :: Lens' Fetcher Natural
entries = lens fetcherEntries (\ fe nat -> fe{fetcherEntries=nat})
data Qualifier = Top | Controversial
deriving stock (Show, Generic)
deriving (FromDhall, ToDhall) via Codec (Constructor TitleCase) Qualifier
data Config = Config
{ configAmqp :: AMQP
, configFetchers :: [Fetcher]
, configSqlite :: FilePath
}
deriving stock (Generic, Show)
deriving (FromDhall, ToDhall)
via (Codec (Field (CamelCase <<< DropPrefix "config"))) Config
amqp :: Lens' Config AMQP
amqp = lens configAmqp (\ con am -> con{configAmqp=am})
fetchers :: Lens' Config [Fetcher]
fetchers = lens configFetchers (\ con fes -> con{configFetchers=fes})
sqlite :: Lens' Config FilePath
sqlite = lens configSqlite (\ con s -> con{configSqlite=s})
readConfig :: FilePath -> IO Config
readConfig = inputFile auto

View File

@ -0,0 +1,41 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Deriving.Aeson
( AesonCodec(..)
, type (<<<)
, Field
, CamelCase
, DropPrefix
)
where
import Control.Lens
import Data.Aeson
import qualified Data.Text.Strict.Lens as T
import Dhall.Deriving
import GHC.Generics (Generic, Rep)
newtype AesonCodec codec a = AesonCodec a
class ModifyAesonOptions a where
modifyAesonOptions :: Options -> Options
instance (ModifyAesonOptions f, ModifyAesonOptions g) => ModifyAesonOptions (f <<< g) where
modifyAesonOptions = modifyAesonOptions @f . modifyAesonOptions @g
instance TextFunction f => ModifyAesonOptions (Field f) where
modifyAesonOptions opts = opts{fieldLabelModifier = over T.packed (textFunction @f) }
instance (Generic a, ModifyAesonOptions codec, GToJSON' Value Zero (Rep a))
=> ToJSON (AesonCodec codec a) where
toJSON (AesonCodec a) =
genericToJSON (modifyAesonOptions @codec defaultOptions) a
instance (ModifyAesonOptions codec, Generic a, GFromJSON Zero (Rep a))
=> FromJSON (AesonCodec codec a) where
parseJSON va =
AesonCodec <$> genericParseJSON (modifyAesonOptions @codec defaultOptions) va

View File

@ -0,0 +1,9 @@
{-# LANGUAGE DerivingVia #-}
module Data.SubReddit where
import Dhall (FromDhall, ToDhall)
newtype SubReddit = SubReddit { getSubReddit :: String }
deriving Show
deriving (FromDhall, ToDhall) via String