| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Elm.Module
Description
Functions in this module are used to generate Elm modules. Note that the generated modules depend on the bartavelle/json-helpers package.
Synopsis
- data DefineElm = forall a.IsElmDefinition a => DefineElm (Proxy a)
- moduleHeader :: ElmVersion -> String -> String
- makeElmModuleWithVersion :: ElmVersion -> String -> [DefineElm] -> String
- makeElmModule :: String -> [DefineElm] -> String
- makeModuleContent :: [DefineElm] -> String
- makeModuleContentWithAlterations :: (ETypeDef -> ETypeDef) -> [DefineElm] -> String
- recAlterType :: (EType -> EType) -> ETypeDef -> ETypeDef
- newtypeAliases :: [String] -> ETypeDef -> ETypeDef
- defaultAlterations :: ETypeDef -> ETypeDef
- defaultTypeAlterations :: EType -> EType
Documentation
Existential quantification wrapper for lists of type definitions
Constructors
| forall a.IsElmDefinition a => DefineElm (Proxy a) |
moduleHeader :: ElmVersion -> String -> String Source #
The module header line for this version of Elm
makeElmModuleWithVersion Source #
Arguments
| :: ElmVersion | |
| -> String | Module name |
| -> [DefineElm] | List of definitions to be included in the module |
| -> String |
Creates an Elm module for the given version. This will use the default
type conversion rules (to -- convert Vector to List, HashMap a b
to List (a,b), etc.).
Arguments
| :: String | Module name |
| -> [DefineElm] | List of definitions to be included in the module |
| -> String |
Creates an Elm module. This will use the default type conversion rules (to
convert Vector to List, HashMap a b to List (a,b), etc.).
default to 0.19
makeModuleContent :: [DefineElm] -> String Source #
Generates the content of a module. You will be responsible for including the required Elm headers. This uses the default type conversion rules.
makeModuleContentWithAlterations :: (ETypeDef -> ETypeDef) -> [DefineElm] -> String Source #
Generates the content of a module, using custom type conversion rules.
recAlterType :: (EType -> EType) -> ETypeDef -> ETypeDef Source #
A helper function that will recursively traverse type definitions and let you convert types.
myAlteration : ETypeDef -> ETypeDef
myAlteration = recAlterType $ \t -> case t of
ETyCon (ETCon "Integer") -> ETyCon (ETCon "Int")
ETyCon (ETCon "Text") -> ETyCon (ETCon "String")
_ -> tnewtypeAliases :: [String] -> ETypeDef -> ETypeDef Source #
Given a list of type names, will newtype all the matching type
definitions.
defaultAlterations :: ETypeDef -> ETypeDef Source #
A default set of type conversion rules:
HashSet a,Set a-> ifais comparable, thenSet a, elseList aHashMap String v,Map String v->Dict String vHashMap k v,Map k v->List (k, v)Integer->IntText->StringVector->ListDouble->FloatTagged t v->v
defaultTypeAlterations :: EType -> EType Source #