move commands to their own subpackage

This commit is contained in:
Simon Michael 2009-06-02 18:29:01 +00:00
parent 71e7f2b293
commit d35792bf3f
14 changed files with 137 additions and 84 deletions

View File

@ -4,12 +4,12 @@ An add command to help with data entry.
-} -}
module AddCommand module Commands.Add
where where
import Prelude hiding (putStr, putStrLn, getLine, appendFile) import Prelude hiding (putStr, putStrLn, getLine, appendFile)
import Ledger import Ledger
import Options import Options
import RegisterCommand (showRegisterReport) import Commands.Register (showRegisterReport)
import System.IO.UTF8 import System.IO.UTF8
import System.IO (stderr, hFlush) import System.IO (stderr, hFlush)
import System.IO.Error import System.IO.Error

37
Commands/All.hs Normal file
View File

@ -0,0 +1,37 @@
{-# OPTIONS_GHC -cpp #-}
{-|
This module re-exports all the Commands modules. It's just a convenience,
you can import individual modules if you prefer.
-}
module Commands.All (
module Commands.Add,
module Commands.Balance,
module Commands.Convert,
module Commands.Histogram,
module Commands.Print,
module Commands.Register,
module Commands.Stats,
#ifdef VTY
module Commands.UI,
#endif
#ifdef HAPPS
module Commands.Web,
#endif
)
where
import Commands.Add
import Commands.Balance
import Commands.Convert
import Commands.Histogram
import Commands.Print
import Commands.Register
import Commands.Stats
#ifdef VTY
import Commands.UI
#endif
#ifdef HAPPS
import Commands.Web
#endif

View File

@ -94,7 +94,7 @@ balance report:
-} -}
module BalanceCommand module Commands.Balance
where where
import Prelude hiding (putStr) import Prelude hiding (putStr)
import Ledger.Utils import Ledger.Utils

View File

@ -36,7 +36,7 @@ optional rule saving.
-} -}
module ConvertCommand where module Commands.Convert where
import Data.Maybe (isJust) import Data.Maybe (isJust)
import Data.List.Split (splitOn) import Data.List.Split (splitOn)
import Options -- (Opt,Debug) import Options -- (Opt,Debug)

View File

@ -4,7 +4,7 @@ Print a histogram report.
-} -}
module HistogramCommand module Commands.Histogram
where where
import Prelude hiding (putStr) import Prelude hiding (putStr)
import qualified Data.Map as Map import qualified Data.Map as Map
@ -30,7 +30,7 @@ showHistogram opts args l = concatMap (printDayWith countBar) daytxns
fullspan = rawLedgerDateSpan $ rawledger l fullspan = rawLedgerDateSpan $ rawledger l
days = filter (DateSpan Nothing Nothing /=) $ splitSpan interval fullspan days = filter (DateSpan Nothing Nothing /=) $ splitSpan interval fullspan
daytxns = [(s, filter (isTransactionInDateSpan s) ts) | s <- days] daytxns = [(s, filter (isTransactionInDateSpan s) ts) | s <- days]
-- same as RegisterCommand -- same as Register
ts = sortBy (comparing tdate) $ filterempties $ filter matchapats $ filterdepth $ ledgerTransactions l ts = sortBy (comparing tdate) $ filterempties $ filter matchapats $ filterdepth $ ledgerTransactions l
filterempties filterempties
| Empty `elem` opts = id | Empty `elem` opts = id

View File

@ -4,7 +4,7 @@ A ledger-compatible @print@ command.
-} -}
module PrintCommand module Commands.Print
where where
import Prelude hiding (putStr) import Prelude hiding (putStr)
import Ledger import Ledger

View File

@ -4,7 +4,7 @@ A ledger-compatible @register@ command.
-} -}
module RegisterCommand module Commands.Register
where where
import Prelude hiding (putStr) import Prelude hiding (putStr)
import qualified Data.Map as Map import qualified Data.Map as Map

View File

@ -4,7 +4,7 @@ Print some statistics for the ledger.
-} -}
module StatsCommand module Commands.Stats
where where
import Prelude hiding (putStr) import Prelude hiding (putStr)
import qualified Data.Map as Map import qualified Data.Map as Map

View File

@ -4,7 +4,7 @@ A simple text UI for hledger, based on the vty library.
-} -}
module UICommand module Commands.UI
where where
import qualified Data.Map as Map import qualified Data.Map as Map
import Data.Map ((!)) import Data.Map ((!))
@ -12,9 +12,9 @@ import Graphics.Vty
import qualified Data.ByteString.Char8 as B import qualified Data.ByteString.Char8 as B
import Ledger import Ledger
import Options import Options
import BalanceCommand import Commands.Balance
import RegisterCommand import Commands.Register
import PrintCommand import Commands.Print
helpmsg = "(b)alance, (r)egister, (p)rint, (right) to drill down, (left) to back up, (q)uit" helpmsg = "(b)alance, (r)egister, (p)rint, (right) to drill down, (left) to back up, (q)uit"

View File

@ -2,7 +2,7 @@
A happs-based web UI for hledger. A happs-based web UI for hledger.
-} -}
module WebCommand module Commands.Web
where where
import Control.Monad.Trans (liftIO) import Control.Monad.Trans (liftIO)
import Data.ByteString.Lazy.UTF8 (toString) import Data.ByteString.Lazy.UTF8 (toString)
@ -21,13 +21,14 @@ import System.Cmd (system)
import System.Info (os) import System.Info (os)
import System.Exit import System.Exit
import Network.HTTP (urlEncode, urlDecode, urlEncodeVars) import Network.HTTP (urlEncode, urlDecode, urlEncodeVars)
import Text.XHtml hiding (dir)
import Ledger import Ledger
import Options import Options
import BalanceCommand import Commands.Balance
import RegisterCommand import Commands.Register
import PrintCommand import Commands.Print
import HistogramCommand import Commands.Histogram
import Utils (filterAndCacheLedgerWithOpts) import Utils (filterAndCacheLedgerWithOpts)
@ -67,7 +68,7 @@ webHandlers opts args l t = msum
where where
opts' = opts ++ [Period p] opts' = opts ++ [Period p]
args' = args ++ (map urlDecode $ words a) args' = args ++ (map urlDecode $ words a)
-- re-filter the full ledger -- re-filter the full ledger with the new opts
l' = filterAndCacheLedgerWithOpts opts' args' t (rawledgertext l) (rawledger l) l' = filterAndCacheLedgerWithOpts opts' args' t (rawledgertext l) (rawledger l)
rqdata = do rqdata = do
@ -78,7 +79,7 @@ rqdata = do
layout :: (String, String) -> String -> ServerPartT IO Response layout :: (String, String) -> String -> ServerPartT IO Response
layout (a,p) s = do layout (a,p) s = do
r <- askRq r <- askRq
return $ setHeader "Content-Type" "text/html" $ toResponse $ maintemplate (a,p) r s return $ setHeader "Content-Type" "text/html" $ toResponse $ maintemplate' (a,p) r s
maintemplate :: (String, String) -> Request -> String -> String maintemplate :: (String, String) -> Request -> String -> String
maintemplate (a,p) r = printf (unlines maintemplate (a,p) r = printf (unlines
@ -110,6 +111,44 @@ maintemplate (a,p) r = printf (unlines
resetlink | null a && null p = "" resetlink | null a && null p = ""
| otherwise = printf "&nbsp; <a href=%s>reset</a>" u | otherwise = printf "&nbsp; <a href=%s>reset</a>" u
maintemplate' :: (String, String) -> Request -> String -> String
maintemplate' (a,period) r s = renderHtml $
body << concatHtml [
(thediv Text.XHtml.! [thestyle "float:right; text-align:right;"]) << noHtml,
pre << s
]
-- printf (unlines
-- ["<div style=\"float:right;text-align:right;\">"
-- ,"<form action=%s>"
-- ,"&nbsp; filter by:&nbsp;<input name=a size=30 value=\"%s\">"
-- ,"&nbsp; reporting period:&nbsp;<input name=p size=30 value=\"%s\">"
-- ,resetlink
-- ,"</form>"
-- ,"</div>"
-- ,"<div style=\"width:100%%; font-weight:bold;\">"
-- ," <a href=balance%s>balance</a>"
-- ,"|"
-- ," <a href=register%s>register</a>"
-- ,"|"
-- ," <a href=print%s>print</a>"
-- ,"|"
-- ," <a href=histogram%s>histogram</a>"
-- ,"</div>"
-- ,"<pre>%s</pre>"
-- ]) u a p q q q q
-- where
-- u = dropWhile (=='/') $ rqUri r
-- -- another way to get them
-- -- a = fromMaybe "" $ queryValue "a" r
-- -- p = fromMaybe "" $ queryValue "p" r
-- q' = intercalate "&" $
-- (if null a then [] else [(("a="++).urlEncode) a]) ++
-- (if null p then [] else [(("p="++).urlEncode) p])
-- q = if null q' then "" else '?':q'
-- resetlink | null a && null p = ""
-- | otherwise = printf "&nbsp; <a href=%s>reset</a>" u
queryValues :: String -> Request -> [String] queryValues :: String -> Request -> [String]
queryValues q r = map (B.unpack . inputValue . snd) $ filter ((==q).fst) $ rqInputs r queryValues q r = map (B.unpack . inputValue . snd) $ filter ((==q).fst) $ rqInputs r

View File

@ -1,5 +1,7 @@
# hledger project makefile # hledger project makefile
SOURCEFILES:=*hs Commands/*hs Ledger/*hs
DOCFILES=HOME README NEWS CONTRIBUTORS SCREENSHOTS
TIME:=`date +"%Y%m%d%H%M"` TIME:=`date +"%Y%m%d%H%M"`
# patches since last release tag (as a haskell string literal) # patches since last release tag (as a haskell string literal)
@ -14,6 +16,9 @@ BUILDFLAGS=-DPATCHES=$(PATCHES) $(OPTFLAGS)
#CICMD=web --debug -BE #CICMD=web --debug -BE
CICMD=test CICMD=test
# executables to benchtest, prepend ./ if not in $PATH.
BENCHEXES=hledger-0.4 hledger-0.5 ledger
# command to run during profiling # command to run during profiling
PROFCMD=-f 1000x1000x10.ledger balance PROFCMD=-f 1000x1000x10.ledger balance
@ -88,9 +93,7 @@ haddocktest:
@make --quiet haddock @make --quiet haddock
# run performance tests and save results in profs/. # run performance tests and save results in profs/.
# Requires some tests defined in bench.tests and some executables defined below. # Requires some tests defined in bench.tests and some executables defined above.
# Prepend ./ to these if not in $PATH.
BENCHEXES=hledger-0.4 hledger-0.5 ledger
benchtest: sampleledgers bench.tests bench benchtest: sampleledgers bench.tests bench
tools/bench -fbench.tests $(BENCHEXES) | tee profs/$(TIME).bench tools/bench -fbench.tests $(BENCHEXES) | tee profs/$(TIME).bench
@(cd profs; rm -f latest.bench; ln -s $(TIME).bench latest.bench) @(cd profs; rm -f latest.bench; ln -s $(TIME).bench latest.bench)
@ -127,19 +130,17 @@ sample.ledger:
###################################################################### ######################################################################
# DOCS # DOCS
DOCS=HOME README NEWS CONTRIBUTORS SCREENSHOTS
# rebuild all docs # rebuild all docs
docs: buildwebsite pdf api-docs docs: buildwebsite pdf api-docs
buildwebsite: website buildwebsite: website
-cp doc/*.css website -cp doc/*.css website
-cp doc/*.png website -cp doc/*.png website
for d in $(DOCS); do pandoc -s -H doc/header.html -A doc/footer.html -r rst $$d >website/$$d.html; done for d in $(DOCFILES); do pandoc -s -H doc/header.html -A doc/footer.html -r rst $$d >website/$$d.html; done
(cd website; rm -f index.html; ln -s HOME.html index.html) (cd website; rm -f index.html; ln -s HOME.html index.html)
pdf: website pdf: website
for d in $(DOCS); do rst2pdf $$d -o website/$$d.pdf; done for d in $(DOCFILES); do rst2pdf $$d -o website/$$d.pdf; done
website: website:
mkdir -p website mkdir -p website
@ -173,7 +174,7 @@ haddock: api-doc-dir hscolour $(MAIN)
HSCOLOUR=HsColour -css HSCOLOUR=HsColour -css
hscolour: api-doc-dir hscolour: api-doc-dir
echo "Generating colourised source" ; \ echo "Generating colourised source" ; \
for f in *hs Ledger/*hs; do \ for f in $(SOURCEFILES); do \
$(HSCOLOUR) -anchor $$f -oapi-doc/`echo "src/"$$f | sed -e's%/%-%g' | sed -e's%\.hs$$%.html%'` ; \ $(HSCOLOUR) -anchor $$f -oapi-doc/`echo "src/"$$f | sed -e's%/%-%g' | sed -e's%\.hs$$%.html%'` ; \
done ; \ done ; \
cp api-doc/src-hledger.html api-doc/src-Main.html ; \ cp api-doc/src-hledger.html api-doc/src-Main.html ; \
@ -355,7 +356,7 @@ showreleasechanges:
tag: emacstags tag: emacstags
emacstags: emacstags:
@rm -f TAGS; hasktags -e *hs Ledger/*hs hledger.cabal @rm -f TAGS; hasktags -e $(SOURCEFILES) hledger.cabal
clean: clean:
rm -f `find . -name "*.o" -o -name "*.hi" -o -name "*~" -o -name "darcs-amend-record*"` rm -f `find . -name "*.o" -o -name "*.hi" -o -name "*~" -o -name "darcs-amend-record*"`

View File

@ -154,12 +154,11 @@ import System.Locale (defaultTimeLocale)
import Text.ParserCombinators.Parsec import Text.ParserCombinators.Parsec
import Test.HUnit import Test.HUnit
import Test.HUnit.Tools (assertRaises, runVerboseTests) import Test.HUnit.Tools (assertRaises, runVerboseTests)
import Commands.All
import Ledger import Ledger
import Utils
import Options import Options
import BalanceCommand import Utils
import PrintCommand
import RegisterCommand
runtests opts args = runner flattests runtests opts args = runner flattests

View File

@ -56,17 +56,14 @@ Executable hledger
regex-pcre, csv, split, utf8-string, http regex-pcre, csv, split, utf8-string, http
Other-Modules: Other-Modules:
AddCommand Commands.Add
BalanceCommand Commands.All
ConvertCommand Commands.Balance
HistogramCommand Commands.Convert
Options Commands.Histogram
PrintCommand Commands.Print
RegisterCommand Commands.Register
Setup Commands.Stats
Tests
Utils
Version
Ledger Ledger
Ledger.Account Ledger.Account
Ledger.AccountName Ledger.AccountName
@ -83,6 +80,11 @@ Executable hledger
Ledger.Transaction Ledger.Transaction
Ledger.Types Ledger.Types
Ledger.Utils Ledger.Utils
Options
Setup
Tests
Utils
Version
-- need to set patchlevel here (darcs changes --from-tag=. --count) -- need to set patchlevel here (darcs changes --from-tag=. --count)
cpp-options: -DPATCHES=0 cpp-options: -DPATCHES=0
@ -90,7 +92,7 @@ Executable hledger
if flag(vty) if flag(vty)
cpp-options: -DVTY cpp-options: -DVTY
Build-Depends:vty >= 3.1.8.2 && < 3.2 Build-Depends:vty >= 3.1.8.2 && < 3.2
Other-Modules:UICommand Other-Modules:Commands.UI
if flag(happs) if flag(happs)
cpp-options: -DHAPPS cpp-options: -DHAPPS
@ -99,5 +101,5 @@ Executable hledger
,happstack-server >= 0.2 && < 0.3 ,happstack-server >= 0.2 && < 0.3
,happstack-state >= 0.2 && < 0.3 ,happstack-state >= 0.2 && < 0.3
,utf8-string >= 0.3 && < 0.4 ,utf8-string >= 0.3 && < 0.4
Other-Modules:WebCommand Other-Modules:Commands.Web

View File

@ -35,50 +35,25 @@ or ghci:
See "Ledger.Ledger" for more examples. See "Ledger.Ledger" for more examples.
-} -}
module Main ( module Main (-- export for easy ghci access:
-- for easy ghci access
module Main, module Main,
module Utils, module Utils,
module Options, module Options,
module BalanceCommand, module Commands.All,
module ConvertCommand,
module PrintCommand,
module RegisterCommand,
module HistogramCommand,
module AddCommand,
module StatsCommand,
#ifdef VTY
module UICommand,
#endif
#ifdef HAPPS
module WebCommand,
#endif
) )
where where
import Prelude hiding (putStr)
import Control.Monad.Error import Control.Monad.Error
import qualified Data.Map as Map (lookup) import Prelude hiding (putStr)
import System.IO.UTF8
import System.IO (stderr) import System.IO (stderr)
import System.IO.UTF8
import qualified Data.Map as Map (lookup)
import Version (versionmsg) import Commands.All
import Ledger import Ledger
import Utils (withLedgerDo)
import Options import Options
import Tests import Tests
import BalanceCommand import Utils (withLedgerDo)
import ConvertCommand import Version (versionmsg)
import PrintCommand
import RegisterCommand
import HistogramCommand
import AddCommand
import StatsCommand
#ifdef VTY
import UICommand
#endif
#ifdef HAPPS
import WebCommand
#endif
main :: IO () main :: IO ()