-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Derive Elm types and Json code from Haskell types, using aeson's options -- -- Building the bridge from Haskell to Elm and back. Define types once, -- and derive the aeson and elm functions at the same time, using any -- aeson option you like. Cheers! @package elm-bridge @version 0.5.2 -- | This module defines how the derived Haskell data types are -- represented. - It is useful for writing type conversion rules. module Elm.TyRep -- | Type definition, including constructors. data ETypeDef ETypeAlias :: EAlias -> ETypeDef ETypePrimAlias :: EPrimAlias -> ETypeDef ETypeSum :: ESum -> ETypeDef -- | Type construction : type variables, type constructors, tuples and type -- application. data EType ETyVar :: ETVar -> EType ETyCon :: ETCon -> EType ETyApp :: EType -> EType -> EType ETyTuple :: Int -> EType -- | Type constructor: -- --
--   ETCon "Int"
--   
data ETCon ETCon :: String -> ETCon [tc_name] :: ETCon -> String -- | Type variable: -- --
--   ETVar "a"
--   
data ETVar ETVar :: String -> ETVar [tv_name] :: ETVar -> String -- | Type name: -- --
--   ETypeName "Map" [ETVar "k", ETVar "v"]
--   
data ETypeName ETypeName :: String -> [ETVar] -> ETypeName [et_name] :: ETypeName -> String [et_args] :: ETypeName -> [ETVar] data EPrimAlias EPrimAlias :: ETypeName -> EType -> EPrimAlias [epa_name] :: EPrimAlias -> ETypeName [epa_type] :: EPrimAlias -> EType data EAlias EAlias :: ETypeName -> [(String, EType)] -> Bool -> Bool -> Bool -> EAlias [ea_name] :: EAlias -> ETypeName [ea_fields] :: EAlias -> [(String, EType)] [ea_omit_null] :: EAlias -> Bool [ea_newtype] :: EAlias -> Bool [ea_unwrap_unary] :: EAlias -> Bool data SumTypeFields Anonymous :: [EType] -> SumTypeFields Named :: [(String, EType)] -> SumTypeFields isNamed :: SumTypeFields -> Bool data SumTypeConstructor STC :: String -> String -> SumTypeFields -> SumTypeConstructor [_stcName] :: SumTypeConstructor -> String [_stcEncoded] :: SumTypeConstructor -> String [_stcFields] :: SumTypeConstructor -> SumTypeFields data ESum ESum :: ETypeName -> [SumTypeConstructor] -> SumEncoding' -> Bool -> Bool -> ESum [es_name] :: ESum -> ETypeName [es_constructors] :: ESum -> [SumTypeConstructor] [es_type] :: ESum -> SumEncoding' [es_omit_null] :: ESum -> Bool [es_unary_strings] :: ESum -> Bool -- | Transforms tuple types in a list of types. Otherwise returns a -- singleton list with the original type. unpackTupleType :: EType -> [EType] unpackToplevelConstr :: EType -> [EType] class IsElmDefinition a compileElmDef :: IsElmDefinition a => Proxy a -> ETypeDef newtype SumEncoding' SumEncoding' :: SumEncoding -> SumEncoding' defSumEncoding :: SumEncoding' -- | Get an elm-bridge type representation for a Haskell type. -- This can be used to render the type declaration via -- ElmRenderable or the the JSON serializer/parser names via -- jsonSerForType and jsonParserForType. toElmType :: Typeable a => Proxy a -> EType instance GHC.Classes.Eq Elm.TyRep.ETypeDef instance GHC.Show.Show Elm.TyRep.ETypeDef instance GHC.Classes.Ord Elm.TyRep.ESum instance GHC.Classes.Eq Elm.TyRep.ESum instance GHC.Show.Show Elm.TyRep.ESum instance GHC.Classes.Ord Elm.TyRep.SumTypeConstructor instance GHC.Classes.Eq Elm.TyRep.SumTypeConstructor instance GHC.Show.Show Elm.TyRep.SumTypeConstructor instance GHC.Classes.Ord Elm.TyRep.SumTypeFields instance GHC.Classes.Eq Elm.TyRep.SumTypeFields instance GHC.Show.Show Elm.TyRep.SumTypeFields instance GHC.Classes.Ord Elm.TyRep.EAlias instance GHC.Classes.Eq Elm.TyRep.EAlias instance GHC.Show.Show Elm.TyRep.EAlias instance GHC.Classes.Ord Elm.TyRep.EPrimAlias instance GHC.Classes.Eq Elm.TyRep.EPrimAlias instance GHC.Show.Show Elm.TyRep.EPrimAlias instance GHC.Classes.Ord Elm.TyRep.ETypeName instance GHC.Classes.Eq Elm.TyRep.ETypeName instance GHC.Show.Show Elm.TyRep.ETypeName instance GHC.Classes.Ord Elm.TyRep.EType instance GHC.Classes.Eq Elm.TyRep.EType instance GHC.Show.Show Elm.TyRep.EType instance GHC.Classes.Ord Elm.TyRep.ETVar instance GHC.Classes.Eq Elm.TyRep.ETVar instance GHC.Show.Show Elm.TyRep.ETVar instance GHC.Classes.Ord Elm.TyRep.ETCon instance GHC.Classes.Eq Elm.TyRep.ETCon instance GHC.Show.Show Elm.TyRep.ETCon instance GHC.Show.Show Elm.TyRep.SumEncoding' instance GHC.Classes.Eq Elm.TyRep.SumEncoding' instance GHC.Classes.Ord Elm.TyRep.SumEncoding' -- | This module should be used to derive the Elm instance alongside the -- JSON ones. The prefered usage is to convert statements such as : -- --
--   $(deriveJSON defaultOptions{fieldLabelModifier = drop 4, constructorTagModifier = map toLower} ''D)
--   
-- -- into: -- --
--   $(deriveBoth defaultOptions{fieldLabelModifier = drop 4, constructorTagModifier = map toLower} ''D)
--   
-- -- Which will derive both the aeson and elm-bridge -- instances at the same time. module Elm.Derive -- | Options that specify how to encode/decode your datatype to/from JSON. -- -- Options can be set using record syntax on defaultOptions with -- the fields below. data Options -- | Specifies how to encode constructors of a sum datatype. data SumEncoding -- | A constructor will be encoded to an object with a field -- tagFieldName which specifies the constructor tag (modified by -- the constructorTagModifier). If the constructor is a record the -- encoded record fields will be unpacked into this object. So make sure -- that your record doesn't have a field with the same label as the -- tagFieldName. Otherwise the tag gets overwritten by the encoded -- value of that field! If the constructor is not a record the encoded -- constructor contents will be stored under the contentsFieldName -- field. TaggedObject :: String -> String -> SumEncoding [tagFieldName] :: SumEncoding -> String [contentsFieldName] :: SumEncoding -> String -- | Constructor names won't be encoded. Instead only the contents of the -- constructor will be encoded as if the type had a single constructor. -- JSON encodings have to be disjoint for decoding to work properly. -- -- When decoding, constructors are tried in the order of definition. If -- some encodings overlap, the first one defined will succeed. -- -- Note: Nullary constructors are encoded as strings (using -- constructorTagModifier). Having a nullary constructor alongside -- a single field constructor that encodes to a string leads to -- ambiguity. -- -- Note: Only the last error is kept when decoding, so in the case -- of malformed JSON, only an error for the last constructor will be -- reported. UntaggedValue :: SumEncoding -- | A constructor will be encoded to an object with a single field named -- after the constructor tag (modified by the -- constructorTagModifier) which maps to the encoded contents of -- the constructor. ObjectWithSingleField :: SumEncoding -- | A constructor will be encoded to a 2-element array where the first -- element is the tag of the constructor (modified by the -- constructorTagModifier) and the second element the encoded -- contents of the constructor. TwoElemArray :: SumEncoding -- | Note that This default set of options is distinct from that in the -- aeson package. defaultOptions :: Options -- | This generates a default set of options. The parameter represents the -- number of characters that must be dropped from the Haskell field -- names. The first letter of the field is then converted to lowercase, -- ie: -- --
--   data Foo = Foo { _fooBarQux :: Int }
--   $(deriveBoth (defaultOptionsDropLower 4) ''Foo)
--   
-- -- Will be encoded as: -- --
--   {"barQux"=12}
--   
defaultOptionsDropLower :: Int -> Options -- | Just derive the elm-bridge definitions for generating the -- serialization/deserialization code. It must be kept synchronized with -- the Haskell code manually. deriveElmDef :: Options -> Name -> Q [Dec] -- | Equivalent to running both deriveJSON and deriveElmDef -- with the same options, so as to ensure the code on the Haskell and Elm -- size is synchronized. deriveBoth :: Options -> Name -> Q [Dec] -- | This module should not usually be imported. module Elm.TyRender class ElmRenderable a renderElm :: ElmRenderable a => a -> String instance Elm.TyRender.ElmRenderable Elm.TyRep.ETypeDef instance Elm.TyRender.ElmRenderable Elm.TyRep.EType instance Elm.TyRender.ElmRenderable Elm.TyRep.ETCon instance Elm.TyRender.ElmRenderable Elm.TyRep.ETVar instance Elm.TyRender.ElmRenderable Elm.TyRep.ETypeName instance Elm.TyRender.ElmRenderable Elm.TyRep.EAlias instance Elm.TyRender.ElmRenderable Elm.TyRep.ESum instance Elm.TyRender.ElmRenderable Elm.TyRep.EPrimAlias -- | This module implements a generator for JSON serialisers and parsers of -- arbitrary elm types. -- -- It is highly recommended to either only use the functions of -- Elm.Module, or to use the functions in this module after having -- modified the ETypeDef arguments with functions such as -- defaultAlterations. -- -- The reason is that Elm types might have an equivalent on the Haskell -- side and should be converted (ie. Text -> String, -- Vector -> List). module Elm.Json -- | Compile a JSON parser for an Elm type definition jsonParserForDef :: ETypeDef -> String -- | Compile a JSON serializer for an Elm type definition jsonSerForDef :: ETypeDef -> String -- | Compile a JSON parser for an Elm type jsonParserForType :: EType -> String -- | Compile a JSON serializer for an Elm type. -- -- The omitNothingFields option is currently not implemented! jsonSerForType :: EType -> String instance GHC.Classes.Eq Elm.Json.MaybeHandling -- | A type to represent versions of Elm for produced code to work against. -- -- This module ONLY supports Elm 0.18 module Elm.Versions data ElmVersion Elm0p18 :: ElmVersion -- | Functions in this module are used to generate Elm modules. Note that -- the generated modules depend on the bartavelle/json-helpers -- package. module Elm.Module -- | Existential quantification wrapper for lists of type definitions data DefineElm DefineElm :: Proxy a -> DefineElm -- | The module header line for this version of Elm moduleHeader :: ElmVersion -> String -> 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.). makeElmModuleWithVersion :: ElmVersion -> String -> [DefineElm] -> 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.). makeElmModule :: String -> [DefineElm] -> String -- | Generates the content of a module. You will be responsible for -- including the required Elm headers. This uses the default type -- conversion rules. makeModuleContent :: [DefineElm] -> String -- | Generates the content of a module, using custom type conversion rules. makeModuleContentWithAlterations :: (ETypeDef -> ETypeDef) -> [DefineElm] -> String -- | 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")
--                     _                        -> t
--   
recAlterType :: (EType -> EType) -> ETypeDef -> ETypeDef -- | Given a list of type names, will newtype all the matching -- type definitions. newtypeAliases :: [String] -> ETypeDef -> ETypeDef -- | A default set of type conversion rules: -- -- defaultAlterations :: ETypeDef -> ETypeDef defaultTypeAlterations :: EType -> EType