module Type.HS2PSSpec (spec) where import Type.HS2PS import Test.Hspec import Test.Types import Language.Haskell.TH.Lib spec :: Spec spec = do describe "renderPSTypes" do it "two types" $ $(renderPSTypes [''Either, ''NT]) `shouldBe` "data Either a b = Left a | Right b\n\ \newtype NT = NTc Int" describe "def2PS" do it "Either" $ $(litE . stringL =<< def2PS ''Either) `shouldBe` "data Either a b = Left a | Right b" it "Non-prim interal type" $ $(litE . stringL =<< def2PS ''NonPrim) `shouldBe` "data NonPrim = NonPrimC (Tuple Char (Either Int Number)) (Either Bool String)" describe "newtype" do it "NT" $ $(litE . stringL =<< def2PS ''NT) `shouldBe` "newtype NT = NTc Int" it "NTRecord" $ $(litE . stringL =<< def2PS ''NTRecord) `shouldBe` "newtype NTRecord = NTRecordC {getNTRecordC :: Int}" describe "data" do it "one constructor with two types" $ $(litE . stringL =<< def2PS ''Data1C2T) `shouldBe` "data Data1C2T = Data1C2Tc Int String" it "ABC" $ $(litE . stringL =<< def2PS ''ABC) `shouldBe` "data ABC = A | B | C" describe "record" do it "Record" $ $(litE . stringL =<< def2PS ''Record) `shouldBe` "newtype Record = RecordC {a :: Int, b :: Bool, c :: Char}" it "ADTRecord" $ $(litE . stringL =<< def2PS ''ADTRecord) `shouldBe` "data ADTRecord = ADTRecordA {adtA :: Int} | ADTRecordB {adtB :: Bool, adtBB :: String}" describe "type alias" do it "String" $ $(litE . stringL =<< def2PS '' String) `shouldBe` "type String = Array Char" describe "ToPS" do describe "Unit" do it "()" $ $(type2PS ''()) `shouldBe` "Unit" describe "prims" do it "Int" $ $(type2PS ''Int) `shouldBe` "Int" it "Double" $ $(type2PS ''Double) `shouldBe` "Number" it "Bool" $ $(type2PS ''Bool) `shouldBe` "Bool" it "Char" $ $(type2PS ''Char) `shouldBe` "Char" it "String" $ $(type2PS ''String) `shouldBe` "String" -- it "Text" $ $(type2PS ''Text) `shouldBe` "String" -- it "ByteString" $ $(type2PS ''ByteString) `shouldBe` "String" describe "no type arguments" do it "NTRecord" $ $(type2PS ''NTRecord) `shouldBe` "NTRecord" describe "Sum Types" do describe "SumType" do it "prim" $ $(type2PS ''SumType) `shouldBe` "SumType" -- it "non-prim" $ toPS @(SumType (Maybe Int) (Either Double Bool) (SumType String () Text)) `shouldBe` -- "SumType (Maybe Int) (Either Number Bool) (SumType String Unit String)" -- -- describe "Maybe" do -- it "prim" $ toPS @(Maybe Int) `shouldBe` -- "Maybe Int" -- -- it "non-prim" $ toPS @(Maybe (Maybe Int)) `shouldBe` -- "Maybe (Maybe Int)" -- -- it "non-prim unit" $ toPS @(Maybe (Maybe ())) `shouldBe` -- "Maybe (Maybe Unit)" -- -- describe "Either" do -- it "prims" $ toPS @(Either Int Bool) `shouldBe` -- "Either Int Bool" -- -- it "non-prim right" $ toPS @(Either Double (Either Int Bool)) `shouldBe` -- "Either Number (Either Int Bool)" -- -- it "non-prim left" $ toPS @(Either (Either Bool Int) Double) `shouldBe` -- "Either (Either Bool Int) Number" -- -- it "non-prim" $ toPS @(Either (Either Int Bool) (Either Text Double)) `shouldBe` -- "Either (Either Int Bool) (Either String Number)" -- -- describe "Reversed" do -- it "prims" $ toPS @(Reversed Int Bool) `shouldBe` -- "Reversed Int Bool" -- -- describe "Product Type" do -- -- describe "Tuple" do -- it "prims" $ toPS @(Int, Text) `shouldBe` -- "Tuple Int String" -- -- it "Non-prims" $ toPS @(Either Int Bool, (String, ByteString)) `shouldBe` -- "Tuple (Either Int Bool) (Tuple String String)" --