haskell-to-elm-0.3.2.0: Generate Elm types and JSON encoders and decoders from Haskell types
Safe HaskellNone
LanguageHaskell2010

Language.Haskell.To.Elm

Synopsis

Classes

class HasElmType a where Source #

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

Minimal complete definition

elmType | elmDefinition

Methods

elmType :: Type v Source #

default elmType :: Type v Source #

elmDefinition :: Maybe Definition Source #

When Just, this 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.

When Nothing, it means that the type is an already existing Elm type that does not need to be generated.

Instances

Instances details
HasElmType Bool Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmType Char Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmType Double Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmType Float Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmType Int Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmType Int8 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmType Int16 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmType Int32 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmType Word8 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmType Word16 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmType Word32 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmType Text Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmType UTCTime Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmType a => HasElmType ([a] :: Type) Source # 
Instance details

Defined in Language.Haskell.To.Elm

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

Defined in Language.Haskell.To.Elm

HasElmType a => HasElmType (Vector a :: Type) Source # 
Instance details

Defined in Language.Haskell.To.Elm

KnownNat n => HasElmType (Parameter n :: Type) Source # 
Instance details

Defined in Language.Haskell.To.Elm

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

Defined in Language.Haskell.To.Elm

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.

Minimal complete definition

elmDecoder | elmDecoderDefinition

Methods

elmDecoder :: Expression v Source #

elmDecoderDefinition :: Maybe Definition Source #

When Just, this 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.

Instances

Instances details
KnownNat n => HasElmDecoder (value :: k) (Parameter n :: Type) Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmDecoder Text Text Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmDecoder Value Bool Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmDecoder Value Char Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmDecoder Value Double Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmDecoder Value Float Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmDecoder Value Int Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmDecoder Value Int8 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmDecoder Value Int16 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmDecoder Value Int32 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmDecoder Value Word8 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmDecoder Value Word16 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmDecoder Value Word32 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmDecoder Value Text Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmDecoder Value UTCTime Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmDecoder Value a => HasElmDecoder Value ([a] :: Type) Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmDecoder Value a => HasElmDecoder Value (Maybe a :: Type) Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmDecoder Value a => HasElmDecoder Value (Vector a :: Type) Source # 
Instance details

Defined in Language.Haskell.To.Elm

(HasElmDecoder Value a, HasElmDecoder Value b) => HasElmDecoder Value ((a, b) :: Type) Source # 
Instance details

Defined in Language.Haskell.To.Elm

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

elmEncoder | elmEncoderDefinition

Methods

elmEncoder :: Expression v Source #

elmEncoderDefinition :: Maybe Definition Source #

When Just, this 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.

Instances

Instances details
KnownNat n => HasElmEncoder (value :: k) (Parameter n :: Type) Source # 
Instance details

Defined in Language.Haskell.To.Elm

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 Float Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Text Int Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Text Int8 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Text Int16 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Text Int32 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Text Word8 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Text Word16 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Text Word32 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 Float Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Value Int Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Value Int8 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Value Int16 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Value Int32 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Value Word8 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Value Word16 Source # 
Instance details

Defined in Language.Haskell.To.Elm

HasElmEncoder Value Word32 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] :: Type) Source # 
Instance details

Defined in Language.Haskell.To.Elm

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

Defined in Language.Haskell.To.Elm

HasElmEncoder Value a => HasElmEncoder Value (Vector a :: Type) Source # 
Instance details

Defined in Language.Haskell.To.Elm

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

Defined in Language.Haskell.To.Elm

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

Defined in Language.Haskell.To.Elm

Derivers

newtype Options Source #

Elm code generation options

Constructors

Options 

Fields

Type definitions

deriveElmTypeDefinition :: forall a. DeriveParameterisedElmTypeDefinition 0 a => Options -> Qualified -> Definition Source #

Automatically create an Elm definition given a Haskell type.

This is suitable for use as the elmDefinition in a HasElmType instance:

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

data Parameter (n :: Nat) Source #

Instances

Instances details
KnownNat n => HasElmEncoder (value :: k) (Parameter n :: Type) Source # 
Instance details

Defined in Language.Haskell.To.Elm

KnownNat n => HasElmDecoder (value :: k) (Parameter n :: Type) Source # 
Instance details

Defined in Language.Haskell.To.Elm

KnownNat n => HasElmType (Parameter n :: Type) Source # 
Instance details

Defined in Language.Haskell.To.Elm

JSON decoders

deriveElmJSONDecoder :: forall a. DeriveParameterisedElmDecoderDefinition 0 Value a => Options -> Options -> Qualified -> Definition Source #

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

This is suitable for use as the elmDecoderDefinition in a HasElmDecoder Value instance:

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

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

JSON encoders

deriveElmJSONEncoder :: forall a. DeriveParameterisedElmEncoderDefinition 0 Value a => Options -> Options -> Qualified -> Definition Source #

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

This is suitable for use as the elmEncoderDefinition in a 'HasElmEncoder Value instance:

instance HasElmEncoder Value MyType where
  elmEncoderDefinition =
    Just $ 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. (HasElmEncoder Value t, HasElmDecoder 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.