diff --git a/.github/workflows/ci.yml b/.github/workflows/ci.yml index 6b0550f..ef2046b 100644 --- a/.github/workflows/ci.yml +++ b/.github/workflows/ci.yml @@ -15,6 +15,8 @@ jobs: - name: Set up a PureScript toolchain uses: purescript-contrib/setup-purescript@main + with: + purs-tidy: "latest" - name: Cache PureScript dependencies uses: actions/cache@v2 @@ -32,3 +34,6 @@ jobs: - name: Run tests run: spago test --no-install + + - name: Check formatting + run: purs-tidy check src test diff --git a/.gitignore b/.gitignore index 7bca306..7e82b68 100644 --- a/.gitignore +++ b/.gitignore @@ -2,6 +2,7 @@ !.gitignore !.github !.editorconfig +!.tidyrc.json output generated-docs diff --git a/.tidyrc.json b/.tidyrc.json new file mode 100644 index 0000000..4f013c1 --- /dev/null +++ b/.tidyrc.json @@ -0,0 +1,10 @@ +{ + "importSort": "source", + "importWrap": "source", + "indent": 2, + "operatorsFile": null, + "ribbon": 1, + "typeArrowPlacement": "first", + "unicode": "never", + "width": null +} diff --git a/CHANGELOG.md b/CHANGELOG.md index 6ad7d26..ba8a2a9 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -11,6 +11,7 @@ New features: Bugfixes: Other improvements: +- Added `purs-tidy` formatter (#38 by @thomashoneyman) ## [v7.0.1](https://github.com/purescript-contrib/purescript-argonaut-generic/releases/tag/v7.0.1) - 2021-05-06 diff --git a/src/Data/Argonaut/Decode/Generic.purs b/src/Data/Argonaut/Decode/Generic.purs index 59ffc89..e397113 100644 --- a/src/Data/Argonaut/Decode/Generic.purs +++ b/src/Data/Argonaut/Decode/Generic.purs @@ -1,16 +1,16 @@ -module Data.Argonaut.Decode.Generic ( - class DecodeRep, - class DecodeRepArgs, - class DecodeLiteral, - decodeRep, - decodeRepWith, - decodeRepArgs, - genericDecodeJson, - genericDecodeJsonWith, - decodeLiteralSum, - decodeLiteralSumWithTransform, - decodeLiteral -) where +module Data.Argonaut.Decode.Generic + ( class DecodeRep + , class DecodeRepArgs + , class DecodeLiteral + , decodeRep + , decodeRepWith + , decodeRepArgs + , genericDecodeJson + , genericDecodeJsonWith + , decodeLiteralSum + , decodeLiteralSumWithTransform + , decodeLiteral + ) where import Prelude @@ -40,90 +40,94 @@ instance decodeRepNoConstructors :: DecodeRep Rep.NoConstructors where instance decodeRepSum :: (DecodeRep a, DecodeRep b) => DecodeRep (Rep.Sum a b) where decodeRepWith e j = Rep.Inl <$> decodeRepWith e j <|> Rep.Inr <$> decodeRepWith e j -withTag :: - Encoding -> - Json -> - String -> - Either JsonDecodeError - { tag :: String - , decodingErr :: JsonDecodeError -> JsonDecodeError - } +withTag + :: Encoding + -> Json + -> String + -> Either JsonDecodeError + { tag :: String + , decodingErr :: JsonDecodeError -> JsonDecodeError + } withTag e j name = do let decodingErr = Named name jObj <- note (decodingErr $ TypeMismatch "Object") (toObject j) jTag <- note (decodingErr $ AtKey e.tagKey MissingValue) (FO.lookup e.tagKey jObj) tag <- note (decodingErr $ AtKey e.tagKey $ TypeMismatch "String") (toString jTag) - when (tag /= name) $ - Left $ decodingErr $ AtKey e.tagKey $ UnexpectedValue $ fromString tag - pure {tag, decodingErr} - -withTagAndValues :: - Encoding -> - Json -> - String -> - Either JsonDecodeError - { tag :: String - , values :: Json - , decodingErr :: JsonDecodeError -> JsonDecodeError - } + when (tag /= name) + $ Left + $ decodingErr + $ AtKey e.tagKey + $ UnexpectedValue + $ fromString tag + pure { tag, decodingErr } + +withTagAndValues + :: Encoding + -> Json + -> String + -> Either JsonDecodeError + { tag :: String + , values :: Json + , decodingErr :: JsonDecodeError -> JsonDecodeError + } withTagAndValues e j name = do - {tag, decodingErr} <- withTag e j name + { tag, decodingErr } <- withTag e j name jObj <- note (decodingErr $ TypeMismatch "Object") (toObject j) values <- note (decodingErr $ AtKey e.valuesKey MissingValue) (FO.lookup e.valuesKey jObj) - pure {tag, values, decodingErr} - -construct :: - forall e t s . - DecodeRepArgs t => - Encoding -> - Array Json -> - (JsonDecodeError -> e) -> - Either e (Rep.Constructor s t) + pure { tag, values, decodingErr } + +construct + :: forall e t s + . DecodeRepArgs t + => Encoding + -> Array Json + -> (JsonDecodeError -> e) + -> Either e (Rep.Constructor s t) construct e valuesArray decodingErr = do - {init, rest} <- lmap decodingErr $ decodeRepArgs valuesArray - when (rest /= []) $ - Left $ decodingErr $ AtKey e.valuesKey $ UnexpectedValue (fromArray rest) + { init, rest } <- lmap decodingErr $ decodeRepArgs valuesArray + when (rest /= []) + $ Left + $ decodingErr + $ AtKey e.valuesKey + $ UnexpectedValue (fromArray rest) pure $ Rep.Constructor init instance decodeRepConstructorNoArgs :: IsSymbol name => DecodeRep (Rep.Constructor name Rep.NoArguments) where decodeRepWith e j = do let name = reflectSymbol (Proxy :: Proxy name) - {decodingErr} <- withTag e j name + { decodingErr } <- withTag e j name construct e [] decodingErr -else -instance decodeRepConstructorArg :: (IsSymbol name, DecodeJson a) => DecodeRep (Rep.Constructor name (Rep.Argument a)) where +else instance decodeRepConstructorArg :: (IsSymbol name, DecodeJson a) => DecodeRep (Rep.Constructor name (Rep.Argument a)) where decodeRepWith e j = do let name = reflectSymbol (Proxy :: Proxy name) - {values, decodingErr} <- withTagAndValues e j name - if e.unwrapSingleArguments - then construct e [values] decodingErr - else do - valuesArray <- note (decodingErr $ AtKey e.valuesKey $ TypeMismatch "Array") (toArray values) - construct e valuesArray decodingErr -else -instance decodeRepConstructor :: (IsSymbol name, DecodeRepArgs a) => DecodeRep (Rep.Constructor name a) where + { values, decodingErr } <- withTagAndValues e j name + if e.unwrapSingleArguments then construct e [ values ] decodingErr + else do + valuesArray <- note (decodingErr $ AtKey e.valuesKey $ TypeMismatch "Array") (toArray values) + construct e valuesArray decodingErr +else instance decodeRepConstructor :: (IsSymbol name, DecodeRepArgs a) => DecodeRep (Rep.Constructor name a) where decodeRepWith e j = do let name = reflectSymbol (Proxy :: Proxy name) - {values, decodingErr} <- withTagAndValues e j name + { values, decodingErr } <- withTagAndValues e j name valuesArray <- note (decodingErr $ AtKey e.valuesKey $ TypeMismatch "Array") (toArray values) construct e valuesArray decodingErr class DecodeRepArgs r where - decodeRepArgs :: Array Json -> Either JsonDecodeError {init :: r, rest :: Array Json} + decodeRepArgs :: Array Json -> Either JsonDecodeError { init :: r, rest :: Array Json } instance decodeRepArgsNoArguments :: DecodeRepArgs Rep.NoArguments where - decodeRepArgs js = Right {init: Rep.NoArguments, rest: js} + decodeRepArgs js = Right { init: Rep.NoArguments, rest: js } instance decodeRepArgsProduct :: (DecodeRepArgs a, DecodeRepArgs b) => DecodeRepArgs (Rep.Product a b) where decodeRepArgs js = do - {init: a, rest: js'} <- decodeRepArgs js - {init: b, rest: js''} <- decodeRepArgs js' - pure {init: Rep.Product a b, rest: js''} + { init: a, rest: js' } <- decodeRepArgs js + { init: b, rest: js'' } <- decodeRepArgs js' + pure { init: Rep.Product a b, rest: js'' } instance decodeRepArgsArgument :: (DecodeJson a) => DecodeRepArgs (Rep.Argument a) where decodeRepArgs js = do - {head, tail} <- note (TypeMismatch "NonEmptyArray") (uncons js) - {init: _, rest: tail} <<< Rep.Argument <$> decodeJson head + { head, tail } <- note (TypeMismatch "NonEmptyArray") (uncons js) + { init: _, rest: tail } <<< Rep.Argument <$> decodeJson head -- | Decode `Json` representation of a value which has a `Generic` type. genericDecodeJson :: forall a r. Rep.Generic a r => DecodeRep r => Json -> Either JsonDecodeError a @@ -154,15 +158,16 @@ instance decodeLiteralConstructor :: (IsSymbol name) => DecodeLiteral (Rep.Const let name = reflectSymbol (Proxy :: Proxy name) let decodingErr = Named name tag <- note (decodingErr $ TypeMismatch "String") (toString j) - when (tag /= tagNameTransform name) $ - Left $ decodingErr $ UnexpectedValue (fromString tag) + when (tag /= tagNameTransform name) + $ Left + $ decodingErr + $ UnexpectedValue (fromString tag) pure $ Rep.Constructor (Rep.NoArguments) - type FailMessage = Text "`decodeLiteralSum` can only be used with sum types, where all of the constructors are nullary. This is because a string literal cannot be encoded into a product type." -instance decodeLiteralConstructorCannotTakeProduct - :: Fail FailMessage - => DecodeLiteral (Rep.Product a b) where - decodeLiteral _ _ = unsafeCrashWith "unreachable DecodeLiteral was reached." +instance decodeLiteralConstructorCannotTakeProduct :: + Fail FailMessage => + DecodeLiteral (Rep.Product a b) where + decodeLiteral _ _ = unsafeCrashWith "unreachable DecodeLiteral was reached." diff --git a/src/Data/Argonaut/Encode/Generic.purs b/src/Data/Argonaut/Encode/Generic.purs index 283bcd1..4872ba9 100644 --- a/src/Data/Argonaut/Encode/Generic.purs +++ b/src/Data/Argonaut/Encode/Generic.purs @@ -1,16 +1,16 @@ -module Data.Argonaut.Encode.Generic ( - class EncodeRep, - class EncodeRepArgs, - class EncodeLiteral, - encodeRep, - encodeRepWith, - encodeRepArgs, - genericEncodeJson, - genericEncodeJsonWith, - encodeLiteralSum, - encodeLiteralSumWithTransform, - encodeLiteral -) where +module Data.Argonaut.Encode.Generic + ( class EncodeRep + , class EncodeRepArgs + , class EncodeLiteral + , encodeRep + , encodeRepWith + , encodeRepArgs + , genericEncodeJson + , genericEncodeJsonWith + , encodeLiteralSum + , encodeLiteralSumWithTransform + , encodeLiteral + ) where import Prelude @@ -44,13 +44,14 @@ instance encodeRepConstructor :: (IsSymbol name, EncodeRepArgs a) => EncodeRep ( $ FO.insert e.valuesKey values $ FO.empty where - values = - let vs = encodeRepArgs a in - if e.unwrapSingleArguments - then case vs of - [v] -> v - _ -> fromArray vs - else fromArray vs + values = + let + vs = encodeRepArgs a + in + if e.unwrapSingleArguments then case vs of + [ v ] -> v + _ -> fromArray vs + else fromArray vs class EncodeRepArgs r where encodeRepArgs :: r -> Array Json @@ -62,7 +63,7 @@ instance encodeRepArgsProduct :: (EncodeRepArgs a, EncodeRepArgs b) => EncodeRep encodeRepArgs (Rep.Product a b) = encodeRepArgs a <> encodeRepArgs b instance encodeRepArgsArgument :: (EncodeJson a) => EncodeRepArgs (Rep.Argument a) where - encodeRepArgs (Rep.Argument a) = [encodeJson a] + encodeRepArgs (Rep.Argument a) = [ encodeJson a ] -- | Encode any `Generic` data structure into `Json`. genericEncodeJson :: forall a r. Rep.Generic a r => EncodeRep r => a -> Json @@ -95,7 +96,7 @@ instance encodeLiteralConstructor :: (IsSymbol name) => EncodeLiteral (Rep.Const type FailMessage = Text """`encodeLiteralSum` can only be used with sum types, where all of the constructors are nullary. This is because a string literal cannot be encoded into a product type.""" -instance encodeLiteralConstructorCannotBeProduct - :: Fail FailMessage - => EncodeLiteral (Rep.Product a b) where +instance encodeLiteralConstructorCannotBeProduct :: + Fail FailMessage => + EncodeLiteral (Rep.Product a b) where encodeLiteral _ _ = unsafeCrashWith "unreachable encodeLiteral was reached." diff --git a/src/Data/Argonaut/Types/Generic.purs b/src/Data/Argonaut/Types/Generic.purs index a92d770..bdc2122 100644 --- a/src/Data/Argonaut/Types/Generic.purs +++ b/src/Data/Argonaut/Types/Generic.purs @@ -1,7 +1,7 @@ -module Data.Argonaut.Types.Generic ( - Encoding(..), - defaultEncoding -) where +module Data.Argonaut.Types.Generic + ( Encoding(..) + , defaultEncoding + ) where -- | Encoding settings: -- | tagKey -- which key to use in the JSON object for sum-type constructors diff --git a/test/Main.purs b/test/Main.purs index 3e22358..777177d 100644 --- a/test/Main.purs +++ b/test/Main.purs @@ -23,7 +23,7 @@ import Test.Assert (assert) data Example = Either (Either String Example) - | Record { foo :: Int, bar :: String} + | Record { foo :: Int, bar :: String } | Nested { foo :: { nested :: Int }, bar :: String } | Product Int Int Example @@ -31,8 +31,10 @@ derive instance eqExample :: Eq Example derive instance genericExample :: Generic Example _ instance showExample :: Show Example where show a = genericShow a + instance encodeJsonExample :: EncodeJson Example where encodeJson a = genericEncodeJson a + instance decodeJson :: DecodeJson Example where decodeJson a = genericDecodeJson a @@ -45,8 +47,10 @@ derive instance eqLiteralStringExample :: Eq LiteralStringExample derive instance genericLiteralStringExample :: Generic LiteralStringExample _ instance showLiteralStringExample :: Show LiteralStringExample where show a = genericShow a + instance encodeJsonLiteralStringExample :: EncodeJson LiteralStringExample where encodeJson a = encodeLiteralSumWithTransform identity a + instance decodeJsonLiteralStringExample :: DecodeJson LiteralStringExample where decodeJson a = decodeLiteralSumWithTransform identity a @@ -57,12 +61,15 @@ diffEncodingOptions = defaultEncoding } data DiffEncoding = A | B Int + derive instance eqDiffEncoding :: Eq DiffEncoding derive instance genericDiffEncoding :: Generic DiffEncoding _ instance showDiffENcoding :: Show DiffEncoding where show a = genericShow a + instance encodeJsonDiffEncoding :: EncodeJson DiffEncoding where encodeJson a = genericEncodeJsonWith diffEncodingOptions a + instance decodeJsonDiffEncoding :: DecodeJson DiffEncoding where decodeJson a = genericDecodeJsonWith diffEncodingOptions a @@ -72,22 +79,28 @@ unwrapSingleArgsOptions = defaultEncoding } data UnwrapSingleArgs = U0 Int | U1 Int Int + derive instance eqUnwrapSingleArgs :: Eq UnwrapSingleArgs derive instance genericUnwrapSingleArgs :: Generic UnwrapSingleArgs _ instance showUnwrapSingleArgs :: Show UnwrapSingleArgs where show a = genericShow a + instance encodeJsonUnwrapSingleArgs :: EncodeJson UnwrapSingleArgs where encodeJson a = genericEncodeJsonWith unwrapSingleArgsOptions a + instance decodeJsonUnwrapSingleArgs :: DecodeJson UnwrapSingleArgs where decodeJson a = genericDecodeJsonWith unwrapSingleArgsOptions a data IgnoreNullaryArgs = NA0 | NA1 Int + derive instance eqIgnoreNullaryArgs :: Eq IgnoreNullaryArgs derive instance genericIgnoreNullaryArgs :: Generic IgnoreNullaryArgs _ instance showIgnoreNullaryArgs :: Show IgnoreNullaryArgs where show a = genericShow a + instance encodeJsonIgnoreNullaryArgs :: EncodeJson IgnoreNullaryArgs where encodeJson a = genericEncodeJson a + instance decodeJsonIgnoreNullaryArgs :: DecodeJson IgnoreNullaryArgs where decodeJson a = genericDecodeJson a @@ -98,8 +111,8 @@ main :: Effect Unit main = do example $ Either $ Left "foo" example $ Either $ Right $ Either $ Left "foo" - example $ Record {foo: 42, bar: "bar"} - example $ Nested {foo: {nested: 42}, bar: "bar"} + example $ Record { foo: 42, bar: "bar" } + example $ Nested { foo: { nested: 42 }, bar: "bar" } example $ Product 1 2 $ Either $ Left "foo" example $ Frikandel example $ A @@ -131,8 +144,9 @@ main = do assert $ parsed == Right original log $ "--------------------------------------------------------------------------------" - testLiteralSumWithTransform :: forall a rep - . Show a + testLiteralSumWithTransform + :: forall a rep + . Show a => Eq a => Generic a rep => EncodeLiteral rep