Skip to content
This repository has been archived by the owner on May 2, 2020. It is now read-only.

Commit

Permalink
Remove lazy bytestrings in examples and tests.
Browse files Browse the repository at this point in the history
  • Loading branch information
Ian Grant Jeffries committed Jan 10, 2017
1 parent 17a5ffb commit 5469a5f
Show file tree
Hide file tree
Showing 3 changed files with 19 additions and 21 deletions.
6 changes: 2 additions & 4 deletions examples/AlternateSchema.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,9 +11,8 @@ module AlternateSchema where
import Protolude

import Data.Aeson (FromJSON(..), Value(..),
decode)
decodeStrict)
import qualified Data.Aeson as AE
import qualified Data.ByteString.Lazy as LBS
import qualified Data.HashMap.Strict as HM
import Data.Maybe (fromMaybe)
import Data.Profunctor (Profunctor (..))
Expand Down Expand Up @@ -66,8 +65,7 @@ validate rs = continueValidating rs (D4.VisitedSchemas [(Nothing, Nothing)])
metaSchema :: Schema
metaSchema =
fromMaybe (panic "Schema decode failed (this should never happen)")
. decode
. LBS.fromStrict
. decodeStrict
$ metaSchemaBytes

checkSchema :: Schema -> [ValidatorFailure]
Expand Down
14 changes: 7 additions & 7 deletions examples/Simple.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,20 +3,20 @@ module Simple where

import Protolude

import Data.Aeson (Value(..), decode, toJSON)
import qualified Data.ByteString.Lazy as LBS
import qualified Data.List.NonEmpty as NE
import Data.Maybe (fromMaybe)
import Data.Aeson (Value(..), decodeStrict, toJSON)
import qualified Data.ByteString as BS
import qualified Data.List.NonEmpty as NE
import Data.Maybe (fromMaybe)

import qualified JSONSchema.Draft4 as D4
import qualified JSONSchema.Draft4 as D4

badData :: Value
badData = toJSON [True, True]

example :: IO ()
example = do
bts <- LBS.readFile "./examples/json/unique.json"
let schema = fromMaybe (panic "Invalid schema JSON.") (decode bts)
bts <- BS.readFile "./examples/json/unique.json"
let schema = fromMaybe (panic "Invalid schema JSON.") (decodeStrict bts)
schemaWithURI = D4.SchemaWithURI
schema
Nothing -- This would be the URI of the schema
Expand Down
20 changes: 10 additions & 10 deletions test/Shared.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,15 +3,15 @@ module Shared where

import Protolude

import Control.Monad (fail)
import Control.Monad (fail)
import Data.Aeson
import Data.Aeson.TH
import qualified Data.ByteString.Lazy as LBS
import Data.Char (toLower)
import Data.List (stripPrefix, unlines)
import qualified Data.Text as T
import qualified System.Directory as SD
import System.FilePath ((</>))
import Data.Aeson.TH (fieldLabelModifier)
import qualified Data.ByteString as BS
import Data.Char (toLower)
import Data.List (stripPrefix, unlines)
import qualified Data.Text as T
import qualified System.Directory as SD
import System.FilePath ((</>))
import Test.Hspec

-- Recursively return the contents of a directory
Expand Down Expand Up @@ -86,8 +86,8 @@ readSchemaTests dir filterFunc = do
fileToCases :: FilePath -> IO [SchemaTest]
fileToCases name = do
let fullPath = dir </> name
jsonBS <- LBS.readFile fullPath
case eitherDecode jsonBS of
jsonBS <- BS.readFile fullPath
case eitherDecodeStrict jsonBS of
Left e -> fail $ "couldn't parse file '" <> fullPath <> "': " <> e
Right schemaTests -> pure $ prependFileName name <$> schemaTests

Expand Down

0 comments on commit 5469a5f

Please sign in to comment.