aeson-typescript-0.6.3.0: Generate TypeScript definition files from your ADTs
Copyright(c) 2022 Tom McLaughlin
LicenseBSD3
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Aeson.TypeScript.TH

Description

This library provides a way to generate TypeScript .d.ts files that match your existing Aeson ToJSON instances. If you already use Aeson's Template Haskell support to derive your instances, then deriving TypeScript is as simple as

$(deriveTypeScript myAesonOptions ''MyType)

For example,

data D a = Nullary
         | Unary Int
         | Product String Char a
         | Record { testOne   :: Double
                  , testTwo   :: Bool
                  , testThree :: D a
                  } deriving Eq

Next we derive the necessary instances.

$(deriveTypeScript (defaultOptions {fieldLabelModifier = drop 4, constructorTagModifier = map toLower}) ''D)

Now we can use the newly created instances.

>>> putStrLn $ formatTSDeclarations $ getTypeScriptDeclarations (Proxy :: Proxy (D T))

type D<T> = INullary<T> | IUnary<T> | IProduct<T> | IRecord<T>;

interface INullary<T> {
  tag: "nullary";
}

interface IUnary<T> {
  tag: "unary";
  contents: number;
}

interface IProduct<T> {
  tag: "product";
  contents: [string, string, T];
}

interface IRecord<T> {
  tag: "record";
  One: number;
  Two: boolean;
  Three: D<T>;
}

It's important to make sure your JSON and TypeScript are being derived with the same options. For this reason, we include the convenience HasJSONOptions typeclass, which lets you write the options only once, like this:

instance HasJSONOptions MyType where getJSONOptions _ = (defaultOptions {fieldLabelModifier = drop 4})

$(deriveJSON (getJSONOptions (Proxy :: Proxy MyType)) ''MyType)
$(deriveTypeScript (getJSONOptions (Proxy :: Proxy MyType)) ''MyType)

Or, if you want to be even more concise and don't mind defining the instances in the same file,

myOptions = defaultOptions {fieldLabelModifier = drop 4}

$(deriveJSONAndTypeScript myOptions ''MyType)

Remembering that the Template Haskell Q monad is an ordinary monad, you can derive instances for several types at once like this:

$(mconcat <$> traverse (deriveJSONAndTypeScript myOptions) [''MyType1, ''MyType2, ''MyType3])

Once you've defined all necessary instances, you can write a main function to dump them out into a .d.ts file. For example:

main = putStrLn $ formatTSDeclarations (
  (getTypeScriptDeclarations (Proxy :: Proxy MyType1)) <>
  (getTypeScriptDeclarations (Proxy :: Proxy MyType2)) <>
  ...
)
Synopsis

Documentation

deriveTypeScript Source #

Arguments

:: Options

Encoding options.

-> Name

Name of the type for which to generate a TypeScript instance declaration.

-> Q [Dec] 

Generates a TypeScript instance declaration for the given data type.

deriveTypeScript' Source #

Arguments

:: Options

Encoding options.

-> Name

Name of the type for which to generate a TypeScript instance declaration.

-> ExtraTypeScriptOptions

Extra options to control advanced features.

-> Q [Dec] 

Generates a TypeScript instance declaration for the given data type.

deriveTypeScriptLookupType Source #

Arguments

:: Name

Name of a type family.

-> String

Name of the declaration to derive.

-> Q [Dec] 

Generates a TypeScript declaration for a closed type family as a lookup type.

The main typeclass

class Typeable a => TypeScript a where Source #

The typeclass that defines how a type is turned into TypeScript.

The getTypeScriptDeclarations method describes the top-level declarations that are needed for a type, while getTypeScriptType describes how references to the type should be translated. The getTypeScriptOptional method exists purely so that Maybe types can be encoded with a question mark.

Instances for common types are built-in and are usually very simple; for example,

instance TypeScript Bool where
  getTypeScriptType _ = "boolean"

Most of the time you should not need to write instances by hand; in fact, the TSDeclaration constructors are deliberately opaque. However, you may occasionally need to specify the type of something. For example, since UTCTime is encoded to a JSON string and is not built-in to this library:

import Data.Time.Clock (UTCTime)

instance TypeScript UTCTime where
  getTypeScriptType _ = "string"

If you need to write a definition for a higher-order type, it may depend on a type parameter. For example, a Set is encoded to a JSON list of the underlying type:

instance (TypeScript a) => TypeScript (Set a) where
  getTypeScriptType _ = getTypeScriptType (Proxy :: Proxy a) <> "[]";

Minimal complete definition

getTypeScriptType

Methods

getTypeScriptDeclarations :: Proxy a -> [TSDeclaration] Source #

Get the declaration(s) needed for this type.

getTypeScriptType :: Proxy a -> String Source #

Get the type as a string.

getTypeScriptKeyType :: Proxy a -> String Source #

getTypeScriptOptional :: Proxy a -> Bool Source #

Get a flag representing whether this type is optional.

getParentTypes :: Proxy a -> [TSType] Source #

Get the types that this type depends on. This is useful for generating transitive closures of necessary types.

isGenericVariable :: Proxy a -> Bool Source #

Special flag to indicate whether this type corresponds to a template variable.

Instances

Instances details
TypeScript Value Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript T Source # 
Instance details

Defined in Data.Aeson.TypeScript.Types

TypeScript T1 Source # 
Instance details

