module Taskell.IO.Config.Layout ( Config , defaultConfig , parser , padding , columnWidth , columnPadding , descriptionIndicator , statusBar ) where import ClassyPrelude import Data.Ini.Config import Taskell.IO.Config.Parser (noEmpty, parseText) data Config = Config { Config -> Int padding :: Int , Config -> Int columnWidth :: Int , Config -> Int columnPadding :: Int , Config -> Text descriptionIndicator :: Text , Config -> Bool statusBar :: Bool } defaultConfig :: Config defaultConfig :: Config defaultConfig = Config :: Int -> Int -> Int -> Text -> Bool -> Config Config {padding :: Int padding = Int 1, columnWidth :: Int columnWidth = Int 30, columnPadding :: Int columnPadding = Int 3, descriptionIndicator :: Text descriptionIndicator = Text "≡", statusBar :: Bool statusBar = Bool True} paddingP :: SectionParser Int paddingP :: SectionParser Int paddingP = Int -> Maybe Int -> Int forall a. a -> Maybe a -> a fromMaybe (Config -> Int padding Config defaultConfig) (Maybe Int -> Int) -> SectionParser (Maybe Int) -> SectionParser Int forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Text -> (Text -> Either String Int) -> SectionParser (Maybe Int) forall a. Text -> (Text -> Either String a) -> SectionParser (Maybe a) fieldMbOf Text "padding" Text -> Either String Int forall a. (Num a, Read a, Typeable a) => Text -> Either String a number columnWidthP :: SectionParser Int columnWidthP :: SectionParser Int columnWidthP = Int -> Maybe Int -> Int forall a. a -> Maybe a -> a fromMaybe (Config -> Int columnWidth Config defaultConfig) (Maybe Int -> Int) -> SectionParser (Maybe Int) -> SectionParser Int forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Text -> (Text -> Either String Int) -> SectionParser (Maybe Int) forall a. Text -> (Text -> Either String a) -> SectionParser (Maybe a) fieldMbOf Text "column_width" Text -> Either String Int forall a. (Num a, Read a, Typeable a) => Text -> Either String a number columnPaddingP :: SectionParser Int columnPaddingP :: SectionParser Int columnPaddingP = Int -> Maybe Int -> Int forall a. a -> Maybe a -> a fromMaybe (Config -> Int columnPadding Config defaultConfig) (Maybe Int -> Int) -> SectionParser (Maybe Int) -> SectionParser Int forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Text -> (Text -> Either String Int) -> SectionParser (Maybe Int) forall a. Text -> (Text -> Either String a) -> SectionParser (Maybe a) fieldMbOf Text "column_padding" Text -> Either String Int forall a. (Num a, Read a, Typeable a) => Text -> Either String a number descriptionIndicatorP :: SectionParser Text descriptionIndicatorP :: SectionParser Text descriptionIndicatorP = Text -> Maybe Text -> Text forall a. a -> Maybe a -> a fromMaybe (Config -> Text descriptionIndicator Config defaultConfig) (Maybe Text -> Text) -> (Maybe Text -> Maybe Text) -> Maybe Text -> Text forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . (Text -> Maybe Text noEmpty (Text -> Maybe Text) -> (Text -> Text) -> Text -> Maybe Text forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . Text -> Text parseText (Text -> Maybe Text) -> Maybe Text -> Maybe Text forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b =<<) (Maybe Text -> Text) -> SectionParser (Maybe Text) -> SectionParser Text forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Text -> SectionParser (Maybe Text) fieldMb Text "description_indicator" statusBarP :: SectionParser Bool statusBarP :: SectionParser Bool statusBarP = Text -> Bool -> SectionParser Bool fieldFlagDef Text "statusbar" (Config -> Bool statusBar Config defaultConfig) parser :: IniParser Config parser :: IniParser Config parser = Config -> Maybe Config -> Config forall a. a -> Maybe a -> a fromMaybe Config defaultConfig (Maybe Config -> Config) -> IniParser (Maybe Config) -> IniParser Config forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Text -> SectionParser Config -> IniParser (Maybe Config) forall a. Text -> SectionParser a -> IniParser (Maybe a) sectionMb Text "layout" (Int -> Int -> Int -> Text -> Bool -> Config Config (Int -> Int -> Int -> Text -> Bool -> Config) -> SectionParser Int -> SectionParser (Int -> Int -> Text -> Bool -> Config) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> SectionParser Int paddingP SectionParser (Int -> Int -> Text -> Bool -> Config) -> SectionParser Int -> SectionParser (Int -> Text -> Bool -> Config) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> SectionParser Int columnWidthP SectionParser (Int -> Text -> Bool -> Config) -> SectionParser Int -> SectionParser (Text -> Bool -> Config) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> SectionParser Int columnPaddingP SectionParser (Text -> Bool -> Config) -> SectionParser Text -> SectionParser (Bool -> Config) forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> SectionParser Text descriptionIndicatorP SectionParser (Bool -> Config) -> SectionParser Bool -> SectionParser Config forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> SectionParser Bool statusBarP)