Copyright | (c) 2022 Tom McLaughlin |
---|---|
License | BSD3 |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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
- deriveTypeScript :: Options -> Name -> Q [Dec]
- deriveTypeScript' :: Options -> Name -> ExtraTypeScriptOptions -> Q [Dec]
- deriveTypeScriptLookupType :: Name -> String -> Q [Dec]
- class Typeable a => TypeScript a where
- getTypeScriptDeclarations :: Proxy a -> [TSDeclaration]
- getTypeScriptType :: Proxy a -> String
- getTypeScriptKeyType :: Proxy a -> String
- getTypeScriptOptional :: Proxy a -> Bool
- getParentTypes :: Proxy a -> [TSType]
- isGenericVariable :: Proxy a -> Bool
- data TSType = forall a.(Typeable a, TypeScript a) => TSType {}
- data TSDeclaration = TSRawDeclaration String
- formatTSDeclarations :: [TSDeclaration] -> String
- formatTSDeclarations' :: FormattingOptions -> [TSDeclaration] -> String
- formatTSDeclaration :: FormattingOptions -> TSDeclaration -> String
- data FormattingOptions = FormattingOptions {}
- defaultFormattingOptions :: FormattingOptions
- defaultNameFormatter :: String -> String
- data SumTypeFormat
- data ExportMode
- defaultExtraTypeScriptOptions :: ExtraTypeScriptOptions
- keyType :: ExtraTypeScriptOptions -> Maybe String
- typeFamiliesToMapToTypeScript :: ExtraTypeScriptOptions -> [Name]
- data ExtraTypeScriptOptions
- class HasJSONOptions a where
- getJSONOptions :: Proxy a -> Options
- deriveJSONAndTypeScript :: Options -> Name -> Q [Dec]
- deriveJSONAndTypeScript' :: Options -> Name -> ExtraTypeScriptOptions -> Q [Dec]
- data T = T
- data T1 = T1
- data T2 = T2
- data T3 = T3
- data T4 = T4
- data T5 = T5
- data T6 = T6
- data T7 = T7
- data T8 = T8
- data T9 = T9
- data T10 = T10
Documentation
:: Options | Encoding options. |
-> Name | Name of the type for which to generate a |
-> Q [Dec] |
Generates a TypeScript
instance declaration for the given data type.
:: Options | Encoding options. |
-> Name | Name of the type for which to generate a |
-> ExtraTypeScriptOptions | Extra options to control advanced features. |
-> Q [Dec] |
Generates a TypeScript
instance declaration for the given data type.
deriveTypeScriptLookupType Source #
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) <> "[]";
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
An existential wrapper for any TypeScript instance.
forall a.(Typeable a, TypeScript a) => TSType | |
data TSDeclaration Source #
Instances
Show TSDeclaration Source # | |
Defined in Data.Aeson.TypeScript.Types showsPrec :: Int -> TSDeclaration -> ShowS # show :: TSDeclaration -> String # showList :: [TSDeclaration] -> ShowS # | |
Eq TSDeclaration Source # | |
Defined in Data.Aeson.TypeScript.Types (==) :: TSDeclaration -> TSDeclaration -> Bool # (/=) :: TSDeclaration -> TSDeclaration -> Bool # | |
Ord TSDeclaration Source # | |
Defined in Data.Aeson.TypeScript.Types compare :: TSDeclaration -> TSDeclaration -> Ordering # (<) :: TSDeclaration -> TSDeclaration -> Bool # (<=) :: TSDeclaration -> TSDeclaration -> Bool # (>) :: TSDeclaration -> TSDeclaration -> Bool # (>=) :: TSDeclaration -> TSDeclaration -> Bool # max :: TSDeclaration -> TSDeclaration -> TSDeclaration # min :: TSDeclaration -> TSDeclaration -> TSDeclaration # |
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 #
FormattingOptions | |
|
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
Instances
Show SumTypeFormat Source # | |
Defined in Data.Aeson.TypeScript.Types showsPrec :: Int -> SumTypeFormat -> ShowS # show :: SumTypeFormat -> String # showList :: [SumTypeFormat] -> ShowS # | |
Eq SumTypeFormat Source # | |
Defined in Data.Aeson.TypeScript.Types (==) :: SumTypeFormat -> SumTypeFormat -> Bool # (/=) :: SumTypeFormat -> SumTypeFormat -> Bool # |
data ExportMode Source #
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.
getJSONOptions :: Proxy a -> Options Source #
deriveJSONAndTypeScript Source #
:: Options | Encoding options. |
-> Name | Name of the type for which to generate |
-> 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 #
:: Options | Encoding options. |
-> Name | Name of the type for which to generate |
-> ExtraTypeScriptOptions | Extra options to control advanced features. |
-> Q [Dec] |
Instances
TypeScript T Source # | |
Defined in Data.Aeson.TypeScript.Types getTypeScriptDeclarations :: Proxy T -> [TSDeclaration] Source # getTypeScriptType :: Proxy T -> String Source # getTypeScriptKeyType :: Proxy T -> String Source # getTypeScriptOptional :: Proxy T -> Bool Source # |
Instances
TypeScript T1 Source # | |
Defined in Data.Aeson.TypeScript.Types getTypeScriptDeclarations :: Proxy T1 -> [TSDeclaration] Source # getTypeScriptType :: Proxy T1 -> String Source # getTypeScriptKeyType :: Proxy T1 -> String Source # getTypeScriptOptional :: Proxy T1 -> Bool Source # |
Instances
TypeScript T2 Source # | |
Defined in Data.Aeson.TypeScript.Types getTypeScriptDeclarations :: Proxy T2 -> [TSDeclaration] Source # getTypeScriptType :: Proxy T2 -> String Source # getTypeScriptKeyType :: Proxy T2 -> String Source # getTypeScriptOptional :: Proxy T2 -> Bool Source # |
Instances
TypeScript T3 Source # | |
Defined in Data.Aeson.TypeScript.Types getTypeScriptDeclarations :: Proxy T3 -> [TSDeclaration] Source # getTypeScriptType :: Proxy T3 -> String Source # getTypeScriptKeyType :: Proxy T3 -> String Source # getTypeScriptOptional :: Proxy T3 -> Bool Source # |
Instances
TypeScript T4 Source # | |
Defined in Data.Aeson.TypeScript.Types getTypeScriptDeclarations :: Proxy T4 -> [TSDeclaration] Source # getTypeScriptType :: Proxy T4 -> String Source # getTypeScriptKeyType :: Proxy T4 -> String Source # getTypeScriptOptional :: Proxy T4 -> Bool Source # |
Instances
TypeScript T5 Source # | |
Defined in Data.Aeson.TypeScript.Types getTypeScriptDeclarations :: Proxy T5 -> [TSDeclaration] Source # getTypeScriptType :: Proxy T5 -> String Source # getTypeScriptKeyType :: Proxy T5 -> String Source # getTypeScriptOptional :: Proxy T5 -> Bool Source # |
Instances
TypeScript T6 Source # | |
Defined in Data.Aeson.TypeScript.Types getTypeScriptDeclarations :: Proxy T6 -> [TSDeclaration] Source # getTypeScriptType :: Proxy T6 -> String Source # getTypeScriptKeyType :: Proxy T6 -> String Source # getTypeScriptOptional :: Proxy T6 -> Bool Source # |
Instances
TypeScript T7 Source # | |
Defined in Data.Aeson.TypeScript.Types getTypeScriptDeclarations :: Proxy T7 -> [TSDeclaration] Source # getTypeScriptType :: Proxy T7 -> String Source # getTypeScriptKeyType :: Proxy T7 -> String Source # getTypeScriptOptional :: Proxy T7 -> Bool Source # |
Instances
TypeScript T8 Source # | |
Defined in Data.Aeson.TypeScript.Types getTypeScriptDeclarations :: Proxy T8 -> [TSDeclaration] Source # getTypeScriptType :: Proxy T8 -> String Source # getTypeScriptKeyType :: Proxy T8 -> String Source # getTypeScriptOptional :: Proxy T8 -> Bool Source # |
Instances
TypeScript T9 Source # | |
Defined in Data.Aeson.TypeScript.Types getTypeScriptDeclarations :: Proxy T9 -> [TSDeclaration] Source # getTypeScriptType :: Proxy T9 -> String Source # getTypeScriptKeyType :: Proxy T9 -> String Source # getTypeScriptOptional :: Proxy T9 -> Bool Source # |
Instances
TypeScript T10 Source # | |
Defined in Data.Aeson.TypeScript.Types getTypeScriptDeclarations :: Proxy T10 -> [TSDeclaration] Source # getTypeScriptType :: Proxy T10 -> String Source # getTypeScriptKeyType :: Proxy T10 -> String Source # getTypeScriptOptional :: Proxy T10 -> Bool Source # |