Type-safety across .Net and TypeScript – Generating TypeScript classes

This is part 4 of how we generate types from our .Net backend to be used in our TypeScript client.

  1. Why do we even bother?
  2. Generating TypeScript constants from .Net constants
  3. Finding the types used in communication between the .Net backend and the TypeScript client
  4. Generating TypeScript classes from .Net types
  5. Generating Angular Services from .Net WebApi Controllers
  6. TypeScript-friendly JSON serialization of F# types
  7. Testing JSON serialization and deserialization
  8. Putting all the parts together

Be prepared, a lot of string operations ahead!

Some context

As you have seen in the last post, we already have all the types for which we need to generate TypeScript classes. So we “just” have to write some strings into a file with a .ts ending

Generating TypeScript classes from .Net types

I’ll show you the whole truth about our approach. So please bare with me that the code snippets get longer and longer. So in this post, I’ve split up the code into some fragments. Enjoy:

Let’s start with some opens. Because we need to handle some special cases, we need to open some of our product specific namespaces (Calitime.*):

module W2w.TypeWriter

open System
open System.Reflection
open System.Text.RegularExpressions
open Calitime
open Calitime.Projections.Timeline
open Microsoft.FSharp.Reflection

In F#, it is not possible to compare types with open generics directly, so we need a fake for classes that need a generic type parameter. We implement ISerializableToString because that is a generic type constraint for some of the classes we have:

// Fake to be used in generic type definitions that use a type that meets generic constraints (like Timeline<_,_>)
type Fake =
    { V : string }
    interface ISerializableToString with
        member _.ToSerializedString() = "fake"

Assembly mappings

We gather types from several .Net assemblies and we have some name conflicts between types from different namespaces. This is mainly because we have a mix of C# and F# code and some basic types with the same name are present in both worlds. So we need to split up the generated types into separated files. We use a simple heuristic that generates (more or less) a file per .Net assembly. Until now, we don’t have name conflicts inside of a single .Net assembly. The following code maps .Net assemblies names to TypeScript file names:

let private assemblyMappings =
    [
        "Core.ActivityTime", "ActivityTime"
        "Calitime.Core", "Core"
        "Calitime.Core.Modules", "Modules"
        "Calitime.Infrastructure", "Infrastructure"
        "Fundamentals", "Fundamentals"
        "Calitime.Api.Clients", "Clients"
        "Calitime.TimeRocket.FunctionsClient", "Functions"
    ]
    |> Map

Direct type replacements

We also need some mappings from .Net types to TypeScript types. Whenever a .Net type is found that is in this map, it is replaced:

let private typeReplacements =
    [
        "number", [ "Int32" ; "Double" ; "Decimal" ; "MinuteDuration" ]
        "boolean", [ "Boolean" ]
        "string", [ "Guid" ; "String" ; "LocalTime" ; "LocalDate"; "Date" ; "RelativeDateRange" ]
        "StringAlias<Workday>", [ "Workday" ]
        "StringAlias<UtcDateTime>", [ "EffectiveDateTime" ; "ApplicationDateTime" ; "EffectiveTickDateTime" ]
        "StringAlias<OffsetDateTime>", [ "OffsetDateTime" ]
        "NumberAlias<SimpleTime>", [ "Time" ]
        "any", [ "ContextStep" ; "Dictionary`2" ; "Object" ]
        "IWorkflowActionDefinition[]", [ "StepDefinition" ]
    ]
    |> List.collect (fun (replacement, values) -> values |> List.map (fun v -> v,replacement))
    |> Map

The StringAlias<_> and NumberAlias are just type aliases for string and number, but it makes it easier for us to understand the generated types. This is a fairly new idea, so it is not yet applied strictly. As you can see by the various kinds of times and dates, our product is obviously a time tracking tool 😉

Helpers

Then we need some small helper functions. The isOption function returns whether a property is an Option. The toSmallCamelCase function transforms CsharpStyle into typeScriptStyle. Note: the code was written before string interpolation was in F#. The getOnlyNameOfType function returns the non-generic part of a type name.

let private isOption (p:PropertyInfo) =
    p.PropertyType.IsGenericType &&
    p.PropertyType.GetGenericTypeDefinition() = typedefof<Option<_>>


