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

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.To.Elm

Contents

Synopsis

Classes

class HasElmType a where Source #

Represents that the corresponding Elm type for the Haskell type a is elmType @a.

This class has a default instance for types that satisfy HasElmDefinition, which refers to the name of that definition.

Minimal complete definition

Nothing

Instances
HasElmType Bool Source # 
Instance details

Defined in Language.Haskell.To.Elm

Methods

elmType :: Type v Source #

HasElmType Char Source # 
Instance details

Defined in Language.Haskell.To.Elm

Methods

elmType :: Type v Source #

HasElmType Double Source # 
Instance details

Defined in Language.Haskell.To.Elm

Methods

elmType :: Type v Source #

HasElmType Int Source # 
Instance details

Defined in Language.Haskell.To.Elm

Methods

elmType :: Type v Source #

HasElmType Text Source # 
Instance details

Defined in Language.Haskell.To.Elm

Methods

elmType :: Type v Source #

HasElmType UTCTime Source # 
Instance details

Defined in Language.Haskell.To.Elm

Methods

elmType :: Type v Source #

HasElmType a => HasElmType [a] Source # 
Instance details

Defined in Language.Haskell.To.Elm

Methods

elmType :: Type v Source #

HasElmType a => HasElmType (Maybe a) Source # 
Instance details

Defined in Language.Haskell.To.Elm

Methods

elmType :: Type v Source #

(HasElmType a, HasElmType b) => HasElmType (a, b) Source # 
Instance details

Defined in Language.Haskell.To.Elm

Methods

elmType :: Type v Source #

class HasElmDefinition a where Source #

Represents that we can generate the definition for the Elm type that corresponds to a using elmDefinition @a.

See deriveElmTypeDefinition for a way to automatically derive elmDefinition.

class HasElmType a => HasElmDecoder value a where Source #

Represents that the Elm type that corresponds to a has a decoder from value, namely elmDecoder @value @a.

This class has a default instance for types that satisfy HasElmDecoderDefinition, which refers to the name of that definition.

Minimal complete definition

Nothing

class HasElmType a => HasElmEncoder value a where Source #

Represents that the Elm type that corresponds to a has an encoder into value, namely elmEncoder @value @a.

This class has a default instance for types that satisfy HasElmEncoderDefinition, which refers to the name of that definition.

Minimal complete definition

Nothing

Instances
HasElmEncoder Text Char Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Text Double Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Text Int Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Text Text Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Value Bool Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Value Char Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Value Double Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Value Int Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Value Text Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Value UTCTime Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Value a => HasElmEncoder Value [a] Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Value a => HasElmEncoder Value (Maybe a) Source # 
Instance details

Defined in Language.Haskell.To.Elm

(HasElmEncoder Value a, HasElmEncoder Value b) => HasElmEncoder Value (a, b) Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder a b => HasElmEncoder (Maybe a) (Maybe b) Source # 
Instance details

Defined in Language.Haskell.To.Elm

class HasElmDecoderDefinition value a where Source #

Represents that we can generate the Elm decoder definition from value for the Elm type that corresponds to a.

See deriveElmJSONDecoder for a way to automatically derive elmDecoderDefinition when value = Value.

class HasElmEncoderDefinition value a where Source #

Represents that we can generate the Elm encoder definition into value for the Elm type that corresponds to a.

See deriveElmJSONEncoder for a way to automatically derive elmEncoderDefinition when value = Value.

Derivers

newtype Options Source #

Elm code generation options

Constructors

Options 

Fields

deriveElmTypeDefinition :: forall a. (HasDatatypeInfo a, All2 HasElmType (Code a)) => Options -> Qualified -> Definition Source #

Automatically create an Elm definition given a Haskell type.

This is suitable for use as a HasElmDefinition instance:

instance HasElmDefinition MyType where
  elmDefinition =
    deriveElmTypeDefinition @MyType defaultOptions "Api.MyType.MyType"

deriveElmJSONDecoder :: forall a. (HasDatatypeInfo a, HasElmType a, All2 (HasElmDecoder Value) (Code a)) => Options -> Options -> Qualified -> Definition Source #

Automatically create an Elm JSON decoder definition given a Haskell type.

This is suitable for use as a HasElmDecoderDefinition Value instance:

instance HasElmDecoderDefinition Value MyType where
  elmDecoderDefinition =
    deriveElmJSONDecoder @MyType defaultOptions defaultOptions "Api.MyType.decoder"

Uses the given Options to match the JSON format of derived FromJSON and ToJSON instances.

deriveElmJSONEncoder :: forall a. (HasDatatypeInfo a, HasElmType a, All2 (HasElmEncoder Value) (Code a)) => Options -> Options -> Qualified -> Definition Source #

Automatically create an Elm JSON encoder definition given a Haskell type.

This is suitable for use as a HasElmEncoderDefinition Value instance:

instance HasElmEncoderDefinition Value MyType where
  elmEncoderDefinition =
    deriveElmJSONEncoder @MyType defaultOptions defaultOptions "Api.MyType.encoder"

Uses the given Options to match the JSON format of derived FromJSON and ToJSON instances.

jsonDefinitions :: forall t. (HasElmDefinition t, HasElmEncoderDefinition Value t, HasElmDecoderDefinition Value t) => [Definition] Source #

A shorthand for a list of the type definitions for jsonDefinitions @MyType is a shorthand for creating a list of its elmDefinition, elmEncoderDefinition @Value, and elmDecoderDefinition @Value.