mirror of
https://github.com/rowtype-yoga/purescript-yoga-json.git
synced 2024-12-01 20:03:15 +03:00
Postel's law for NonEmpty* (#18)
This commit is contained in:
parent
bdb2316df6
commit
ccbde17dff
@ -36,6 +36,7 @@ import Control.Comonad.Cofree as Cofree
|
||||
import Control.Monad.Except (ExceptT(..), except, runExcept, throwError, withExcept)
|
||||
import Data.Array as Array
|
||||
import Data.Array.NonEmpty (NonEmptyArray, fromArray, toArray)
|
||||
import Data.Array.NonEmpty as NonEmptyArray
|
||||
import Data.Bifunctor (lmap)
|
||||
import Data.DateTime (DateTime)
|
||||
import Data.DateTime.Instant (Instant, instant, unInstant)
|
||||
@ -54,10 +55,10 @@ import Data.Maybe (Maybe(..), fromMaybe, fromMaybe', maybe)
|
||||
import Data.Newtype (class Newtype, unwrap, wrap)
|
||||
import Data.Nullable (Nullable, toMaybe, toNullable)
|
||||
import Data.Number as Number
|
||||
import Data.String.NonEmpty.Internal (NonEmptyString)
|
||||
import Data.String.NonEmpty.Internal as NonEmptyString
|
||||
import Data.String.NonEmpty (NonEmptyString)
|
||||
import Data.String.NonEmpty as NonEmptyString
|
||||
import Data.Symbol (class IsSymbol, reflectSymbol)
|
||||
import Data.Time.Duration (Days(..), Hours(..), Milliseconds(..), Minutes(..), Seconds(..))
|
||||
import Data.Time.Duration (Days, Hours, Milliseconds, Minutes, Seconds)
|
||||
import Data.Traversable (traverse)
|
||||
import Data.Tuple (Tuple(..))
|
||||
import Data.Variant (Variant, inj, on)
|
||||
@ -228,7 +229,13 @@ instance ReadForeign Boolean where
|
||||
instance ReadForeign a ⇒ ReadForeign (Array a) where
|
||||
readImpl = sequenceCombining <<< mapWithIndex readAtIdx <=< readArray
|
||||
|
||||
instance ReadForeign a ⇒ ReadForeign (Maybe a) where
|
||||
instance ReadForeign (Maybe (NonEmptyString)) where
|
||||
readImpl = readImpl >=> pure <<< NonEmptyString.fromString
|
||||
|
||||
else instance ReadForeign a ⇒ ReadForeign (Maybe (NonEmptyArray a)) where
|
||||
readImpl = readImpl >=> pure <<< NonEmptyArray.fromArray
|
||||
|
||||
else instance ReadForeign a ⇒ ReadForeign (Maybe a) where
|
||||
readImpl = readNullOrUndefined readImpl
|
||||
where
|
||||
readNullOrUndefined _ value | isNull value || isUndefined value = pure
|
||||
|
@ -2,6 +2,7 @@ module Test.BasicsSpec where
|
||||
|
||||
import Prelude
|
||||
|
||||
import Data.Array.NonEmpty (NonEmptyArray)
|
||||
import Data.Array.NonEmpty as NEA
|
||||
import Data.Either (Either(..))
|
||||
import Data.Foldable (traverse_)
|
||||
@ -59,6 +60,8 @@ spec = describe "En- and decoding" $ do
|
||||
it "roundtrips LazyList" $ traverse_ roundtrips (LazyList.fromFoldable [ [ "A", "B" ], [] ])
|
||||
it "roundtrips List" $ traverse_ roundtrips (List.fromFoldable [ [ "A", "B" ], [] ])
|
||||
it "roundtrips NonEmptyArray" $ roundtrips (NEA.cons' "A" [ "B" ])
|
||||
it "decodes Maybe NonEmptyArray" $
|
||||
readJSON "[]" `shouldEqual` Right (Nothing ∷ _ (NonEmptyArray Int))
|
||||
it "roundtrips Object" $ roundtrips (Object.fromHomogeneous { a: 12, b: 54 })
|
||||
it "roundtrips String Map" $ roundtrips (Map.fromFoldable [ ("A" /\ 8), ("C" /\ 7) ])
|
||||
it "roundtrips Int Map" $ roundtrips (Map.fromFoldable [ (4 /\ "B"), (8 /\ "D") ])
|
||||
@ -172,6 +175,9 @@ spec = describe "En- and decoding" $ do
|
||||
it "fails to decode empty strings" do
|
||||
let (result ∷ (Either _ NonEmptyString)) = readJSON (show "")
|
||||
result `shouldEqual` Left (pure $ ForeignError "String must not be empty")
|
||||
it "succeeds decoding optional empty strings" do
|
||||
let (result ∷ (Either _ (Maybe NonEmptyString))) = readJSON (show "")
|
||||
result `shouldEqual` Right Nothing
|
||||
|
||||
describe "works on trees" do
|
||||
it "roundtrips" do
|
||||
|
Loading…
Reference in New Issue
Block a user