{-# LANGUAGE DataKinds #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE NoImplicitPrelude #-} module Data.Morpheus.Client.Declare.Client ( declareTypes, ) where import Data.Morpheus.Client.Declare.Aeson ( aesonDeclarations, ) import Data.Morpheus.Client.Declare.Type ( typeDeclarations, ) import Data.Morpheus.Client.Internal.Types ( ClientTypeDefinition (..), ) import Language.Haskell.TH import Relude hiding (Type) declareTypes :: [ClientTypeDefinition] -> Q [Dec] declareTypes :: [ClientTypeDefinition] -> Q [Dec] declareTypes [ClientTypeDefinition] subTypes = forall (t :: * -> *) a. Foldable t => t [a] -> [a] concat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> forall (t :: * -> *) (f :: * -> *) a b. (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) traverse ClientTypeDefinition -> Q [Dec] declareType [ClientTypeDefinition] subTypes declareType :: ClientTypeDefinition -> Q [Dec] declareType :: ClientTypeDefinition -> Q [Dec] declareType clientType :: ClientTypeDefinition clientType@ClientTypeDefinition {TypeKind clientKind :: ClientTypeDefinition -> TypeKind clientKind :: TypeKind clientKind} = do [Dec] types <- TypeKind -> ClientTypeDefinition -> Q [Dec] typeDeclarations TypeKind clientKind ClientTypeDefinition clientType [Dec] instances <- TypeKind -> ClientTypeDefinition -> Q [Dec] aesonDeclarations TypeKind clientKind ClientTypeDefinition clientType forall (f :: * -> *) a. Applicative f => a -> f a pure ([Dec] types forall a. Semigroup a => a -> a -> a <> [Dec] instances)