{-# LANGUAGE UnicodeSyntax, MultiParamTypeClasses #-}

module Todos.Config where

import Prelude.Unicode
import Control.Monad.Reader

import Todos.Types
import Todos.Dot
import qualified System.Console.ANSI as ANSI

-- | Any user-specified runtime config type should belong to this class
class RuntimeConfig c where
  -- | Does given TODO item match query?
  getPredicate āˆ· DateTime ā†’ c ā†’ (TodoItem ā†’ š”¹) 
  -- | Get basic configuration
  toBaseConfig āˆ· c ā†’ BaseConfig

-- | Any user-specified runtime config type should include at least this properties
data BaseConfig = BConfig {
      outOnlyFirst āˆ· š”¹,           -- ^ Output only first matching entry
      outColors āˆ· š”¹,              -- ^ Show colored output
      outIds :: š”¹,                -- ^ Show IDs
      outHighlight āˆ· š”¹,           -- ^ Highlight matching items
      sorting āˆ· SortingType,      -- ^ How to sort items
      pruneL āˆ· Limit, 
      minL   āˆ· Limit,
      commandToRun āˆ· TodoCommand,
      prefix āˆ· Maybe String,      -- ^ Nothing ā€” use default parser, Just p ā€” use alternate parser with prefix Ā«pĀ»
      outputFormat āˆ· String,
      indentString āˆ· String,      -- ^ String to use for output tree indenting (two spaces by default)
      skipStatus āˆ· š”¹,             -- ^ Skip status field in input
      groupByFile āˆ· š”¹,
      groupByTag āˆ· š”¹,
      groupByStatus āˆ· š”¹,
      forcedStatus āˆ· Maybe String,
      topStatus āˆ· Maybe String
      }
    deriving (Eq, Show)

-- | Configuration for console output. Is generated in runtime from TodosConfig and Config.
data PrintConfig c = PConfig {
  printConfig āˆ· c,
  printStatusColor āˆ·  String ā†’ (ANSI.ColorIntensity, ANSI.Color),       -- ^ Color of status field from status
  printItemColor āˆ·  TodoItem ā†’ Maybe (ANSI.ColorIntensity, ANSI.Color), -- ^ Color of item name
  printHighlightColor āˆ· (ANSI.ColorIntensity, ANSI.Color),              -- ^ Color to use for highlighting
  doHighlight āˆ· TodoItem ā†’ š”¹                                            -- ^ Whether to highlight given item
  }

-- | User Todos config. User can specify it in @~/.config/todos/todos.hs@.
data TodosConfig c = Todos {
     parseCommandLine āˆ· DateTime ā†’ c ā†’ [String] ā†’ CmdLineParseResult c,     -- ^ Function to parse command line
     filterTodos āˆ· DateTime ā†’ c ā†’ [Todo] ā†’ [Todo],                          -- ^ Any function to be run to transform read TODOs tree
     statusConsoleColor āˆ· String ā†’ (ANSI.ColorIntensity, ANSI.Color),       -- ^ Function to select a color of item's status field in console output
     itemConsoleColor āˆ· TodoItem ā†’ Maybe (ANSI.ColorIntensity, ANSI.Color), -- ^ Function to select a color of item's name in console output
     highlightColor āˆ· (ANSI.ColorIntensity, ANSI.Color),                    -- ^ Color to use for highlighting
     itemColor āˆ· TodoItem ā†’ HSV,                                            -- ^ Function to select color for item's node in DOT output
     itemShape āˆ· TodoItem ā†’ Shape,                                          -- ^ Function to select shape for item's node in DOT output
     printTodos āˆ· PrintConfig c ā†’ [Todo] ā†’ IO (),                           -- ^ Any function to output TODOs list
     nullConfig āˆ· c                                                         -- ^ Default Config (to be used without any options in command line and configs)
}

-- | Result of parsing command line
data CmdLineParseResult c = 
     Parsed c [FilePath]       -- ^ Parsed successfully, got Config and list of source files
   | ParseError String         -- ^ Some error occured
   | CmdLineHelp               -- ^ User asked for help
   deriving (Eq,Show)

-- | ask field from BaseConfig
askBase āˆ· (RuntimeConfig c) ā‡’ (BaseConfig ā†’ a) ā†’ Reader c a
askBase field = asks (field āˆ˜ toBaseConfig)