| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Elminator
Description
Generate Elm type definitions, encoders and decoders from Haskell data types.
{-#Language ScopedTypeVariables#-}
{-#Language FlexibleInstances#-}
{-#Language DeriveAnyClass#-}
{-#Language OverloadedStrings#-}
module Lib where
import Elminator
import GHC.Generics
data SingleCon = SingleCon (Maybe Int) String deriving (Generic, ToHType)
data WithMaybesPoly a b =
WithMaybesPoly
{ mbpF1 :: Maybe a
, mbpF2 :: Maybe b
}
deriving (Generic, ToHType)
Here is how we generate Elm source for the above defined types.
{-#Language OverloadedStrings#-}
{-#Language TemplateHaskell#-}
module CodeGen where
import Data.Proxy
import Elminator
import Data.Text
import Lib
elmSource :: Text
elmSource = $(generateFor Elm19 myDefaultOptions (Just "./elm-app/src/Autogen.elm") $ do
include (Proxy :: Proxy SingleCon) $ Everything Mono
include (Proxy :: Proxy (WithMaybesPoly (Maybe String) Float)) $ Definiton Poly
Synopsis
- include :: ToHType a => Proxy a -> GenOption -> Builder
- generateFor :: ElmVersion -> Options -> Maybe FilePath -> Builder -> Q Exp
- data ElmVersion = Elm19
- data HType
- = HUDef UDefData
- | HMaybe HType
- | HList HType
- | HPrimitive MData
- | HRecursive MData
- | HExternal ExInfo [HType]
- class ToHType f where
- data ExItem = ExItem {
- extModuleName :: Text
- extSymbol :: Text
- data ExInfo = ExInfo {}
- type Builder = State GenConfig ()
- data GenOption
- data PolyConfig
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 #
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 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
(ExItem "Lib" "MyExtType")
(Just $ ExItem "Lib" "encodeMyExtType")
(Just $ ExItem "Lib" "decodeMyExtType"))
[ha, hb]
Constructors
| HUDef UDefData | |
| HMaybe HType | |
| HList HType | |
| HPrimitive MData | |
| HRecursive MData | |
| HExternal ExInfo [HType] |
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 Bool Source # | |
| ToHType Char Source # | |
| ToHType Float Source # | |
| ToHType Int Source # | |
| ToHType () Source # | |
| ToHType a => ToHType [a] Source # | |
| ToHType a => ToHType (Maybe a) Source # | |
| (ToHType a, ToHType b) => ToHType (Either a b) Source # | |
| (ToHType a1, ToHType a2) => ToHType (a1, a2) Source # | |
| (ToHType a1, ToHType a2, ToHType a3) => ToHType (a1, a2, a3) Source # | |
| (ToHType a1, ToHType a2, ToHType a3, ToHType a4) => ToHType (a1, a2, a3, a4) Source # | |
| (ToHType a1, ToHType a2, ToHType a3, ToHType a4, ToHType a5) => ToHType (a1, a2, a3, a4, a5) Source # | |
| (ToHType a1, ToHType a2, ToHType a3, ToHType a4, ToHType a5, ToHType a6) => ToHType (a1, a2, a3, a4, a5, a6) Source # | |
| (ToHType a1, ToHType a2, ToHType a3, ToHType a4, ToHType a5, ToHType a6, ToHType a7) => ToHType (a1, a2, a3, a4, a5, a6, a7) Source # | |
Constructors
| ExItem | |
Fields
| |
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.
Constructors
| Definiton PolyConfig | |
| EncoderDecoder | |
| Everything PolyConfig |
data PolyConfig Source #
Decides wether the type definition will be polymorphic.
Instances
| Show PolyConfig Source # | |
Defined in Elminator.Lib Methods showsPrec :: Int -> PolyConfig -> ShowS # show :: PolyConfig -> String # showList :: [PolyConfig] -> ShowS # | |