hledger and hledger-web were reading their version number (and program name) from their cabal files at compile time using cabal-file-th, which allowed the version number be maintained in one place (per package). This meant you had to be in same directory as the cabal file when building, which made life more complicated, eg emacs compilation mode could not jump to errors. Also, it slowed down building slightly, and is a factor in hledger Debian packages being unavailable on a number of platforms (we also use TH for report templates). Now, the build version is set with a CPP VERSION flag, which seems simpler overall. For cabal builds, this needs to be configured manually in a few more places in each cabal file. For makefile builds, it is set it to the name of the most recent darcs tag (which should be more useful than the old behaviour). If not set, it defaults to the blank string, useful eg for haddock. And, all makefile builds now run from the top directory.
		
			
				
	
	
		
			84 lines
		
	
	
		
			2.6 KiB
		
	
	
	
		
			Haskell
		
	
	
	
	
	
			
		
		
	
	
			84 lines
		
	
	
		
			2.6 KiB
		
	
	
	
		
			Haskell
		
	
	
	
	
	
| {-# LANGUAGE TemplateHaskell, CPP #-}
 | |
| {-|
 | |
| 
 | |
| -}
 | |
| 
 | |
| module Hledger.Web.Options
 | |
| where
 | |
| import Prelude
 | |
| import Data.Maybe
 | |
| import System.Console.CmdArgs
 | |
| import System.Console.CmdArgs.Explicit
 | |
| 
 | |
| import Hledger.Cli hiding (progname,version,prognameandversion)
 | |
| import Hledger.Web.Settings
 | |
| 
 | |
| progname, version :: String
 | |
| progname = "hledger-web"
 | |
| #ifdef VERSION
 | |
| version = VERSION
 | |
| #else
 | |
| version = ""
 | |
| #endif
 | |
| prognameandversion :: String
 | |
| prognameandversion = progname ++ " " ++ version :: String
 | |
| 
 | |
| defbaseurlexample :: String
 | |
| defbaseurlexample = (reverse $ drop 4 $ reverse $ defbaseurl defport) ++ "PORT"
 | |
| 
 | |
| webflags :: [Flag [([Char], [Char])]]
 | |
| webflags = [
 | |
|   flagReq ["base-url"]  (\s opts -> Right $ setopt "base-url" s opts) "URL" ("set the base url (default: "++defbaseurlexample++")")
 | |
|  ,flagReq ["port"]  (\s opts -> Right $ setopt "port" s opts) "PORT" ("listen on this tcp port (default: "++show defport++")")
 | |
|  ]
 | |
|  
 | |
| webmode :: Mode [([Char], [Char])]
 | |
| webmode =  (mode "hledger-web" [("command","web")]
 | |
|             "start serving the hledger web interface"
 | |
|             mainargsflag []){
 | |
|               modeGroupFlags = Group {
 | |
|                                 groupUnnamed = webflags
 | |
|                                ,groupHidden = [flagNone ["binary-filename"] (setboolopt "binary-filename") "show the download filename for this executable, and exit"]
 | |
|                                ,groupNamed = [(generalflagstitle, generalflags1)]
 | |
|                                }
 | |
|              ,modeHelpSuffix=[
 | |
|                   -- "Reads your ~/.hledger.journal file, or another specified by $LEDGER_FILE or -f, and starts the full-window curses ui."
 | |
|                  ]
 | |
|            }
 | |
| 
 | |
| -- hledger-web options, used in hledger-web and above
 | |
| data WebOpts = WebOpts {
 | |
|      base_url_ :: String
 | |
|     ,port_     :: Int
 | |
|     ,cliopts_  :: CliOpts
 | |
|  } deriving (Show)
 | |
| 
 | |
| defwebopts :: WebOpts
 | |
| defwebopts = WebOpts
 | |
|     def
 | |
|     def
 | |
|     def
 | |
| 
 | |
| -- instance Default WebOpts where def = defwebopts
 | |
| 
 | |
| toWebOpts :: RawOpts -> IO WebOpts
 | |
| toWebOpts rawopts = do
 | |
|   cliopts <- toCliOpts rawopts
 | |
|   let p = fromMaybe defport $ maybeintopt "port" rawopts
 | |
|   return defwebopts {
 | |
|               port_ = p
 | |
|              ,base_url_ = maybe (defbaseurl p) stripTrailingSlash $ maybestringopt "base-url" rawopts
 | |
|              ,cliopts_   = cliopts
 | |
|              }
 | |
|   where
 | |
|     stripTrailingSlash = reverse . dropWhile (=='/') . reverse -- yesod don't like it
 | |
| 
 | |
| checkWebOpts :: WebOpts -> IO WebOpts
 | |
| checkWebOpts opts = do
 | |
|   checkCliOpts $ cliopts_ opts
 | |
|   return opts
 | |
| 
 | |
| getHledgerWebOpts :: IO WebOpts
 | |
| getHledgerWebOpts = processArgs webmode >>= return . decodeRawOpts >>= toWebOpts >>= checkWebOpts
 | |
| 
 |