The add form has become a modal dialog, and been moved into the default template. This simplifies some things, for now. Eg it's easily accessible from any page.
		
			
				
	
	
		
			162 lines
		
	
	
		
			6.6 KiB
		
	
	
	
		
			Haskell
		
	
	
	
	
	
			
		
		
	
	
			162 lines
		
	
	
		
			6.6 KiB
		
	
	
	
		
			Haskell
		
	
	
	
	
	
| -- | POST helpers.
 | |
| 
 | |
| module Handler.Post where
 | |
| 
 | |
| import Import
 | |
| 
 | |
| import Control.Applicative
 | |
| import Data.Either (lefts,rights)
 | |
| import Data.List (intercalate)
 | |
| import qualified Data.List as L (head) -- qualified keeps dev & prod builds warning-free
 | |
| import Data.Text (unpack)
 | |
| import qualified Data.Text as T (null)
 | |
| import Text.Parsec (eof)
 | |
| import Text.Printf (printf)
 | |
| 
 | |
| import Hledger.Utils
 | |
| import Hledger.Data
 | |
| import Hledger.Read
 | |
| import Hledger.Cli
 | |
| 
 | |
| 
 | |
| -- | Handle a post from any of the edit forms.
 | |
| handlePost :: Handler Html
 | |
| handlePost = do
 | |
|   action <- lookupPostParam  "action"
 | |
|   case action of Just "add"    -> handleAdd
 | |
|                  Just "edit"   -> handleEdit
 | |
|                  Just "import" -> handleImport
 | |
|                  _             -> invalidArgs ["invalid action"]
 | |
| 
 | |
| -- | Handle a post from the transaction add form.
 | |
| handleAdd :: Handler Html
 | |
| handleAdd = do
 | |
|   VD{..} <- getViewData
 | |
|   -- get form input values. M means a Maybe value.
 | |
|   dateM <- lookupPostParam  "date"
 | |
|   descM <- lookupPostParam  "description"
 | |
|   acct1M <- lookupPostParam  "account1"
 | |
|   amt1M <- lookupPostParam  "amount1"
 | |
|   acct2M <- lookupPostParam  "account2"
 | |
|   amt2M <- lookupPostParam  "amount2"
 | |
|   journalM <- lookupPostParam  "journal"
 | |
|   -- supply defaults and parse date and amounts, or get errors.
 | |
|   let dateE = maybe (Left "date required") (either (\e -> Left $ showDateParseError e) Right . fixSmartDateStrEither today . unpack) dateM
 | |
|       descE = Right $ maybe "" unpack descM
 | |
|       -- XXX simplify...
 | |
|       maybeNothing = maybe Nothing (\t -> if T.null t then Nothing else Just t)
 | |
|       acct1E = maybe (Left "To account required") (Right . strip . unpack) (maybeNothing acct1M)
 | |
|                >>= \a -> either (Left . ("could not parse To account: "++) . show) Right (parsewith (accountnamep <* eof) a)
 | |
|       acct2E = maybe (Left "From account required") (Right . strip . unpack) (maybeNothing acct2M)
 | |
|                >>= \a -> either (Left . ("could not parse From account: "++) . show) Right (parsewith (accountnamep <* eof) a)
 | |
|       amt1E = maybe (Left "Amount 1 required") (Right . strip . unpack) (maybeNothing amt1M)
 | |
|                >>= \a -> either (Left . ("could not parse To account: "++) . show) Right (parseWithCtx nullctx (amountp <* eof) a)
 | |
|       amt2E = maybe (Right missingamt) (either (Left . ("could not parse amount 2: "++) . show) Right . parseWithCtx nullctx amountp . strip . unpack) amt2M
 | |
|       journalE = maybe (Right $ journalFilePath j)
 | |
|                        (\f -> let f' = unpack f in
 | |
|                               if f' `elem` journalFilePaths j
 | |
|                               then Right f'
 | |
|                               else Left $ "unrecognised journal file path: " ++ f'
 | |
|                               )
 | |
|                        journalM
 | |
|       strEs = [dateE, descE, acct1E, acct2E, journalE]
 | |
|       amtEs = [amt1E, amt2E]
 | |
|       errs = lefts strEs ++ lefts amtEs
 | |
|       [date,desc,acct1,acct2,journalpath] = rights strEs
 | |
|       [amt1,amt2] = rights amtEs
 | |
|       -- if no errors so far, generate a transaction and balance it or get the error.
 | |
|       tE | not $ null errs = Left errs
 | |
|          | otherwise = either (\e -> Left ["unbalanced postings: " ++ (L.head $ lines e)]) Right
 | |
