| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Language.Haskell.To.Elm
Synopsis
- class HasElmType a where
- elmType :: Type v
- elmDefinition :: Maybe Definition
- class HasElmType a => HasElmDecoder value a where
- class HasElmType a => HasElmEncoder value a where
- newtype Options = Options {
- fieldLabelModifier :: String -> String
- defaultOptions :: Options
- deriveElmTypeDefinition :: forall a. (HasDatatypeInfo a, All2 HasElmType (Code a)) => Options -> Qualified -> Definition
- deriveElmJSONDecoder :: forall a. (HasDatatypeInfo a, HasElmType a, All2 (HasElmDecoder Value) (Code a)) => Options -> Options -> Qualified -> Definition
- deriveElmJSONEncoder :: forall a. (HasDatatypeInfo a, HasElmType a, All2 (HasElmEncoder Value) (Code a)) => Options -> Options -> Qualified -> Definition
- jsonDefinitions :: forall t. (HasElmEncoder Value t, HasElmDecoder Value t) => [Definition]
Classes
class HasElmType a where Source #
Represents that the corresponding Elm type for the Haskell type a is .elmType @a
Minimal complete definition
Methods
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
| HasElmType Bool Source # | |
Defined in Language.Haskell.To.Elm | |
| HasElmType Char Source # | |
Defined in Language.Haskell.To.Elm | |
| HasElmType Double Source # | |
Defined in Language.Haskell.To.Elm | |
| HasElmType Int Source # | |
Defined in Language.Haskell.To.Elm | |
| HasElmType Text Source # | |
Defined in Language.Haskell.To.Elm | |
| HasElmType UTCTime Source # | |
Defined in Language.Haskell.To.Elm | |
| HasElmType a => HasElmType [a] Source # | |
Defined in Language.Haskell.To.Elm | |
| HasElmType a => HasElmType (Maybe a) Source # | |
Defined in Language.Haskell.To.Elm | |
| (HasElmType a, HasElmType b) => HasElmType (a, b) Source # | |
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
Methods
elmDecoder :: Expression v Source #
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
| HasElmDecoder Text Text Source # | |
Defined in Language.Haskell.To.Elm | |
| HasElmDecoder Value Bool Source # | |
Defined in Language.Haskell.To.Elm | |
| HasElmDecoder Value Char Source # | |
Defined in Language.Haskell.To.Elm | |
| HasElmDecoder Value Double Source # | |
Defined in Language.Haskell.To.Elm | |
| HasElmDecoder Value Int Source # | |
Defined in Language.Haskell.To.Elm | |
| HasElmDecoder Value Text Source # | |
Defined in Language.Haskell.To.Elm | |
| HasElmDecoder Value UTCTime Source # | |
Defined in Language.Haskell.To.Elm | |
| HasElmDecoder Value a => HasElmDecoder Value [a] Source # | |
Defined in Language.Haskell.To.Elm | |
| HasElmDecoder Value a => HasElmDecoder Value (Maybe a) Source # | |
Defined in Language.Haskell.To.Elm | |
| (HasElmDecoder Value a, HasElmDecoder Value b) => HasElmDecoder Value (a, b) Source # | |
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
Methods
elmEncoder :: Expression v Source #
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
Derivers
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 the elmDefinition in a HasElmType instance:
instanceHasElmTypeMyType whereelmDefinition=Just$deriveElmTypeDefinition@MyTypedefaultOptions"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 the elmDecoderDefinition in a
instance:HasElmDecoder Value
instanceHasElmDecoderValueMyType whereelmDecoderDefinition= Just $deriveElmJSONDecoder@MyTypedefaultOptionsdefaultOptions"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 the elmEncoderDefinition in a 'HasElmEncoder instance:Value
instanceHasElmEncoderValueMyType whereelmEncoderDefinition=Just$deriveElmJSONEncoder@MyTypedefaultOptionsdefaultOptions"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
is a shorthand for creating a list of its
jsonDefinitions @MyTypeelmDefinition, , and
elmEncoderDefinition @Value.elmDecoderDefinition @Value