{-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE CPP #-} module Main where import Control.Monad (unless) import qualified Data.Map as Map import Data.Proxy import qualified Data.Text as T import Language.PureScript.Bridge import Language.PureScript.Bridge.TypeParameters import Test.Hspec (Spec, hspec, describe, it) import Test.Hspec.Expectations.Pretty import TestData main :: IO () main = hspec $ do allTests allTests :: Spec allTests = describe "buildBridge" $ do it "tests with Int" $ let bst = buildBridge defaultBridge (mkTypeInfo (Proxy :: Proxy Int)) ti = TypeInfo { _typePackage = "purescript-prim" , _typeModule = "Prim" , _typeName = "Int" , _typeParameters = []} in bst `shouldBe` ti it "tests with custom type Foo" $ let bst = bridgeSumType (buildBridge defaultBridge) (mkSumType (Proxy :: Proxy Foo)) st = SumType TypeInfo { _typePackage = "" , _typeModule = "TestData" , _typeName = "Foo" , _typeParameters = [] } [ DataConstructor { _sigConstructor = "Foo" , _sigValues = Left [] } , DataConstructor { _sigConstructor = "Bar" , _sigValues = Left [ TypeInfo { _typePackage = "purescript-prim" , _typeModule = "Prim" , _typeName = "Int" , _typeParameters = [] } ] } , DataConstructor { _sigConstructor = "FooBar" , _sigValues = Left [ TypeInfo { _typePackage = "purescript-prim" , _typeModule = "Prim" , _typeName = "Int" , _typeParameters = [] } , TypeInfo { _typePackage = "purescript-prim" , _typeModule = "Prim" , _typeName = "String" , _typeParameters = [] } ] } ] in bst `shouldBe` st it "tests the generation of a whole (dummy) module" $ let advanced = bridgeSumType (buildBridge defaultBridge) (mkSumType (Proxy :: Proxy (Bar A B M1))) modules = sumTypeToModule advanced Map.empty m = head . map moduleToText . Map.elems $ modules txt = T.unlines [ "-- File auto generated by purescript-bridge! --" , "module TestData where" , "" , "import Data.Either (Either)" , "import Data.Maybe (Maybe)" , "" , "import Data.Generic (class Generic)" , "" , "" , "data Bar a b m =" , " Bar1 (Maybe a)" , " | Bar2 (Either a b)" , " | Bar3 a" , " | Bar4 {" , " myMonadicResult :: m b" , " }" , "" , "derive instance genericBar :: Generic Bar" , "" ] in m `shouldBe` txt