|                         (balanceTransaction Nothing $ nulltransaction { -- imprecise balancing
 | |
|                            tdate=parsedate date
 | |
|                           ,tdescription=desc
 | |
|                           ,tpostings=[
 | |
|                             nullposting{paccount=acct1, pamount=mixed amt1}
 | |
|                            ,nullposting{paccount=acct2, pamount=mixed amt2}
 | |
|                            ]
 | |
|                           })
 | |
|   -- display errors or add transaction
 | |
|   -- XXX currently it's still possible to write an invalid entry, eg by adding space space ; after the first account name
 | |
|   case tE of
 | |
|    Left errs' -> do
 | |
|     -- save current form values in session
 | |
|     -- setMessage $ toHtml $ intercalate "; " errs
 | |
|     setMessage [shamlet|
 | |
|                  Errors:<br>
 | |
|                  $forall e<-errs'
 | |
|                   \#{e}<br>
 | |
|                |]
 | |
|    Right t -> do
 | |
|     let t' = txnTieKnot t -- XXX move into balanceTransaction
 | |
|     liftIO $ do ensureJournalFileExists journalpath
 | |
|                 appendToJournalFileOrStdout journalpath $ showTransaction t'
 | |
|     -- setMessage $ toHtml $ (printf "Added transaction:\n%s" (show t') :: String)
 | |
|     setMessage [shamlet|<span>Added transaction:<small><pre>#{chomp $ show t'}</pre></small>|]
 | |
| 
 | |
|   redirect (JournalR, [("add","1")])
 | |
| 
 | |
| -- | Handle a post from the journal edit form.
 | |
| handleEdit :: Handler Html
 | |
| handleEdit = do
 | |
|   VD{..} <- getViewData
 | |
|   -- get form input values, or validation errors.
 | |
|   -- getRequest >>= liftIO (reqRequestBody req) >>= mtrace
 | |
|   textM <- lookupPostParam "text"
 | |
|   journalM <- lookupPostParam "journal"
 | |
|   let textE = maybe (Left "No value provided") (Right . unpack) textM
 | |
|       journalE = maybe (Right $ journalFilePath j)
 | |
|                        (\f -> let f' = unpack f in
 | |
|                               if f' `elem` journalFilePaths j
 | |
|                               then Right f'
 | |
|                               else Left "unrecognised journal file path")
 | |
|                        journalM
 | |
|       strEs = [textE, journalE]
 | |
|       errs = lefts strEs
 | |
|       [text,journalpath] = rights strEs
 | |
|   -- display errors or perform edit
 | |
|   if not $ null errs
 | |
|    then do
 | |
|     setMessage $ toHtml (intercalate "; " errs :: String)
 | |
|     redirect JournalR
 | |
| 
 | |
|    else do
 | |
|     -- try to avoid unnecessary backups or saving invalid data
 | |
|     filechanged' <- liftIO $ journalSpecifiedFileIsNewer j journalpath
 | |
|     told <- liftIO $ readFileStrictly journalpath
 | |
|     let tnew = filter (/= '\r') text
 | |
|         changed = tnew /= told || filechanged'
 | |
|     if not changed
 | |
|      then do
 | |
|        setMessage "No change"
 | |
|        redirect JournalR
 | |
|      else do
 | |
|       jE <- liftIO $ readJournal Nothing Nothing True (Just journalpath) tnew
 | |
|       either
 | |
|        (\e -> do
 | |
|           setMessage $ toHtml e
 | |
|           redirect JournalR)
 | |
|        (const $ do
 | |
|           liftIO $ writeFileWithBackup journalpath tnew
 | |
|           setMessage $ toHtml (printf "Saved journal %s\n" (show journalpath) :: String)
 | |
|           redirect JournalR)
 | |
|        jE
 | |
| 
 | |
| -- | Handle a post from the journal import form.
 | |
| handleImport :: Handler Html
 | |
| handleImport = do
 | |
|   setMessage "can't handle file upload yet"
 | |
|   redirect JournalR
 | |
|   -- -- get form input values, or basic validation errors. E means an Either value.
 | |
|   -- fileM <- runFormPost $ maybeFileInput "file"
 | |
|   -- let fileE = maybe (Left "No file provided") Right fileM
 | |
|   -- -- display errors or import transactions
 | |
|   -- case fileE of
 | |
|   --  Left errs -> do
 | |
|   --   setMessage errs
 | |
|   --   redirect JournalR
 | |
| 
 | |
|   --  Right s -> do
 | |
|   --    setMessage s
 | |
|   --    redirect JournalR
 | |
| 
 |