json-spec-elm-0.4.0.1: Elm code generate for `json-spec`.
Safe HaskellNone
LanguageHaskell2010

Data.JsonSpec.Elm

Description

This module provide a way to generate Elm types, encoders, and decoders for json-spec Specifications

Generally you will probably want elmDefs, but sometimes you might want to directly use the methods of HasType.

Since not every part of a Specification may have a name, we can generate encoders and decoders for anonymous Elm types like records, as well as named Elm types and type aliases. This package figures out how to name things given the following rules:

  • If a name appears in a JsonLet binding, then it gets a name in Elm as a type or type alias.
  • If a second JsonLet binding, with exactly one definition, of the form JsonLet '[ '(name, def) ] (JsonRef name) appears as the RHS of a JsonLetbinding, then that is interpreted as a constructor name, and the generated Elm definition will be a regular type instead of a type alias. See Named for an easy shorthand way to spell JsonLet '[ '(name, def) ] (JsonRef name)
  • For any Named leaf of a tree of JsonEithers, the name is interpreted as a data constructor name, otherwise a data constructor name is auto-generated.

Examples:

Type alias

The specification

Named "MyType" JsonString

will produce the Elm type

type alias MyType = String

Type with a constructor

The specification

Named "MyType" (Named "MyDataConstructor" JsonString)

will produce the Elm type

type MyType = MyDataConstructor String

Sum Type

Note that the root of a tree of JsonEithers must be named, because Elm has no way to represent anonymous sum types.

The specification

Named "MySumType"
  ( JsonEither
      (Named "AnInt" JsonInt)
      ( JsonEither
          JsonFloat -- note the omitted name
          ( Named "AString" JsonString)
      )
  )

will produce the Elm type

type MySumType
  = AnInt Int
  | MySumType_2 Float -- auto-generated constructor name.
  | AString String

Producing actual Elm code

This package gets you as far as having a collection of Definitions in hand, which come from the 'elm-syntax' package. You will need to use the pretty printing features of that package to actually produce code. See https://hackage.haskell.org/package/elm-syntax/docs/Language-Elm-Pretty.html, or you can look at the source code for the tests in this package.

Synopsis

Documentation

elmDefs :: forall (spec :: Specification). HasType spec => Proxy spec -> Set Definition Source #

Generate Elm type, encoder, and decoder Definitions for all named types in a Specification. Note that this will not produce any types, decoders, or encoders for anonymous parts of the Specification, since we wouldn't know what to names to give those things in Elm.

class HasType (spec :: Specification) where Source #

Translates Specifications into "anonymous" Elm types (where "anonymous" really means the RHS of a definition, which could be truly anonymous but might in fact be a reference to something previously named Definition).

Methods

typeOf :: Definitions (Type v) Source #

Produce the anonymous Elm type for the spec, collecting any necessary Definitions along the way.

decoderOf :: Definitions (Expression Void) Source #

Produce the Elm Decode for the spec, collecting any necessary Definitions along the way

encoderOf :: Definitions (Expression Void) Source #

Produce the Elm Encoder for the spec, collecting any necessary Definitions along the way.

Instances

Instances details
HasType 'JsonBool Source # 
Instance details

Defined in Data.JsonSpec.Elm

HasType 'JsonDateTime Source # 
Instance details

Defined in Data.JsonSpec.Elm

HasType 'JsonInt Source # 
Instance details

Defined in Data.JsonSpec.Elm

HasType 'JsonNum Source # 
Instance details

Defined in Data.JsonSpec.Elm

HasType 'JsonString Source # 
Instance details

Defined in Data.JsonSpec.Elm

HasType spec => HasType ('JsonArray spec) Source # 
Instance details

Defined in Data.JsonSpec.Elm

HasType spec => HasType ('JsonNullable spec) Source # 
Instance details

Defined in Data.JsonSpec.Elm

Record fields => HasType ('JsonObject fields) Source # 
Instance details

Defined in Data.JsonSpec.Elm

KnownSymbol name => HasType ('JsonRef name) Source # 
Instance details

Defined in Data.JsonSpec.Elm

KnownSymbol const => HasType ('JsonTag const) Source # 
Instance details

Defined in Data.JsonSpec.Elm

(TypeError AnonSumTypeError :: Constraint) => HasType ('JsonEither left right) Source # 
Instance details

Defined in Data.JsonSpec.Elm

(HasDef def, HasType ('JsonLet more spec)) => HasType ('JsonLet (def ': more) spec) Source # 
Instance details

Defined in Data.JsonSpec.Elm

HasType spec => HasType ('JsonLet ('[] :: [(Symbol, Specification)]) spec) Source # 
Instance details

Defined in Data.JsonSpec.Elm

type Named (name :: Symbol) (def :: Specification) = 'JsonLet '['(name, def)] ('JsonRef name) Source #

Helper for giving a specification a name. This is especially useful for making sure sum type data constructors have meaningful names.