cli/ui/web: rename X.Options modules to X.XOptions

Make these modules' names more like the heavily-used types they
define (CliOpts, UIOpts, WebOpts). This is consistent with
RawOptions and ReportOptions, and helps with code navigation.
This commit is contained in:
Simon Michael 2015-08-28 12:33:33 -07:00
parent 8673332c8e
commit 74512814ec
37 changed files with 54 additions and 54 deletions

View File

@ -4,18 +4,18 @@ Re-export the modules of the hledger-chart program.
module Hledger.Chart ( module Hledger.Chart (
module Hledger.Chart.Main, module Hledger.Chart.Main,
module Hledger.Chart.Options, module Hledger.Chart.ChartOptions,
tests_Hledger_Chart tests_Hledger_Chart
) )
where where
import Test.HUnit import Test.HUnit
import Hledger.Chart.Main import Hledger.Chart.Main
import Hledger.Chart.Options import Hledger.Chart.ChartOptions
tests_Hledger_Chart :: Test tests_Hledger_Chart :: Test
tests_Hledger_Chart = TestList tests_Hledger_Chart = TestList
[ [
-- tests_Hledger_Chart_Main -- tests_Hledger_Chart_Main
-- tests_Hledger_Chart_Options -- tests_Hledger_Chart_ChartOptions
] ]

View File

@ -23,7 +23,7 @@ import Text.Printf
import Hledger import Hledger
import Hledger.Cli hiding (progname,progversion) import Hledger.Cli hiding (progname,progversion)
import Hledger.Chart.Options import Hledger.Chart.ChartOptions
main :: IO () main :: IO ()
main = do main = do

View File

@ -3,7 +3,7 @@
-} -}
module Hledger.Chart.Options module Hledger.Chart.ChartOptions
where where
import Data.Maybe import Data.Maybe
import System.Console.CmdArgs import System.Console.CmdArgs

View File

@ -71,7 +71,7 @@ ptrace msg = do
-- a higher value (note: not @--debug N@ for some reason). This uses -- a higher value (note: not @--debug N@ for some reason). This uses
-- unsafePerformIO and can be accessed from anywhere and before normal -- unsafePerformIO and can be accessed from anywhere and before normal
-- command-line processing. After command-line processing, it is also -- command-line processing. After command-line processing, it is also
-- available as the @debug_@ field of 'Hledger.Cli.Options.CliOpts'. -- available as the @debug_@ field of 'Hledger.Cli.CliOptions.CliOpts'.
-- {-# OPTIONS_GHC -fno-cse #-} -- {-# OPTIONS_GHC -fno-cse #-}
-- {-# NOINLINE debugLevel #-} -- {-# NOINLINE debugLevel #-}
debugLevel :: Int debugLevel :: Int

View File

@ -4,7 +4,7 @@ Re-export the modules of the hledger-ui program.
module Hledger.UI ( module Hledger.UI (
module Hledger.UI.Main, module Hledger.UI.Main,
module Hledger.UI.Options, module Hledger.UI.UIOptions,
module Hledger.UI.Theme, module Hledger.UI.Theme,
tests_Hledger_UI tests_Hledger_UI
) )
@ -12,12 +12,12 @@ where
import Test.HUnit import Test.HUnit
import Hledger.UI.Main import Hledger.UI.Main
import Hledger.UI.Options import Hledger.UI.UIOptions
import Hledger.UI.Theme import Hledger.UI.Theme
tests_Hledger_UI :: Test tests_Hledger_UI :: Test
tests_Hledger_UI = TestList tests_Hledger_UI = TestList
[ [
-- tests_Hledger_UI_Main -- tests_Hledger_UI_Main
-- tests_Hledger_UI_Options -- tests_Hledger_UI_UIOptions
] ]

View File

@ -25,8 +25,8 @@ import Brick.Widgets.List
import Hledger import Hledger
import Hledger.Cli hiding (progname,prognameandversion,green) import Hledger.Cli hiding (progname,prognameandversion,green)
-- import Hledger.Cli.Options (defaultBalanceLineFormat) -- import Hledger.Cli.CliOptions (defaultBalanceLineFormat)
import Hledger.UI.Options import Hledger.UI.UIOptions
-- import Hledger.UI.Theme -- import Hledger.UI.Theme
import Hledger.UI.UITypes import Hledger.UI.UITypes
import Hledger.UI.UIUtils import Hledger.UI.UIUtils

View File

@ -26,7 +26,7 @@ import Brick
import Hledger import Hledger
import Hledger.Cli hiding (progname,prognameandversion,green) import Hledger.Cli hiding (progname,prognameandversion,green)
import Hledger.UI.Options import Hledger.UI.UIOptions
import Hledger.UI.UITypes import Hledger.UI.UITypes
-- import Hledger.UI.UIUtils -- import Hledger.UI.UIUtils
import Hledger.UI.Theme import Hledger.UI.Theme

View File

@ -24,7 +24,7 @@ import Brick.Widgets.List
import Hledger import Hledger
import Hledger.Cli hiding (progname,prognameandversion,green) import Hledger.Cli hiding (progname,prognameandversion,green)
import Hledger.UI.Options import Hledger.UI.UIOptions
-- import Hledger.UI.Theme -- import Hledger.UI.Theme
import Hledger.UI.UITypes import Hledger.UI.UITypes
import Hledger.UI.UIUtils import Hledger.UI.UIUtils

View File

@ -3,7 +3,7 @@
-} -}
module Hledger.UI.Options module Hledger.UI.UIOptions
where where
#if !MIN_VERSION_base(4,8,0) #if !MIN_VERSION_base(4,8,0)
import Data.Functor.Compat ((<$>)) import Data.Functor.Compat ((<$>))