let toSmallCamelCase (v : string) =
    match v with
    | "" -> ""
    | s -> sprintf "%s%s" (s.Substring(0, 1).ToLower()) (s.Substring(1))


/// returns the name of the type, if it is generic then the generic type arguments are left out
let getOnlyNameOfType (t : Type) =
    let i = t.Name.IndexOf('`')
    if i > 0 then t.Name.Substring(0, i) else t.Name

Replace type names

The getTypeName and replaceType functions are used to get the TypeScript compatible type name for a .Net type.

/// gets the name of a type and replaced generic type parameters in a TypeScript compatible way
let rec private getTypeName (sourceType : Type) =
    if (sourceType.IsGenericType) then
        let genericTypeReplacement = getOnlyNameOfType sourceType
        let genericTypeArgumentReplacements =
            sourceType.GetGenericArguments()
            |> Array.map (replaceType)
            |> String.concat ","
        sprintf "%s<%s>" genericTypeReplacement genericTypeArgumentReplacements
    else
        sourceType.Name

/// replaces a C#/F# type with a TypeScript "type"
and replaceType (sourceType : Type) =
    if sourceType.IsGenericParameter then // Foo<'a> -> Foo<A>
        if sourceType.Name.Length = 1 then sourceType.Name.ToUpper()
        else sourceType.Name
    elif sourceType.IsGenericType && sourceType.GetGenericTypeDefinition() = typedefof<Option<_>> then // Foo option -> Foo | null
        let nestedType = sourceType.GenericTypeArguments.[0]
        let replacement = typeReplacements |> Map.tryFind nestedType.Name
        let nestedTypeReplacement =
            match replacement with
            | Some t -> t
            | None -> getTypeName nestedType
        sprintf "%s | null" nestedTypeReplacement
    elif (sourceType.IsArray) then 
        let nestedType = sourceType.GetElementType() 
        let replacement = replaceType nestedType 
        sprintf "%s[]" replacement
    elif (sourceType.IsGenericType && sourceType.GetGenericTypeDefinition() = typedefof<List<_>>) // Foo list -> []
        || (sourceType.IsGenericType && sourceType.GetGenericTypeDefinition() = typedefof<System.Collections.Generic.IEnumerable<_>>) // IEnumerable<Foo> -> Foo[]
        || (sourceType.IsGenericType && sourceType.GetGenericTypeDefinition() = typedefof<System.Collections.Generic.IReadOnlyCollection<_>>) // ReadOnlyCollection<Foo> -> Foo[]
        || (sourceType.IsGenericType && sourceType.GetGenericTypeDefinition() = typedefof<System.Collections.Generic.IReadOnlyList<_>>) then // ReadOnlyList<Foo> -> Foo[]
        let nestedType = sourceType.GenericTypeArguments.[0]
        let replacement = replaceType nestedType
        sprintf "%s[]" replacement
    elif sourceType.IsGenericType && sourceType.GetGenericTypeDefinition() = typedefof<Nullable<_>> then // Nullable<Foo> -> Foo
        let nestedType = sourceType.GenericTypeArguments.[0]
        let replacement = replaceType nestedType
        sprintf "%s" replacement
    elif FSharpType.IsTuple sourceType then
        let elements =
            FSharpType.GetTupleElements sourceType
            |> Array.map replaceType
            |> String.concat ", "
        sprintf "[%s]" elements
    elif sourceType.IsGenericType && sourceType.GetGenericTypeDefinition() = typedefof<Timeline<Fake, Fake>> then // Timeline<A,B> -> ValueInRange<A,B>[]
        let a = sourceType.GenericTypeArguments.[0] |> replaceType
        let b = sourceType.GenericTypeArguments.[1] |> replaceType
        $"ValueInRange<{a},{b}>[]"
    else
        let replacement = typeReplacements |> Map.tryFind sourceType.Name

        match replacement with
        | Some t -> t
        | None -> sourceType |> getTypeName

