{-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE OverloadedLists #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} import Data.Aeson (Value) import Data.Aeson.Flow as Flow import Data.Fix (Fix (..)) import Data.Functor.Foldable import Data.HashMap.Strict (HashMap) import Data.Proxy (Proxy (..)) import Data.Text (Text) import Data.Tree (Tree) import Data.Vector (Vector) import GHC.Generics import Test.Tasty import Test.Tasty.HUnit -- | Pretty-print a flowtype in flowtype syntax exportFlowTypeAs :: Text -> FlowType -> Text exportFlowTypeAs = exportTypeAs RenderOptions{renderMode=RenderFlow} data User = User { username :: Text , realname :: Maybe Text , dob :: Maybe (Int, Int, Int) , extraInfo :: Value } deriving (Generic) instance FlowTyped User data Recur = Recur { asdf :: Int , stuff :: [User] , recurs :: [Recur] } deriving (Generic) instance FlowTyped Recur data Adt2 = A2 | B2 deriving (Generic) instance FlowTyped Adt2 data Adt3 = A3 | B3 | C3 deriving (Generic) instance FlowTyped Adt3 data Adt4 = A4 | B4 | C4 | D4 deriving (Generic) instance FlowTyped Adt4 data Sub = Sub Adt4 deriving (Generic) instance FlowTyped Sub data Codep = Codep { corecurs :: [Recur] , cousers :: [User] , subsub :: Sub } deriving (Generic) instance FlowTyped Codep data Hmap = Hmap (HashMap Text User) deriving (Generic) instance FlowTyped Hmap data Poly2 a b = Poly2 a b | Poly2Go (Poly2 a b) deriving (Generic) instance (Typeable a, FlowTyped a, Typeable b, FlowTyped b) => FlowTyped (Poly2 a b) where flowTypeVars _ = [ typeRep (Var :: Var a) , typeRep (Var :: Var b) ] data Mono = Mono (Poly2 Int Bool) (Poly2 Bool Int) deriving (Generic) instance FlowTyped Mono main :: IO () main = defaultMain $ testGroup "aeson-flowtyped" [ testCase "nullable" $ showFlowType (flowType (Proxy :: Proxy (Maybe Int))) @=? showFlowType (FNullable FPrimNumber) , testCase "array" $ do showFlowType (flowType (Proxy :: Proxy [Int])) @=? showFlowType (FArray FPrimNumber) showFlowType (flowType (Proxy :: Proxy (Vector Int))) @=? showFlowType (FArray FPrimNumber) -- (Fix (Array (Fix (Prim Number)))) -- XXX: actually use Eq , testCase "User export" $ "export type User =\n\ \ {| extraInfo: mixed,\n\ \ dob: null | [number,number,number],\n\ \ username: string,\n\ \ realname: null | string |};" @=? exportFlowTypeAs "User" (flowType (Proxy :: Proxy User)) , testCase "Recursive type export" $ "export type Recur =\n\ \ {| stuff: User[], recurs: Recur[], asdf: number |};" @=? exportFlowTypeAs "Recur" (flowType (Proxy :: Proxy Recur)) , testCase "Nullary string tags (2 tags)" $ "export type Adt2 =\n\ \ 'A2' |\n\ \ 'B2';" @=? exportFlowTypeAs "Adt2" (flowType (Proxy :: Proxy Adt2)) , testCase "Nullary string tags (3 tags)" $ "export type Adt3 =\n\ \ 'A3' |\n\ \ 'B3' |\n\ \ 'C3';" @=? exportFlowTypeAs "Adt3" (flowType (Proxy :: Proxy Adt3)) , testCase "Nullary string tags (4 tags)" $ "export type Adt4 =\n\ \ 'A4' |\n\ \ 'B4' |\n\ \ 'C4' |\n\ \ 'D4';" @=? exportFlowTypeAs "Adt4" (flowType (Proxy :: Proxy Adt4)) , testCase "map-style object / hashmap instance" $ "export type Hmap =\n\ \ { [key: string]: User };" @=? exportFlowTypeAs "Hmap" (flowType (Proxy :: Proxy (HashMap Text User))) , testCase "parens around nullable array" $ "export type T =\n\ \ null | string[];" @=? exportFlowTypeAs "T" (flowType (Proxy :: Proxy (Maybe [Text]))) , testCase "parens around nullable array of nullable elements" $ "export type T =\n\ \ null | (null | string)[];" @=? exportFlowTypeAs "T" (flowType (Proxy :: Proxy (Maybe [Maybe Text]))) , testCase "export dependencies" $ [ FlowName (Proxy :: Proxy Codep) "Codep" , FlowName (Proxy :: Proxy User) "User" , FlowName (Proxy :: Proxy Recur) "Recur" , FlowName (Proxy :: Proxy Sub) "Sub" , FlowName (Proxy :: Proxy Adt4) "Adt4" ] @=? exportsDependencies [ Export (Proxy :: Proxy Codep) ] , testCase "polymorphism (arity 1)" $ "// @flow\n\ \// This module has been generated by aeson-flowtyped.\n\n\ \export type Tree =\n\ \ [A,Tree[]];\n" @=? generateModule flowModuleOptions [ Export (Proxy :: Proxy (Tree (Var 0))) ] {- , testCase "polymorphism (arity 2)" $ "// @flow\n\ \// This module has been generated by aeson-flowtyped.\n\n\ \export type Poly2 =\n\ \ {| tag: 'Poly2', contents: [A,B] |} |\n\ \ {| tag: 'Poly2Go', contents: Poly2 |};\n" @=? generateModule flowModuleOptions [ Export (Proxy :: Proxy (Poly2 (Var 0) (Var 1))) ] -} , testCase "monomorphic use of polymorphic type (dependencies)" $ [ FlowName (Proxy :: Proxy Mono) "Mono" , FlowName (Proxy :: Proxy (Poly2 () ())) "Poly2" ] @=? exportsDependencies [Export (Proxy :: Proxy Mono)] {- , testCase "monomorphic use of polymorphic type" $ "// @flow\n\ \// This module has been generated by aeson-flowtyped.\n\n\ \export type Poly2 =\n\ \ {| tag: 'Poly2', contents: [A,B] |} |\n\ \ {| tag: 'Poly2Go', contents: Poly2 |};\n" @=? generateModule flowModuleOptions [Export (Proxy :: Proxy Mono)] -} ]