This increases composability and avoids some ugly case handling. We re-export runExceptT in Hledger.Read. The final return types of the following functions has been changed from IO (Either String a) to ExceptT String IO a. If this causes a problem, you can get the old behaviour by calling runExceptT on the output: readJournal, readJournalFiles, readJournalFile Or, you can use the easy functions readJournal', readJournalFiles', and readJournalFile', which assume default options and return in the IO monad.
		
			
				
	
	
		
			102 lines
		
	
	
		
			3.8 KiB
		
	
	
	
		
			Haskell
		
	
	
	
	
	
			
		
		
	
	
			102 lines
		
	
	
		
			3.8 KiB
		
	
	
	
		
			Haskell
		
	
	
	
	
	
| {-# LANGUAGE OverloadedStrings #-}
 | |
| 
 | |
| module Hledger.Web.Test (
 | |
|   hledgerWebTest
 | |
| ) where
 | |
| 
 | |
| import qualified Data.Text as T
 | |
| import Test.Hspec (hspec)
 | |
| import Yesod.Default.Config
 | |
| import Yesod.Test
 | |
| 
 | |
| import Hledger.Web.Application ( makeFoundationWith )
 | |
| import Hledger.Web.WebOptions ( WebOpts(cliopts_), defwebopts, prognameandversion )
 | |
| import Hledger.Web.Import hiding (get, j)
 | |
| import Hledger.Cli hiding (prognameandversion)
 | |
| 
 | |
| 
 | |
| runHspecTestsWith :: AppConfig DefaultEnv Extra -> WebOpts -> Journal -> YesodSpec App -> IO ()
 | |
| runHspecTestsWith yesodconf hledgerwebopts j specs = do
 | |
|   app <- makeFoundationWith j yesodconf hledgerwebopts
 | |
|   hspec $ yesodSpec app specs
 | |
| 
 | |
| -- Run hledger-web's built-in tests using the hspec test runner.
 | |
| hledgerWebTest :: IO ()
 | |
| hledgerWebTest = do
 | |
|   putStrLn $ "Running tests for " ++ prognameandversion -- ++ " (--test --help for options)"
 | |
| 
 | |
|   -- loadConfig fails without ./config/settings.yml; use a hard-coded one
 | |
|   let conf = AppConfig{
 | |
|                appEnv = Testing
 | |
|               ,appPort = 3000  -- will it clash with a production instance ? doesn't seem to
 | |
|               ,appRoot = "http://localhost:3000"
 | |
|               ,appHost = "*4"
 | |
|               ,appExtra = Extra
 | |
|                           { extraCopyright  = ""
 | |
|                           , extraAnalytics  = Nothing
 | |
|                           , extraStaticRoot = Nothing
 | |
|                           }
 | |
|                   }
 | |
| 
 | |
|   -- http://hspec.github.io/writing-specs.html
 | |
|   -- https://hackage.haskell.org/package/yesod-test-1.6.10/docs/Yesod-Test.html
 | |
|   -- "The best way to see an example project using yesod-test is to create a scaffolded Yesod project:
 | |
|   -- stack new projectname yesodweb/sqlite
 | |
|   -- (See https://github.com/commercialhaskell/stack-templates/wiki#yesod for the full list of Yesod templates)"
 | |
| 
 | |
|   -- Since these tests use makeFoundation, the startup code in Hledger.Web.Main is not tested. XXX
 | |
|   --
 | |
|   -- Be aware that unusual combinations of opts/files here could cause problems,
 | |
|   -- eg if cliopts{file_} is left empty journalReload might reload the user's default journal.
 | |
| 
 | |
|   -- basic tests
 | |
|   runHspecTestsWith conf defwebopts nulljournal $ do
 | |
|     ydescribe "hledger-web" $ do
 | |
| 
 | |
|       yit "serves a reasonable-looking journal page" $ do
 | |
|         get JournalR
 | |
|         statusIs 200
 | |
|         bodyContains "Add a transaction"
 | |
| 
 | |
|       yit "serves a reasonable-looking register page" $ do
 | |
|         get RegisterR
 | |
|         statusIs 200
 | |
|         bodyContains "accounts"
 | |
| 
 | |
|       -- WIP
 | |
|       -- yit "shows the add form" $ do
 | |
|       --   get JournalR
 | |
|       --   -- printBody
 | |
|       --   -- let addbutton = "button:contains('add')"
 | |
|       --   -- bodyContains addbutton
 | |
|       --   -- htmlAnyContain "button:visible" "add"
 | |
|       --   printMatches "div#addmodal:visible"
 | |
|       --   htmlCount "div#addmodal:visible" 0
 | |
| 
 | |
|       --   -- clickOn "a#addformlink"
 | |
|       --   -- printBody
 | |
|       --   -- bodyContains addbutton
 | |
| 
 | |
|       -- yit "can add transactions" $ do
 | |
| 
 | |
|   let
 | |
|     -- Have forecasting on for testing
 | |
|     iopts = definputopts{forecast_=Just nulldatespan}
 | |
|     copts = defcliopts{inputopts_=iopts, file_=[""]}  -- non-empty, see file_ note above
 | |
|     wopts = defwebopts{cliopts_=copts}
 | |
|   pj <- readJournal' (T.pack $ unlines  -- PARTIAL: readJournal' should not fail
 | |
|     ["~ monthly"
 | |
|     ,"    assets    10"
 | |
|     ,"    income"
 | |
|     ])
 | |
|   -- Have to give a non-null filename "fake" so forecast transactions get index 0
 | |
|   j <- fmap (either error id) . runExceptT $ journalFinalise iopts "fake" "" pj  -- PARTIAL: journalFinalise should not fail
 | |
|   runHspecTestsWith conf wopts j $ do
 | |
|     ydescribe "hledger-web --forecast" $ do
 | |
| 
 | |
|       yit "serves a journal page showing forecasted transactions" $ do
 | |
|         get JournalR
 | |
|         statusIs 200
 | |
|         bodyContains "id=\"transaction-0-1\""  -- 0 indicates a fileless (forecasted) txn
 | |
|         bodyContains "id=\"transaction-0-2\""  -- etc.
 |