{-# OPTIONS_GHC -Wno-orphans #-} module Data.Aeson.Generics.TypeScript.ASTSpec ( main , spec ) where import Data.Aeson.Generics.TypeScript ( FieldSpec (FieldSpec, fs_wrapped) , FieldType (ConcreteField, GenericField) , IsNewtype (Newtype, Oldtype) , TSField (TSField) , TSGenericVar , TSInterface (TSInterface) , TSType (TSType) , TypeScriptDefinition (..) , concretely , genericly ) import Data.Aeson.Generics.TypeScript.Types ( CouldBe , GenericRecordInSum , HasEither , ItsEnum , ItsRecord , ItsRecordWithGeneric , MapParty , NewIdentity , Prod , RecordWithWrappedType , Sum , Unit , definedIn ) import Data.List.NonEmpty (NonEmpty ((:|))) import Data.Time.Clock (UTCTime) import Test.Hspec (Spec, hspec, it, shouldBe) import Test.Hspec.QuickCheck (prop) import Test.QuickCheck (Arbitrary (..), arbitraryBoundedEnum) instance Arbitrary FieldType where arbitrary = arbitraryBoundedEnum -- | Form a list like thing as a product (@:|) :: (Applicative f, Semigroup (f p)) => p -> p -> f p x @:| y = pure x <> pure y main :: IO () main = hspec spec unitExpected :: TSType unitExpected = TSType "Unit" definedIn (pure $ TSInterface "MkUnit" Nothing []) Oldtype mkCouldBe :: FieldSpec -> TSType mkCouldBe x = TSType "CouldBe" definedIn ( TSInterface "ForSure" Nothing [TSField Nothing x] @:| TSInterface "Nah" Nothing []) Oldtype mkSum :: FieldSpec -> FieldSpec -> TSType mkSum x y = TSType "Sum" definedIn (TSInterface "Foyst" Nothing [TSField Nothing x] @:| TSInterface "Loser" Nothing [TSField Nothing y]) Oldtype mkProd :: FieldSpec -> FieldSpec -> FieldSpec -> TSType mkProd x y z = TSType "Prod" definedIn (pure $ TSInterface "MkProd" Nothing [TSField Nothing x, TSField Nothing y, TSField Nothing z]) Oldtype itsEnumExpected :: TSType itsEnumExpected = TSType "ItsEnum" definedIn ( TSInterface "One" Nothing [] :| [ TSInterface "Two" Nothing [], TSInterface "Three" Nothing [] ]) Oldtype itsRecordExpected :: TSType itsRecordExpected = TSType "ItsRecord" definedIn (pure $ TSInterface "MkItsRecord" Nothing [ TSField (Just "oneThing") (concretely "number") , TSField (Just "twoThing") (concretely "string") , TSField (Just "threeThing") (concretely "[]") ]) Oldtype itsRecordWithGenericExpected :: TSType itsRecordWithGenericExpected = TSType "ItsRecordWithGeneric" definedIn (pure $ TSInterface "MkItsRecordWithGeneric" Nothing [ TSField (Just "oneThing") $ concretely "number" , TSField (Just "twoThing") $ (concretely "string") { fs_wrapped = "string | null" } , TSField (Just "threeThing") $ genericly "A" ]) Oldtype genericRecordInSumExpected :: TSType genericRecordInSumExpected = TSType "GenericRecordInSum" definedIn ( TSInterface "OtherThing" Nothing [] @:| TSInterface "MkGenericRecordInSum" Nothing [ TSField (Just "oneThing") (concretely "number") , TSField (Just "twoThing") (FieldSpec GenericField "Array" "A") ]) Oldtype recordWithWrappedTypeExpected :: TSType recordWithWrappedTypeExpected = TSType "RecordWithWrappedType" definedIn (pure $ TSInterface "RecordWithWrappedType" Nothing [ TSField (Just "oneThing") (concretely "number") , TSField (Just "twoThing") (FieldSpec ConcreteField "Array" "string") ]) Oldtype digitalExpected :: TSType digitalExpected = TSType "NewIdentity" definedIn ( pure $ TSInterface "NewIdentity" Nothing [ TSField Nothing (genericly "A") ]) Newtype mapPartyIntStringExpected :: TSType mapPartyIntStringExpected = TSType "MapParty" definedIn (pure $ TSInterface "MapParty" Nothing [ TSField Nothing $ FieldSpec ConcreteField "{ [key: string]: string }" "number,string" ]) Newtype hasEitherExpected :: TSType hasEitherExpected = TSType "HasEither" definedIn (pure $ TSInterface "HasEither" Nothing [ TSField (Just "notTheEither") $ FieldSpec ConcreteField "number" "number" , TSField (Just "theEither") $ FieldSpec ConcreteField "{ Left: string } | { Right: boolean }" "{ Left: string } | { Right: boolean }" ]) Oldtype spec :: Spec spec = do prop "FieldType Semigroup" \x y z -> x <> (y <> z) == (x <> y) <> (z :: FieldType) it "Unit" $ gen @Unit `shouldBe` unitExpected it "CouldBe a" $ gen @(CouldBe (TSGenericVar "a")) `shouldBe` mkCouldBe (genericly "A") it "CouldBe ()" $ gen @(CouldBe ()) `shouldBe` mkCouldBe (concretely "[]") it "CouldBe Int" $ gen @(CouldBe Int) `shouldBe` mkCouldBe (concretely "number") it "CouldBe String" $ gen @(CouldBe String) `shouldBe` mkCouldBe (concretely "string") it "CouldBe UTCTime" $ gen @(CouldBe UTCTime) `shouldBe` mkCouldBe (concretely "string") it "Sum Int ()" $ gen @(Sum Int ()) `shouldBe` mkSum (concretely "number") (concretely "[]") it "Sum () String" $ gen @(Sum () String) `shouldBe` mkSum (concretely "[]") (concretely "string") it "Sum a a" $ gen @(Sum (TSGenericVar "a") (TSGenericVar "a")) `shouldBe` mkSum (genericly "A") (genericly "A") it "Prod Int () String" $ gen @(Prod Int () String) `shouldBe` mkProd (concretely "number") (concretely "[]") (concretely "string") it "Prod a a a" $ gen @(Prod (TSGenericVar "a") (TSGenericVar "a") (TSGenericVar "a")) `shouldBe` mkProd (genericly "A") (genericly "A") (genericly "A") it "ItsEnum" $ gen @ItsEnum `shouldBe` itsEnumExpected it "ItsRecord" $ gen @ItsRecord `shouldBe` itsRecordExpected it "ItsRecordWithGeneric" $ gen @(ItsRecordWithGeneric (TSGenericVar "a")) `shouldBe` itsRecordWithGenericExpected it "GenericRecordInSum" $ gen @(GenericRecordInSum (TSGenericVar "a")) `shouldBe` genericRecordInSumExpected it "RecordWithWrappedType" $ gen @RecordWithWrappedType `shouldBe` recordWithWrappedTypeExpected it "NewIdentity" $ gen @(NewIdentity (TSGenericVar "a")) `shouldBe` digitalExpected it "MapParty Int String" $ gen @(MapParty Int String) `shouldBe` mapPartyIntStringExpected it "HasEither" $ gen @HasEither `shouldBe` hasEitherExpected