Search code examples
haskelltestinghspec

How to test with hspec whether the readerError function was executed


I'm new to Haskell.

I have written the following piece of code which will parse the arguments sent to a script;

module Billing.Options
  (
      GlobalOpts(..)
    , globalOptsParser
    , parseDb
  ) where

import Options.Applicative
import Options.Applicative.Simple
import Options.Applicative.Types
import System.FilePath.Posix
import Text.Regex.PCRE

-- ------------------------------------------------------------

data GlobalOpts = GlobalOpts
  {
    optDb          :: String,
    optSql         :: String
  } deriving Show

-- ------------------------------------------------------------

globalOptsParser :: Parser GlobalOpts
globalOptsParser = GlobalOpts
  <$> option (parseDb =<< readerAsk)
    (   long "db"
    <>  short 'd'
    <>  metavar "<DB name>"
    <>  help "dmt | report"
    )
  <*> option parseSql
    (   long "sql"
    <>  metavar "<SQL SELECT statement>"
    <>  help "sql select statement to use in order to generate JSON config file"
    )
-- ------------------------------------------------------------

matches :: String -> String -> Bool
matches = (=~)

-- ------------------------------------------------------------

parseDb :: String -> ReadM String
parseDb val = do
    if not (elem val ["dmt", "report"])
        then readerError $ "Unknown DB, '" ++ val ++ "'"
        else return val

-- ------------------------------------------------------------

parseSql :: ReadM String
parseSql = do
    val <- readerAsk
    if not (val `matches` "(?i)select .+ from .+")
        then readerError $ "Please provide a valid SQL SELECT statement"
        else return val

-- [EOF]

I want to test the "parseDb" function above with hspec. I want to ensure that a "readerError" will be thrown when an unknown database is specified. Thus I want to test that the function call parseDb "unknown" generates a "readerError" call which according to me should throw an exception.

I have tried the hspec shouldThrow function but it doesn't work. Seems no exception was thrown. The return type for readerError is "ReadM a". After spending a few days reading up on monads and reader monads I'm still stuck (and confused) and have no idea how to test this and whether it is even possible to test it. Couldn't find any relevant examples when I googled.


Solution

  • Here are some relevant type sigs:

    parseDb :: String -> ReadM String
    
    -- from Options.Applicative.Internal
    
    runReadM :: MonadP m => ReadM a -> String -> m a
    runP :: P a -> ParserPrefs -> (Either ParseError a, Context)
    

    Docs for runReadM and runP: (link)

    ParserPrefs is just a simple data structure.

    And this typechecks:

     import Options.Applicative.Types
     import Options.Applicative.Internal
    
     parseDb :: String -> ReadM String
     parseDb val = do
         if not (elem val ["dmt", "report"])
             then readerError $ "Unknown DB, '" ++ val ++ "'"
             else return val
    
     foo :: (Either ParseError String, Context)     -- might be [Context] now
     foo =   runP (runReadM (parseDb "foo") "asd") opts
       where opts = ParserPrefs "suffix" False False False 80
    

    Evaluating fst foo returns:

    *Main> fst foo
    Left (ErrorMsg "Unknown DB, 'foo'")
    

    Update

    Here is how to test a Parser like globalOptsParser:

    import Options.Applicative.Common (runParser)
    import Options.Applicative.Internal (runP)
    
    bar = let mp = runParser AllowOpts globalOptsParser ["asd"]
              opts = ParserPrefs "suffix" False False False 80
          in fst $ runP mp opts
    

    Here ["asd"] are the command line arguments to test against.

    Check that the ParserPrefs are what you want - they can affect option processing.