elminator-0.2.3.1: Generate ELM types/encoders/decoders from Haskell types.

Safe HaskellNone
LanguageHaskell2010

Elminator

Description

Generate Elm type definitions, encoders and decoders from Haskell data types.

Synopsis

Documentation

include :: ToHType a => Proxy a -> GenOption -> Builder Source #

Include the elm source for the Haskell type specified by the proxy argument. The second argument decides which components will be included and if the generated type will be polymorphic.

generateFor :: ElmVersion -> Options -> Maybe FilePath -> Builder -> Q Exp Source #

Return the generated Elm code in a template haskell splice and optionally write to a Elm source file at the same time. The second argument is the Options type from Aeson library. Use include calls to build the Builder value.

data ElmVersion Source #

Specify Elm version to generate code for

Constructors

Elm0p18 
Elm0p19 

data HType Source #

This type holds the type information we get from generics. Only the HExternal constructor is supposed to be used by the programmer to implement ToHType instances for entites that are predefined in Elm. A sample can be seen below.

Here, let `MyExtType a b` be a type which has the corresponding type, encoders and decoders predefined in Elm in a module named Lib. Here is how you can implement a ToHType instance for this type so that your other autogenerated types can have fields of type `MyExtType a b`.

instance (ToHType a, ToHType b) => ToHType (MyExtType a b) where
  toHType _ = do
    ha <- toHType (Proxy :: Proxy a)
    hb <- toHType (Proxy :: Proxy b)
    pure $
      HExternal
        (ExInfo
           (External, MyExtType)
           (Just (External, "encodeMyExtType"))
           (Just (External, "decodeMyExtType"))
           [ha, hb])

Constructors

HUDef UDefData 
HMaybe HType 
HList HType 
HPrimitive MData 
HRecursive MData 
HExternal (ExInfo HType) 
Instances
Show HType Source # 
Instance details

Defined in Elminator.Generics.Simple

Methods

showsPrec :: Int -> HType -> ShowS #

show :: HType -> String #

showList :: [HType] -> ShowS #

class ToHType f where Source #

Minimal complete definition

Nothing

Methods

toHType :: Proxy f -> HState HType Source #

toHType :: (ToHTArgs (ExtractTArgs f), Generic f, ToHType_ (Rep f)) => Proxy f -> HState HType Source #

Instances
ToHType () Source # 
Instance details

Defined in Elminator.Generics.Simple

Methods

toHType :: Proxy () -> HState HType Source #

Typeable a => ToHType a Source # 
Instance details

Defined in Elminator.Generics.Simple

Methods

toHType :: Proxy a -> HState HType Source #

ToHType Text Source # 
Instance details

Defined in Elminator.Generics.Simple

Methods

toHType :: Proxy Text -> HState HType Source #

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

Defined in Elminator.Generics.Simple

Methods

toHType :: Proxy [a] -> HState HType Source #

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

Defined in Elminator.Generics.Simple

Methods

toHType :: Proxy (Maybe a) -> HState HType Source #

(ToHType a, ToHType b) => ToHType (Either a b) Source # 
Instance details

Defined in Elminator.Generics.Simple

Methods

toHType :: Proxy (Either a b) -> HState HType Source #

(ToHType a1, ToHType a2) => ToHType (a1, a2) Source # 
Instance details

Defined in Elminator.Generics.Simple

Methods

toHType :: Proxy (a1, a2) -> HState HType Source #

(ToHType a1, ToHType a2, ToHType a3) => ToHType (a1, a2, a3) Source # 
Instance details

Defined in Elminator.Generics.Simple

Methods

toHType :: Proxy (a1, a2, a3) -> HState HType Source #

(ToHType a1, ToHType a2, ToHType a3, ToHType a4) => ToHType (a1, a2, a3, a4) Source # 
Instance details

Defined in Elminator.Generics.Simple

Methods

toHType :: Proxy (a1, a2, a3, a4) -> HState HType Source #

(ToHType a1, ToHType a2, ToHType a3, ToHType a4, ToHType a5) => ToHType (a1, a2, a3, a4, a5) Source # 
Instance details

Defined in Elminator.Generics.Simple

Methods

toHType :: Proxy (a1, a2, a3, a4, a5) -> HState HType Source #

(ToHType a1, ToHType a2, ToHType a3, ToHType a4, ToHType a5, ToHType a6) => ToHType (a1, a2, a3, a4, a5, a6) Source # 
Instance details

Defined in Elminator.Generics.Simple

Methods

toHType :: Proxy (a1, a2, a3, a4, a5, a6) -> HState HType Source #

(ToHType a1, ToHType a2, ToHType a3, ToHType a4, ToHType a5, ToHType a6, ToHType a7) => ToHType (a1, a2, a3, a4, a5, a6, a7) Source # 
Instance details

Defined in Elminator.Generics.Simple

Methods

toHType :: Proxy (a1, a2, a3, a4, a5, a6, a7) -> HState HType Source #

data ExInfo a Source #

Constructors

ExInfo 

Fields

Instances
Show a => Show (ExInfo a) Source # 
Instance details

Defined in Elminator.Generics.Simple

Methods

showsPrec :: Int -> ExInfo a -> ShowS #

show :: ExInfo a -> String #

showList :: [ExInfo a] -> ShowS #

type Builder = State GenConfig () Source #

data GenOption Source #

Decides which among type definiton, encoder and decoder will be included for a type. The poly config value decides wether the included type definition will be polymorphic.

Instances
Show GenOption Source # 
Instance details

Defined in Elminator.Lib

data PolyConfig Source #

Decides wether the type definition will be polymorphic.

Constructors

Mono 
Poly 
Instances
Show PolyConfig Source # 
Instance details

Defined in Elminator.Lib