1
1
mirror of https://github.com/sol/hpack.git synced 2024-10-04 03:38:00 +03:00

better error message propagation when parsing List

This commit is contained in:
Sönke Hahn 2015-07-16 12:43:40 +08:00
parent 768119c70a
commit de5b6a7f38
2 changed files with 27 additions and 6 deletions

View File

@ -42,7 +42,9 @@ newtype List a = List {fromList :: [a]}
deriving (Eq, Show, Data, Typeable)
instance FromJSON a => FromJSON (List a) where
parseJSON v = List <$> (parseJSON v <|> (return <$> parseJSON v))
parseJSON v = List <$> case v of
Array _ -> parseJSON v
_ -> return <$> parseJSON v
type GhcOption = String

View File

@ -1,10 +1,14 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Hpack.UtilSpec (main, spec) where
import Helper
import Data.Aeson
import Data.Aeson.QQ
import Data.Aeson.Types
import Helper
import System.Directory
import Hpack.Config
import Hpack.Util
main :: IO ()
@ -53,11 +57,26 @@ spec = do
]
describe "List" $ do
it "can be a single value" $ do
fromJSON (toJSON $ Number 23) `shouldBe` Success (List [23 :: Int])
let invalid = [aesonQQ|{
name: "hpack",
gi: "sol/hpack",
ref: "master"
}|]
parseError :: Either String (List Dependency)
parseError = Left "neither key \"git\" nor key \"github\" present"
context "when parsing single values" $ do
it "returns the value in a singleton list" $ do
fromJSON (toJSON $ Number 23) `shouldBe` Success (List [23 :: Int])
it "can be a list of values" $ do
fromJSON (toJSON [Number 23, Number 42]) `shouldBe` Success (List [23, 42 :: Int])
it "returns error messages from element parsing" $ do
parseEither parseJSON invalid `shouldBe` parseError
context "when parsing a list of values" $ do
it "returns the list" $ do
fromJSON (toJSON [Number 23, Number 42]) `shouldBe` Success (List [23, 42 :: Int])
it "propagates parse error messages of invalid elements" $ do
parseEither parseJSON (toJSON [String "foo", invalid]) `shouldBe` parseError
describe "tryReadFile" $ do
it "reads file" $ do