elmental-0.1.0.2: Generate Elm datatype definitions, encoders and decoders from Haskell datatypes.
Safe HaskellSafe-Inferred
LanguageGHC2021

Elmental

Synopsis

Documentation

class ElmKind (KindOf x) => ElmDeclarable x where Source #

Class mapping a Haskell type constructor x :: k to an Elm type constructor.

You can define instances for this class for any Haskell data / newtype constructor, be it unapplied, partially applied or fully applied, provided that its kind is not Elm-compatible (i.e., not higher-kinded).

For example:

   data SomeHKT f a = SomeHKT (f a)

   instance ElmDeclarable ((Type -> Type) -> Type) SomeHKT -- Not OK: SomeHKT is higher-kinded.
   instance ElmDeclarable (Type -> Type) (SomeHKT Maybe) -- OK
   instance ElmDeclarable Type (SomeHKT Maybe Int) -- OK

   instance ElmDeclarable [] -- OK
   instance ElmDeclarable [Char] -- OK

Minimal complete definition

Nothing

Methods

mapTo :: ElmMapping Source #

Elm mapping information.

Contains the name location of the type and its encoder decoder. Can be overridden.

Example:

   instance ElmDeclarable Type [Char] where
     mapTo = ElmMapping
       { typeName = String
       , moduleName = Nothing
       , encoderLocation = Just $ SymbolLocation
           { symbolName = "string"
           , moduleName = Json.Encode
           }
       , decoderLocation = Just $ SymbolLocation
           { symbolName = "string"
           , moduleName = Json.Decode
           }
       , args = []
       }
 

mkTyRef :: PList (NParams (KindOf x)) TyRef -> TyRef Source #

Internal function. You should not have to define this method yourself.

default mkTyRef :: PList (NParams (KindOf x)) TyRef -> TyRef Source #

Instances

Instances details
(ElmDeclarable t, ElmDeclarable x) => ElmDeclarable (x t :: k) Source #

Instance for applied type constructors.

Necessary to traverse the list of type constructors down to the root when constructing type references to applied type constructors.

Instance details

Defined in Elmental

Methods

mapTo :: ElmMapping Source #

mkTyRef :: PList (NParams (KindOf (x t))) TyRef -> TyRef Source #

type HasElmStructure k x = HasElmStructure' k x (RepK x) Source #

data ElmMapping Source #

Contains the mapping of Haskell type constructor to an Elm type constructor, and potentially the location of its encoder / decoder.

Constructors

ElmMapping 

Fields

type HasSymbolInfo x = (KnownSymbol (GetTypeNameG (RepK x)), KnownSymbol (GetModuleNameG (RepK x))) Source #

type ElmKind k = ElmKindB k ~ True Source #

Constraint establishing that a kind is valid in Elm.

getElmStructure :: forall {k} (x :: k). HasElmStructure k x => DatatypeStructure x Source #

Extract the structure of the representation of a datatype in Elm.

Used by code generation.

setModule :: Text -> ElmMapping -> ElmMapping Source #

Overrides / sets the module name everywhere in a mapping. Often useful in conjunction wit defaultMapping.