haskell-to-elm: Generate Elm types and JSON encoders and decoders from Haskell types

[ bsd3, compiler, elm, language, library ] [ Propose Tags ]

Please see the README on GitHub at https://github.com/folq/haskell-to-elm#readme


[Skip to Readme]

Modules

[Index] [Quick Jump]

Flags

Manual Flags

NameDescriptionDefault
examples

Build examples

Disabled

Use -f <flag> to enable a flag, or -f -<flag> to disable that flag. More info

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.1.0.1, 0.2.0.0, 0.2.1.0, 0.3.0.0, 0.3.1.0, 0.3.2.0
Change log CHANGELOG.md
Dependencies aeson (>=1.4.0), base (>=4.7 && <5), bound (>=2.0.0), elm-syntax (>=0.1.0 && <0.1.1), generics-sop (>=0.4.0 && <0.5.0), haskell-to-elm, protolude (>=0.2.3), text (>=1.2.0), time (>=1.8.0), unordered-containers (>=0.2.8) [details]
License BSD-3-Clause
Copyright 2019 Olle Fredriksson
Author Olle Fredriksson
Maintainer fredriksson.olle@gmail.com
Category Elm, Compiler, Language
Home page https://github.com/folq/haskell-to-elm#readme
Bug tracker https://github.com/folq/haskell-to-elm/issues
Source repo head: git clone https://github.com/folq/haskell-to-elm
Uploaded by OlleFredriksson at 2019-12-20T10:06:05Z
Distributions
Reverse Dependencies 1 direct, 0 indirect [details]
Executables user-example
Downloads 2177 total (26 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2019-12-20 [all 1 reports]

Readme for haskell-to-elm-0.2.0.0

[back to package description]

haskell-to-elm Hackage

haskell-to-elm is a library that takes Haskell type definitions as input and generates matching Elm type definitions and JSON encoders and decoders that match Aeson's format.

The problem

Let's say we're building a web page with a Haskell backend and an Elm frontend.

We might have a Haskell type like this, that we pass to the frontend encoded as JSON. The JSON encoder is derived using the Aeson library.

data User = User
  { name :: Text
  , age :: Int
  } deriving (Generic, ToJSON)

We mirror the type on the Elm side and add a JSON decoder as follows:

type alias User =
    { name : String
    , age : Int
    }

decoder : Decoder User
decoder =
    Decode.map2 User
        (Decode.field "name" Decode.string)
        (Decode.field "age" Decode.int)

Now, let's say we want to change a field in the backend:

-- Haskell
data User = User
  { name :: Text
--, age :: Int
  , birthday :: Date -- <---- new!
  } deriving (Generic, ToJSON)

If we now run the application again, but forget to update the Elm code, the User decoder will fail at runtime in Elm.

The solution

haskell-to-elm solves this problem by letting us generate the Elm User type and decoder from the Haskell User type.

With haskell-to-elm as part of your build pipeline you can make sure that the frontend is always in sync with your backend, and get type errors in your frontend code when you change your backend types.

The companion library servant-to-elm also lets you generate Elm client libraries for your Servant APIs.

Basic usage

To generate code for the User type above, we first need to derive a bunch of class instances:

data User = User
  { name :: Text
  , age :: Int
  } deriving (Generic, Aeson.ToJSON, SOP.Generic, SOP.HasDatatypeInfo)

instance HasElmType User where
  elmDefinition =
    Just $ deriveElmTypeDefinition @User defaultOptions "Api.User.User"

instance HasElmDecoder Aeson.Value User where
  elmDecoderDefinition =
    Just $ deriveElmJSONDecoder @User defaultOptions Aeson.defaultOptions "Api.User.decoder"

instance HasElmEncoder Aeson.Value User where
  elmEncoderDefinition =
    Just $ deriveElmJSONEncoder @User defaultOptions Aeson.defaultOptions "Api.User.encoder"

Then we can print the generated Elm code using the following code:

main :: IO ()
main = do
  let
    definitions =
      jsonDefinitions @User

    modules =
      Pretty.modules definitions

  forM_ (HashMap.toList modules) $ \(_moduleName, contents) ->
    print contents

Running main will print the following Elm code:

module Api.User exposing (..)

import Json.Decode
import Json.Decode.Pipeline
import Json.Encode


type alias User =
    { name : String, age : Int }


encoder : User -> Json.Encode.Value
encoder a =
    Json.Encode.object [ ("name" , Json.Encode.string a.name)
    , ("age" , Json.Encode.int a.age) ]


decoder : Json.Decode.Decoder User
decoder =
    Json.Decode.succeed User |>
    Json.Decode.Pipeline.required "name" Json.Decode.string |>
    Json.Decode.Pipeline.required "age" Json.Decode.int

In an actual project we would be writing the code to disk instead of printing it.

See this file for the full code with imports.

Roadmap

  • Derive JSON encoders and generically
    • Support all Aeson options
  • Pretty-print the Elm AST
    • Separate pretty printing from code generation: elm-syntax
  • Generate Elm modules
  • Servant client library generation: servant-to-elm
  • Test that encoding and decoding round-trip: elm-to-haskell-test

Libraries that use or are used by haskell-to-elm:

  • elm-syntax defines Haskell ASTs for Elm's syntax, and lets us pretty-print it.
  • servant-to-elm can be used to generate Elm client libraries from Servant APIs.
  • haskell-to-elm-test does end-to-end testing of this library.

Others: