elm-bridge: Derive Elm types from Haskell types

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

Building the bridge from Haskell to Elm and back. Define types once, use on both sides and enjoy easy (de)serialisation. Cheers!


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.2.1.0, 0.2.1.1, 0.2.2.0, 0.2.2.1, 0.3.0.0, 0.3.0.2, 0.4.0, 0.4.1, 0.4.2, 0.4.3, 0.5.0, 0.5.1, 0.5.2, 0.6.0, 0.6.1, 0.7.0, 0.8.0, 0.8.1, 0.8.2, 0.8.3
Change log CHANGELOG.md
Dependencies aeson (>=0.9), base (>=4.7 && <5), template-haskell [details]
License BSD-3-Clause
Copyright (c) 2015 - 2016 Alexander Thiemann and contributors
Author Alexander Thiemann <mail@athiemann.net>, Simon Marechal <bartavelle@gmail.com>
Maintainer Alexander Thiemann <mail@athiemann.net>
Category Web, Compiler, Language
Home page https://github.com/agrafix/elm-bridge
Source repo head: git clone https://github.com/agrafix/elm-bridge
Uploaded by AlexanderThiemann at 2016-05-27T15:51:47Z
Distributions LTSHaskell:0.8.3, NixOS:0.8.3
Reverse Dependencies 2 direct, 0 indirect [details]
Downloads 11191 total (56 in the last 30 days)
Rating 2.0 (votes: 1) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2016-05-27 [all 1 reports]

Readme for elm-bridge-0.3.0.2

[back to package description]

Elm Bridge

Build Status

Hackage Deps

Intro

Hackage: elm-bridge

Building the bridge from Haskell to Elm and back. Define types once, use on both sides and enjoy easy (de)serialisation. Cheers!

Note that the bartavelle/json-helpers package, with version >= 1.1.0, is expected by the generated Elm modules.

Usage

{-# LANGUAGE TemplateHaskell #-}
import Elm.Derive
import Elm.Module

import Data.Proxy

data Foo
   = Foo
   { f_name :: String
   , f_blablub :: Int
   } deriving (Show, Eq)

deriveBoth defaultOptions ''Foo

main :: IO ()
main =
    putStrLn $ makeElmModule "Foo"
    [ DefineElm (Proxy :: Proxy Foo)
    ]

Output will be:

module Foo where

import Json.Decode
import Json.Decode exposing ((:=))
import Json.Encode
import Json.Helpers exposing (..)


type alias Foo  =
   { f_name: String
   , f_blablub: Int
   }

jsonDecFoo : Json.Decode.Decoder ( Foo )
jsonDecFoo =
   ("f_name" := Json.Decode.string) `Json.Decode.andThen` \pf_name ->
   ("f_blablub" := Json.Decode.int) `Json.Decode.andThen` \pf_blablub ->
   Json.Decode.succeed {f_name = pf_name, f_blablub = pf_blablub}

jsonEncFoo : Foo -> Value
jsonEncFoo  val =
   Json.Encode.object
   [ ("f_name", Json.Encode.string val.f_name)
   , ("f_blablub", Json.Encode.int val.f_blablub)
   ]

For more usage examples check the tests or the examples dir.

Install

Haskell

  • Using cabal: cabal install elm-bridge
  • From Source: git clone https://github.com/agrafix/elm-bridge.git && cd elm-bridge && cabal install

Elm

  • elm package install bartavelle/json-helpers

Contribute

Pull requests are welcome! Please consider creating an issue beforehand, so we can discuss what you would like to do. Code should be written in a consistent style throughout the project. Avoid whitespace that is sensible to conflicts. (E.g. alignment of = signs in functions definitions) Note that by sending a pull request you agree that your contribution can be released under the BSD3 License as part of the elm-bridge package or related packages.