View File

@ -6,7 +6,7 @@ import Brick
import Brick.Widgets.List (List) import Brick.Widgets.List (List)
import Hledger import Hledger
import Hledger.UI.Options import Hledger.UI.UIOptions
---------------------------------------------------------------------- ----------------------------------------------------------------------

View File

@ -76,7 +76,7 @@ executable hledger-ui
other-modules: other-modules:
Hledger.UI Hledger.UI
Hledger.UI.Main Hledger.UI.Main
Hledger.UI.Options Hledger.UI.UIOptions
Hledger.UI.Theme Hledger.UI.Theme
Hledger.UI.UITypes Hledger.UI.UITypes
Hledger.UI.UIUtils Hledger.UI.UIUtils

View File

@ -36,11 +36,11 @@ import Handler.JournalR
import Handler.RegisterR import Handler.RegisterR
import Handler.SidebarR import Handler.SidebarR
import Hledger.Web.Options (WebOpts(..), defwebopts) import Hledger.Web.WebOptions (WebOpts(..), defwebopts)
import Hledger.Data (Journal, nulljournal) import Hledger.Data (Journal, nulljournal)
import Hledger.Read (readJournalFile) import Hledger.Read (readJournalFile)
import Hledger.Utils (error') import Hledger.Utils (error')
import Hledger.Cli.Options (defcliopts, journalFilePathFromOpts) import Hledger.Cli.CliOptions (defcliopts, journalFilePathFromOpts)
-- This line actually creates our YesodDispatch instance. It is the second half -- This line actually creates our YesodDispatch instance. It is the second half
-- of the call to mkYesodData which occurs in Foundation.hs. Please see the -- of the call to mkYesodData which occurs in Foundation.hs. Please see the

View File

@ -30,7 +30,7 @@ import Text.Jasmine (minifym)
import Text.Blaze.Html.Renderer.String (renderHtml) import Text.Blaze.Html.Renderer.String (renderHtml)
import Text.Hamlet (hamletFile) import Text.Hamlet (hamletFile)
import Hledger.Web.Options import Hledger.Web.WebOptions
import Hledger.Data.Types import Hledger.Data.Types
-- import Hledger.Web.Settings -- import Hledger.Web.Settings
-- import Hledger.Web.Settings.StaticFiles -- import Hledger.Web.Settings.StaticFiles

View File

@ -21,8 +21,8 @@ import Hledger.Utils
import Hledger.Data import Hledger.Data
import Hledger.Query import Hledger.Query
import Hledger.Reports import Hledger.Reports
import Hledger.Cli.Options import Hledger.Cli.CliOptions
import Hledger.Web.Options import Hledger.Web.WebOptions
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
-- Common page layout -- Common page layout

View File

@ -12,8 +12,8 @@ import Hledger.Data
import Hledger.Query import Hledger.Query
import Hledger.Reports import Hledger.Reports
import Hledger.Utils import Hledger.Utils
import Hledger.Cli.Options import Hledger.Cli.CliOptions
import Hledger.Web.Options import Hledger.Web.WebOptions
-- | The formatted journal view, with sidebar. -- | The formatted journal view, with sidebar.
getJournalR :: Handler Html getJournalR :: Handler Html

View File

@ -17,8 +17,8 @@ import Hledger.Data
import Hledger.Query import Hledger.Query
import Hledger.Reports import Hledger.Reports
import Hledger.Utils import Hledger.Utils
import Hledger.Cli.Options import Hledger.Cli.CliOptions
import Hledger.Web.Options import Hledger.Web.WebOptions
-- | The main journal/account register view, with accounts sidebar. -- | The main journal/account register view, with accounts sidebar.
getRegisterR :: Handler Html getRegisterR :: Handler Html

View File

@ -3,19 +3,19 @@ Re-export the modules of the hledger-web program.
-} -}
module Hledger.Web ( module Hledger.Web (
module Hledger.Web.Options, module Hledger.Web.WebOptions,
module Hledger.Web.Main, module Hledger.Web.Main,
tests_Hledger_Web tests_Hledger_Web
) )
where where
import Test.HUnit import Test.HUnit
import Hledger.Web.Options import Hledger.Web.WebOptions
import Hledger.Web.Main import Hledger.Web.Main
tests_Hledger_Web :: Test tests_Hledger_Web :: Test
tests_Hledger_Web = TestList tests_Hledger_Web = TestList
[ [
-- tests_Hledger_Web_Options -- tests_Hledger_Web_WebOptions
-- ,tests_Hledger_Web_Main -- ,tests_Hledger_Web_Main
] ]

View File

@ -32,7 +32,7 @@ import Prelude hiding (putStrLn)
import Hledger import Hledger
import Hledger.Utils.UTF8IOCompat (putStrLn) import Hledger.Utils.UTF8IOCompat (putStrLn)
import Hledger.Cli hiding (progname,prognameandversion) import Hledger.Cli hiding (progname,prognameandversion)
import Hledger.Web.Options import Hledger.Web.WebOptions
main :: IO () main :: IO ()

View File

@ -1,5 +1,5 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
module Hledger.Web.Options module Hledger.Web.WebOptions
where where
import Prelude import Prelude
#if !MIN_VERSION_base(4,8,0) #if !MIN_VERSION_base(4,8,0)

View File

@ -176,7 +176,7 @@ library
Handler.Utils Handler.Utils
Hledger.Web Hledger.Web
Hledger.Web.Main Hledger.Web.Main
Hledger.Web.Options Hledger.Web.WebOptions
Import Import
Settings Settings
Settings.Development Settings.Development

View File

@ -208,7 +208,7 @@ library:
- Handler.Utils - Handler.Utils
- Hledger.Web - Hledger.Web
- Hledger.Web.Main - Hledger.Web.Main
- Hledger.Web.Options - Hledger.Web.WebOptions
- Import - Import
- Settings - Settings
- Settings.Development - Settings.Development

View File