Defined in Data.Aeson.TypeScript.Types

TypeScript T10 Source # 
Instance details

Defined in Data.Aeson.TypeScript.Types

TypeScript T2 Source # 
Instance details

Defined in Data.Aeson.TypeScript.Types

TypeScript T3 Source # 
Instance details

Defined in Data.Aeson.TypeScript.Types

TypeScript T4 Source # 
Instance details

Defined in Data.Aeson.TypeScript.Types

TypeScript T5 Source # 
Instance details

Defined in Data.Aeson.TypeScript.Types

TypeScript T6 Source # 
Instance details

Defined in Data.Aeson.TypeScript.Types

TypeScript T7 Source # 
Instance details

Defined in Data.Aeson.TypeScript.Types

TypeScript T8 Source # 
Instance details

Defined in Data.Aeson.TypeScript.Types

TypeScript T9 Source # 
Instance details

Defined in Data.Aeson.TypeScript.Types

TypeScript Void Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript Int16 Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript Int32 Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript Int64 Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript Word16 Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript Word32 Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript Word64 Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript Word8 Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript Text Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript Text Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript Integer Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript Natural Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript () Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript Bool Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript Char Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript Double Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript Float Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript Int Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript Word Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript a => TypeScript (KeyMap a :: Type) Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript a => TypeScript (Identity a :: Type) Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript a => TypeScript (NonEmpty a :: Type) Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript a => TypeScript (Set a :: Type) Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript a => TypeScript (HashSet a :: Type) Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript a => TypeScript (Maybe a :: Type) Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript [Char] Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

TypeScript a => TypeScript ([a] :: Type) Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

(TypeScript a, TypeScript b) => TypeScript (Either a b :: Type) Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

(TypeScript a, TypeScript b) => TypeScript (Map a b :: Type) Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

(TypeScript a, TypeScript b) => TypeScript (HashMap a b :: Type) Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

(TypeScript a, TypeScript b) => TypeScript ((a, b) :: Type) Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

(Typeable k, Typeable b, TypeScript a) => TypeScript (Const a b :: Type) Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

(TypeScript a, TypeScript b, TypeScript c) => TypeScript ((a, b, c) :: Type) Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

(Typeable k, Typeable f, Typeable g, Typeable a, TypeScript (f a), TypeScript (g a)) => TypeScript (Product f g a :: Type) Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

(TypeScript a, TypeScript b, TypeScript c, TypeScript d) => TypeScript ((a, b, c, d) :: Type) Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

(Typeable k, Typeable k1, Typeable f, Typeable g, Typeable a, TypeScript (f (g a)), TypeScript a) => TypeScript (Compose f g a :: Type) Source # 
Instance details

Defined in Data.Aeson.TypeScript.Instances

data TSType Source #

An existential wrapper for any TypeScript instance.

Constructors

forall a.(Typeable a, TypeScript a) => TSType 

Fields

Instances

Instances details
Show TSType Source # 
Instance details

Defined in Data.Aeson.TypeScript.Types

Eq TSType Source # 
Instance details

Defined in Data.Aeson.TypeScript.Types

Methods

(==) :: TSType -> TSType -> Bool #

(/=) :: TSType -> TSType -> Bool #

Ord TSType Source # 
Instance details

Defined in Data.Aeson.TypeScript.Types

Formatting declarations

formatTSDeclarations :: [TSDeclaration] -> String Source #

Same as formatTSDeclarations', but uses default formatting options.

formatTSDeclarations' :: FormattingOptions -> [TSDeclaration] -> String Source #

Format a list of TypeScript declarations into a string, suitable for putting directly into a .d.ts file.

formatTSDeclaration :: FormattingOptions -> TSDeclaration -> String Source #

Format a single TypeScript declaration. This version accepts a FormattingOptions object in case you want more control over the output.

data FormattingOptions Source #

Constructors

FormattingOptions 

Fields

defaultNameFormatter :: String -> String Source #

The defaultNameFormatter in the FormattingOptions checks to see if the name is a legal TypeScript name. If it is not, then it throws a runtime error.

data SumTypeFormat Source #

TODO: docstrings here

Constructors

TypeAlias 
Enum 
EnumWithType 

data ExportMode Source #

Constructors

ExportEach

Prefix every declaration with the "export" keyword (suitable for putting in a TypeScripe module)

ExportNone

No exporting (suitable for putting in a .d.ts file)

Advanced options

data ExtraTypeScriptOptions Source #

Type variable gathering

Convenience tools

class HasJSONOptions a where Source #

Convenience typeclass class you can use to "attach" a set of Aeson encoding options to a type.

deriveJSONAndTypeScript Source #

Arguments

:: Options

Encoding options.

-> Name

Name of the type for which to generate ToJSON, FromJSON, and TypeScript instance declarations.

-> Q [Dec] 

Convenience function to generate ToJSON, FromJSON, and TypeScript instances simultaneously, so the instances are guaranteed to be in sync.

This function is given mainly as an illustration. If you want some other permutation of instances, such as ToJSON and TypeScript only, just take a look at the source and write your own version.

Since: 0.1.0.4

deriveJSONAndTypeScript' Source #

Arguments

:: Options

Encoding options.

-> Name

Name of the type for which to generate ToJSON, FromJSON, and TypeScript instance declarations.

-> ExtraTypeScriptOptions

Extra options to control advanced features.

-> Q [Dec]