Line 3: If it is a generic type, we replace the generic parts of the name to get Foo<A> from Foo<`a>. Otherwise we just use the name as it is.

Line 15: For generic type parameters we make sure that they start with a capital letter since F# uses small single letter generic type parameter names.

Line 18-25: Transform Option<T> to T | null. We also check whether there is a direct type replacement for the contained type.

Line 26-36: We replace all kinds of collections to arrays.

Line 37-40: Nullables are replaced with their nested type.

Line 41-46: Tuples are replaced with arrays. We just combine the replaced element types.

Line 47-50: A special case, you can ignore it. Since it is the only special case here, I didn’t add some abstraction to add custom handling from the outside.

Line 51-56: In all other cases (classes, structs, records) we look at whether there is a direct type replacement, otherwise we just use getTypeName function (see above).

Unions

We replace something like

type ActivityTimeFrame =
    | Duration of int<minutes>
    | FromTo of Time * Time

with

export type ActivityTimeFrame = {
    "Duration"?: number
    "FromTo"?: [NumberAlias<SimpleTime>, NumberAlias<SimpleTime>]
};

The following code takes care of this:

let private writeUnion (t : Type) =
    if t.IsSpecialName then // skip union case by itself
        ""
    else
        let cases = FSharpType.GetUnionCases(t)

        match cases with
        | [| single |] when single.Name = t.Name->
            let fields = single.GetFields()

            match fields with
            | [| propertyInfo |] ->
                let sourceType = propertyInfo.PropertyType
                let targetType = replaceType sourceType
                sprintf "export type %s = %s;" t.Name targetType
            | _ ->
                failwithf "cannot (yet) handle discriminated unions with multiple fields. Type = %s" t.FullName
        | _ ->
            let isEnum = cases |> Array.forall (fun case -> case.GetFields().Length = 0)

            if isEnum then
                cases
                |> Array.map (fun case -> sprintf @"""%s""" case.Name)
                |> String.concat " | "
                |> sprintf "export type %s = %s;" t.Name

            else
                let content =
                    cases
                    |> Array.map (fun case ->
                        let fields = case.GetFields()

                        match fields with
                        | [| field |] ->
                            sprintf @"""%s""?: %s" case.Name (field.PropertyType |> replaceType)
                        | _ ->
                            let parts =
                                fields
                                |> Array.map (fun field -> field.PropertyType |> replaceType)
                                |> String.concat ", "
                            sprintf @"""%s""?: [%s]" case.Name parts
                    )
                    |> String.concat "\r\n    "

                sprintf
                    @"export type %s = {
    %s
};"
                    (t |> getTypeName)
                    content

Line 2: I use t.IsSpecialName to identify a union case. These are found by the type reflector with have seen in the last post, but are not needed here.

Line 8-17: Single-case DUs that use the same name for the single case as for the DU itself are treated specially. These are always wrappers in our code and we don’t want the wrapper in TypeScript.

We get the field and write its replaced type into the TypeScript type definition.

Line 19: Another special case is simple enum DUs. If all cases of a DU have no fields, we treat it as a simple enum, like export type E = A | B.

Line 28-50: For “normal” DUs we write a type with optional properties for every case as shown at the beginning of this section. Tuples in the DU cases are replaced with arrays.

Records and classes

Classes and C# records are a bit trickier than records because we need to handle their interfaces. A note to myself: we are about to use records with interfaces, so we probably will need to use the class code for records as well.

let ripGenerics (name : string) =
    let start = name.IndexOf('<')
    let ungenericName = if start > 0 then
                            name.Substring(0, start)
                        else
                            name
    ungenericName.Replace("[", "").Replace("]", "")

let private writeClass (relevantAssemblies : Assembly[]) (ignoredTypes : Type list) (t : Type) =
    let propertyInfos =
        t.GetProperties(BindingFlags.Instance ||| BindingFlags.Public)
    let properties =
        propertyInfos
        |> Array.map (fun property ->
            sprintf
                "public %s: %s"
                (property.Name |> toSmallCamelCase)
                (property.PropertyType |> replaceType))
    let properties' = String.concat ",\r\n        " properties
    let name = (t |> getTypeName)

    let interfaces =
        t.GetInterfaces()
        |> Array.filter (fun i -> relevantAssemblies |> Array.contains i.Assembly)
        |> Array.filter (fun i -> not (ignoredTypes |> List.contains i))

    if (propertyInfos.Length = 1 && propertyInfos.[0].Name = "Value") && (interfaces.Length = 0 || interfaces |> Array.contains typeof<ISerializableToString>) then
            sprintf """export type %s = %s""" name (propertyInfos.[0].PropertyType |> replaceType)
    else
        if interfaces.Length > 0 then
            let interfaces' =
                interfaces
                |> Array.map getTypeName
                |> String.concat ", "

            sprintf
                """export class %s implements %s {
    constructor(
        %s) {
    }

    $type = %s.$typeName;
    public static $typeName = "%s";
}"""
                name
                interfaces'
                properties'
                (name |> ripGenerics)
                (name |> ripGenerics)
        else
            sprintf
                """export class %s {
    constructor(
        %s) {
    }
}"""
                name
                properties'

Line 1-7: ripGenerics removes the generic part in a type name.

Line 10-25: Get the properties.

Line 22-34: If the record or class implements any interfaces from the relevant assemblies that are not ignored, we add them to the type definition.

Line 27: Checks a special case for classes that are simple wrappers around a string or GUID. We then use the wrapped type instead.

Line 42: We add a special property $type that allows us to “pattern match” classes in TypeScript.

Interfaces

Interfaces are again straight forward. Get all the properties and transform them:

let private writeInterface (t : Type) =
    let properties =
        t.GetProperties(BindingFlags.Instance ||| BindingFlags.Public)
        |> Array.map (fun property ->
            sprintf
                "%s: %s"
                (property.Name |> toSmallCamelCase)
                (property.PropertyType |> replaceType))
        |> Array.toSeq
    let properties' = String.concat ",\r\n    " properties

    sprintf
        @"export interface %s {
    %s
    $type: string;
}"
        (t |> getTypeName)
        properties'

Some special wrappers

We have some special cases:

  • Wrapper classes around a GUID.
  • Wrapper class around a string identifier.
  • Wrapper around a number.
let private writeGuidIdentifier (t : Type) =
    sprintf
        @"export type %s = string"
        (t |> getTypeName)


let writeEnum (t : Type) =
    let names = Enum.GetNames(t)
    let values : int[] = downcast Enum.GetValues(t)

    let content =
        Array.zip names values
        |> Array.map (fun (n, v) -> sprintf "%s = %i" n v)
        |> String.concat ",\r\n    "

    sprintf
        @"export enum %s {
    %s
}"
        (t |> getTypeName)
        content


let writeIdentifier (t : Type) =
    let name = t |> getTypeName
    sprintf
        """export type %s = string"""
        name


let writeNumberValue (t : Type) =
    let name = t |> getTypeName
    sprintf
        """export type %s = number"""
        name

Putting the type writer together

The writeType function puts all of the above together to get a TypeScript type declaration from a .Net type:

let writeType (relevantAssemblies : Assembly[]) (ignoredTypes : Type list) (assemblyName : string) (t : Type) =
    printfn "writing type %s to %s" t.FullName assemblyName

    let t = if t.IsGenericType then t.GetGenericTypeDefinition() else t // replace Foo<string> -> Foo<'a>

    let x =
        if t.IsInterface then
            writeInterface t
        elif typeof<IDecimalValue>.IsAssignableFrom t || typeof<INumericIdentifier>.IsAssignableFrom t || typeof<IIntValue>.IsAssignableFrom t then
            writeNumberValue t
        elif FSharpType.IsUnion t then
            writeUnion t
        elif FSharpType.IsRecord t then
            writeRecord t
        elif t.IsClass then
            if typeof<IIdentifier>.IsAssignableFrom t then
                writeIdentifier t
            else
                writeClass relevantAssemblies ignoredTypes t
        elif t.IsValueType then
            if t.Name.EndsWith("Guid") then
                writeGuidIdentifier t
            elif t.IsEnum then
                writeEnum t
            elif typeof<IIdentifier>.IsAssignableFrom t then
                writeIdentifier t
            else
                writeClass relevantAssemblies ignoredTypes t
        else
            failwithf "cannot write type %s" t.FullName
    x

Line 4: We want to use the open generic type, not a specific one.

Line 6-30: we check what kind of type it is and call the corresponding handler function. As you can see, we have some special cases that we handle here. Especially IIdentifiers that have a very special meaning in our codebase because they are used in our permission system.

Creating the files with imports

Oh, you are still reading! Great, so the next part can’t scare you off then 😉

In this section, we create the .ts files with the needed imports. That’s really ugly, so feel free to skip to the next section.

let mapAssembly assemblyName =
    assemblyMappings
    |> Map.tryFind assemblyName
    |> Option.defaultValue "Infrastructure" //needed for additional types that we want to include

/// the types per assembly/file that should be ignored in the import list because there are two types with the same name.
let typesToBeIgnoredInImports =
    [
        "ActivityTime",
        [
            "Infrastructure", [ "StartAndEndRange" ; "Time"  ; "Workday" ]
            "Modules", [ "ForeAndFamilyName" ; "SimpleEmployeeName" ]
        ] |> Map
    ]
    |> Map

/// creates the import for one file (`forAssembly`)
/// the included types = all types from imported assembly - types not used in the importing file
let getTypeImports (forAssembly : string) (fromAssembly : string) (allTypes : Type seq) (types : string) =
    let typesToBeIgnored =
        typesToBeIgnoredInImports
        |> Map.tryFind forAssembly
        |> Option.map (fun map -> map |> Map.tryFind fromAssembly)
        |> Option.flatten
        |> Option.defaultValue []

    allTypes
    |> Seq.filter (fun t -> t.Assembly.GetName().Name |> mapAssembly = fromAssembly)
    |> Seq.map (fun t -> $"""{getOnlyNameOfType t }""")
    |> Seq.filter (fun t -> not(typesToBeIgnored |> List.contains t)) // ignore types that are defined twice (different assemblies)
    |> Seq.filter (fun t -> // remove all types from the import that are not used in the file
        let regex = Regex($@"\W{t}\W")
        regex.Match(types).Success
        )
    |> Seq.distinct
    |> String.concat ", "


let writeAssembly
    (relevantAssemblies : Assembly[])
    (ignoredTypes : Type list)
    (assemblyName : string)
    (typesOfAssembly : Type seq)
    (allTypes : Type seq)
    =
    let types' =
        typesOfAssembly
        |> Seq.map (writeType relevantAssemblies ignoredTypes assemblyName)
        |> String.concat "\r\n\r\n"

    let imports =
         match assemblyName with
         | "Core" ->
             let infrastructureImports = getTypeImports assemblyName "Infrastructure" allTypes types'
             let modulesImports = getTypeImports assemblyName "Modules" allTypes types'
             $"""import {{ Maybe, StringAlias, NumberAlias, {infrastructureImports} }} from "root/generated/Infrastructure.types";
import {{ {modulesImports} }} from "root/generated/Modules.types";
import {{ UtcDateTime }} from "root/rootShared/time/utcdatetime";
import {{ OffsetDateTime }} from "root/rootShared/time/offsetdatetime";
import {{ SimpleTime }} from "root/rootShared/time/simpletime";
import {{ StartAndEndRange }} from "root/rootShared/time/range";
import {{ Workday }} from "root/rootShared/time/workday";"""

         | "Modules" ->
             let infrastructureImports = getTypeImports assemblyName "Infrastructure" allTypes types'
             $"""import {{ Maybe, StringAlias, NumberAlias, {infrastructureImports} }} from "root/generated/Infrastructure.types";
import {{ OffsetDateTime }} from "root/rootShared/time/offsetdatetime";
import {{ UtcDateTime }} from "root/rootShared/time/utcdatetime";
import {{ SimpleTime }} from "root/rootShared/time/simpletime";
import {{ StartAndEndRange }} from "root/rootShared/time/range";
import {{ Workday }} from "root/rootShared/time/workday";"""

         | "ActivityTime" ->
             let infrastructureImports = getTypeImports assemblyName "Infrastructure" allTypes types'
             let modulesImports = getTypeImports assemblyName "Modules" allTypes types'
             let fundamentalsImports = getTypeImports assemblyName "Fundamentals" allTypes types'
             let coreImports = getTypeImports assemblyName "Core" allTypes types'
             $"""import {{ Maybe, StringAlias, NumberAlias, {infrastructureImports} }} from "root/generated/Infrastructure.types";
import {{ {modulesImports} }} from "root/generated/Modules.types";
import {{ {fundamentalsImports} }} from "root/generated/Fundamentals.types";
import {{ {coreImports} }} from "root/generated/Core.types";
import {{ SimpleTime }} from "root/rootShared/time/simpletime";
import {{ UtcDateTime }} from "root/rootShared/time/utcdatetime";"""

         | "Clients" | "Functions" ->
             let infrastructureImports = getTypeImports assemblyName "Infrastructure" allTypes types'
             let modulesImports = getTypeImports assemblyName "Modules" allTypes types'
             let coreImports = getTypeImports assemblyName "Core" allTypes types'
             $"""import {{ Maybe, StringAlias, NumberAlias, {infrastructureImports} }} from "root/generated/Infrastructure.types";
import {{ {modulesImports} }} from "root/generated/Modules.types";
import {{ {coreImports} }} from "root/generated/Core.types";
import {{ UtcDateTime }} from "root/rootShared/time/utcdatetime";
import {{ OffsetDateTime }} from "root/rootShared/time/offsetdatetime";
import {{ SimpleTime }} from "root/rootShared/time/simpletime";
import {{ StartAndEndRange }} from "root/rootShared/time/range";
import {{ Workday }} from "root/rootShared/time/workday";"""

         | "Fundamentals" ->
             """"""

         | "Infrastructure" ->
             """import { SimpleDateTime } from "root/rootShared/time/simpledatetime";
import { OffsetDateTime } from "root/rootShared/time/offsetdatetime";
import { SimpleTime } from "root/rootShared/time/simpletime";
import { StartAndEndRange } from "root/rootShared/time/range";
import { Workday } from "root/rootShared/time/workday";

export type StringAlias<T> = string
export type NumberAlias<T> = number

export class Maybe<T> {
    constructor(
        public hasValue: boolean,
        public value: T) { }

    public static Some<T>(value: T) : Maybe<T> {
        return new Maybe<T>(
            true,
            value);
    }

    public static None<T>() : Maybe<T> {
        return new Maybe<T>(
            false,
            null);
    }

    public static Create<T>(value: T) : Maybe<T> {
        return value
         ? Maybe.Some<T>(value)
         : Maybe.None<T>();
    }

    public map<T2>(f: (x: T) => T2) : Maybe<T2> {
      if(this.hasValue)
      {
         return Maybe.Some<T2>(
            f(this.value));
      }

      return Maybe.None<T2>();
   }

   public getValueOr(defaultValue: T) : T {
      if(this.hasValue)
      {
         return this.value;
      }

      return defaultValue;
   }
}
"""
         | _ -> ""

    sprintf
        @"%s

%s"
        imports
        types'

Line 1: A helper function to get the file a type has to be written to depending on the assembly it is defined in.

Line 7-15: A map of all the types that we don’t want to include in the imports. The reason for this is that these are types that are present both in C# and F#. With this we can configure, what types is used where.

Line 19-36: This puts together the import statements. They are constructed by checking all types needed to get a compiling file – import all types used by the types defined in the file – yeah a Regex.

Line 39-161: writeAssembly writes a single TypeScript file containing some of our types.

Line 46-49: Get the string representation of the TypeScript types for the .Net types that go into this file.

Line 51-154: Generate the import statements. As you can see, we use a lot of hard coding to get the import statements we need. For every file we write, we include the files that this file depends on, as well as some types that are defined in the TypeScript code of our client. Finally, we add some basic types like Maybe<_>. Yeah, not nice, but it works.

Line 156-161: Put the whole content of the file into a single string and return it.

Writing all the type declaration files

Finally, the writeTypes function groups the types by assemblies/files and gets the content and returns an anonymous record to its caller.

let writeTypes (relevantAssemblies : Assembly[]) (ignoredTypes : Type list) (types : Type list) =
    types
    |> List.groupBy (fun t ->
        t.Assembly.GetName().Name |> mapAssembly)
    |> List.map (fun (assemblyName, typesOfAssembly) ->
        let types' = writeAssembly relevantAssemblies ignoredTypes assemblyName typesOfAssembly types

        {|
           Assembly = assemblyName
           Types = types'
        |})

Still here? My respect!

See you then in the next post about generating Angular services for our Web controllers. It will be easier, promised – at least a bit 😀

This blog post is made possible with the support of Time Rocket, the product this blog post is about. Take a look (German only).

About the author

Urs Enzler

4 comments

By Urs Enzler

Recent Posts