@ -18,7 +18,7 @@ module Hledger.Cli (
module Hledger.Cli.Print, module Hledger.Cli.Print,
module Hledger.Cli.Register, module Hledger.Cli.Register,
module Hledger.Cli.Stats, module Hledger.Cli.Stats,
module Hledger.Cli.Options, module Hledger.Cli.CliOptions,
module Hledger.Cli.Utils, module Hledger.Cli.Utils,
module Hledger.Cli.Version, module Hledger.Cli.Version,
tests_Hledger_Cli, tests_Hledger_Cli,
@ -41,7 +41,7 @@ import Hledger.Cli.Incomestatement
import Hledger.Cli.Print import Hledger.Cli.Print
import Hledger.Cli.Register import Hledger.Cli.Register
import Hledger.Cli.Stats import Hledger.Cli.Stats
import Hledger.Cli.Options import Hledger.Cli.CliOptions
import Hledger.Cli.Utils import Hledger.Cli.Utils
import Hledger.Cli.Version import Hledger.Cli.Version
@ -56,7 +56,7 @@ tests_Hledger_Cli = TestList
,tests_Hledger_Cli_Cashflow ,tests_Hledger_Cli_Cashflow
-- ,tests_Hledger_Cli_Histogram -- ,tests_Hledger_Cli_Histogram
,tests_Hledger_Cli_Incomestatement ,tests_Hledger_Cli_Incomestatement
,tests_Hledger_Cli_Options ,tests_Hledger_Cli_CliOptions
-- ,tests_Hledger_Cli_Print -- ,tests_Hledger_Cli_Print
,tests_Hledger_Cli_Register ,tests_Hledger_Cli_Register
-- ,tests_Hledger_Cli_Stats -- ,tests_Hledger_Cli_Stats

View File

@ -23,7 +23,7 @@ import Test.HUnit
import Hledger import Hledger
import Prelude hiding (putStrLn) import Prelude hiding (putStrLn)
import Hledger.Utils.UTF8IOCompat (putStrLn) import Hledger.Utils.UTF8IOCompat (putStrLn)
import Hledger.Cli.Options import Hledger.Cli.CliOptions
-- | Command line options for this command. -- | Command line options for this command.

View File

@ -29,7 +29,7 @@ import Text.Parsec
import Text.Printf import Text.Printf
import Hledger import Hledger
import Hledger.Cli.Options import Hledger.Cli.CliOptions
import Hledger.Cli.Register (postingsReportAsText) import Hledger.Cli.Register (postingsReportAsText)

View File

@ -253,7 +253,7 @@ import Text.Tabular as T
import Text.Tabular.AsciiArt import Text.Tabular.AsciiArt
import Hledger import Hledger
import Hledger.Cli.Options import Hledger.Cli.CliOptions
import Hledger.Cli.Utils import Hledger.Cli.Utils

View File

@ -17,7 +17,7 @@ import Test.HUnit
import Text.Shakespeare.Text import Text.Shakespeare.Text
import Hledger import Hledger
import Hledger.Cli.Options import Hledger.Cli.CliOptions
import Hledger.Cli.Balance import Hledger.Cli.Balance

View File

@ -20,7 +20,7 @@ import Test.HUnit
import Text.Shakespeare.Text import Text.Shakespeare.Text
import Hledger import Hledger
import Hledger.Cli.Options import Hledger.Cli.CliOptions
import Hledger.Cli.Balance import Hledger.Cli.Balance

View File

@ -6,7 +6,7 @@ related utilities used by hledger commands.
-} -}
module Hledger.Cli.Options ( module Hledger.Cli.CliOptions (
-- * cmdargs flags & modes -- * cmdargs flags & modes
helpflags, helpflags,
@ -55,7 +55,7 @@ module Hledger.Cli.Options (
hledgerAddons, hledgerAddons,
-- * Tests -- * Tests
tests_Hledger_Cli_Options tests_Hledger_Cli_CliOptions
) )
where where
@ -584,7 +584,7 @@ getDirectoryContentsSafe d =
-- tests -- tests
tests_Hledger_Cli_Options :: Test tests_Hledger_Cli_CliOptions :: Test
tests_Hledger_Cli_Options = TestList tests_Hledger_Cli_CliOptions = TestList
[ [
] ]

View File

@ -14,7 +14,7 @@ import System.Console.CmdArgs.Explicit
import Text.Printf import Text.Printf
import Hledger import Hledger
import Hledger.Cli.Options import Hledger.Cli.CliOptions
import Prelude hiding (putStr) import Prelude hiding (putStr)
import Hledger.Utils.UTF8IOCompat (putStr) import Hledger.Utils.UTF8IOCompat (putStr)

View File

@ -17,7 +17,7 @@ import Test.HUnit
import Text.Shakespeare.Text import Text.Shakespeare.Text
import Hledger import Hledger
import Hledger.Cli.Options import Hledger.Cli.CliOptions
import Hledger.Cli.Balance import Hledger.Cli.Balance

View File

@ -60,7 +60,7 @@ import Hledger.Cli.Incomestatement
import Hledger.Cli.Print import Hledger.Cli.Print
import Hledger.Cli.Register import Hledger.Cli.Register
import Hledger.Cli.Stats import Hledger.Cli.Stats
import Hledger.Cli.Options import Hledger.Cli.CliOptions
import Hledger.Cli.Tests import Hledger.Cli.Tests
import Hledger.Cli.Utils import Hledger.Cli.Utils
import Hledger.Cli.Version import Hledger.Cli.Version
@ -186,7 +186,7 @@ main = do
-- on the raw command-line arguments, cmdarg's interpretation of -- on the raw command-line arguments, cmdarg's interpretation of
-- same, and hledger-* executables in the user's PATH. A somewhat -- same, and hledger-* executables in the user's PATH. A somewhat
-- complex mishmash of cmdargs and custom processing, hence all the -- complex mishmash of cmdargs and custom processing, hence all the
-- debugging support and tests. See also Hledger.Cli.Options and -- debugging support and tests. See also Hledger.Cli.CliOptions and
-- command-line.test. -- command-line.test.
-- some preliminary (imperfect) argument parsing to supplement cmdargs -- some preliminary (imperfect) argument parsing to supplement cmdargs

View File

@ -18,7 +18,7 @@ import Test.HUnit
import Text.CSV import Text.CSV
import Hledger import Hledger
import Hledger.Cli.Options import Hledger.Cli.CliOptions
import Hledger.Cli.Utils import Hledger.Cli.Utils

View File

@ -22,7 +22,7 @@ import Test.HUnit
import Text.Printf import Text.Printf
import Hledger import Hledger
import Hledger.Cli.Options import Hledger.Cli.CliOptions
import Hledger.Cli.Utils import Hledger.Cli.Utils

View File

@ -21,7 +21,7 @@ import Text.Printf
import qualified Data.Map as Map import qualified Data.Map as Map
import Hledger import Hledger
import Hledger.Cli.Options import Hledger.Cli.CliOptions
import Prelude hiding (putStr) import Prelude hiding (putStr)
import Hledger.Cli.Utils (writeOutput) import Hledger.Cli.Utils (writeOutput)

View File

@ -53,7 +53,7 @@ import System.Time (ClockTime(TOD))
import Data.Time.Clock.POSIX (utcTimeToPOSIXSeconds) import Data.Time.Clock.POSIX (utcTimeToPOSIXSeconds)
#endif #endif
import Hledger.Cli.Options import Hledger.Cli.CliOptions
import Hledger.Data import Hledger.Data
import Hledger.Read import Hledger.Read
import Hledger.Utils import Hledger.Utils

View File

@ -100,7 +100,7 @@ library
exposed-modules: exposed-modules:
Hledger.Cli Hledger.Cli
Hledger.Cli.Main Hledger.Cli.Main
Hledger.Cli.Options Hledger.Cli.CliOptions
Hledger.Cli.Tests Hledger.Cli.Tests
Hledger.Cli.Utils Hledger.Cli.Utils
Hledger.Cli.Version Hledger.Cli.Version

View File

@ -118,7 +118,7 @@ library:
exposed-modules: exposed-modules:
- Hledger.Cli - Hledger.Cli
- Hledger.Cli.Main - Hledger.Cli.Main
- Hledger.Cli.Options - Hledger.Cli.CliOptions
- Hledger.Cli.Tests - Hledger.Cli.Tests
- Hledger.Cli.Utils - Hledger.Cli.Utils
- Hledger.Cli.Version - Hledger.Cli.Version