elm-bridge-0.6.0: Derive Elm types and Json code from Haskell types, using aeson's options

Safe HaskellNone
LanguageHaskell2010

Elm.TyRep

Description

This module defines how the derived Haskell data types are represented. - It is useful for writing type conversion rules.

Synopsis

Documentation

data ETypeDef Source #

Type definition, including constructors.

Instances
Eq ETypeDef Source # 
Instance details

Defined in Elm.TyRep

Show ETypeDef Source # 
Instance details

Defined in Elm.TyRep

ElmRenderable ETypeDef Source # 
Instance details

Defined in Elm.TyRender

data EType Source #

Type construction : type variables, type constructors, tuples and type application.

Instances
Eq EType Source # 
Instance details

Defined in Elm.TyRep

Methods

(==) :: EType -> EType -> Bool #

(/=) :: EType -> EType -> Bool #

Ord EType Source # 
Instance details

Defined in Elm.TyRep

Methods

compare :: EType -> EType -> Ordering #

(<) :: EType -> EType -> Bool #

(<=) :: EType -> EType -> Bool #

(>) :: EType -> EType -> Bool #

(>=) :: EType -> EType -> Bool #

max :: EType -> EType -> EType #

min :: EType -> EType -> EType #

Show EType Source # 
Instance details

Defined in Elm.TyRep

Methods

showsPrec :: Int -> EType -> ShowS #

show :: EType -> String #

showList :: [EType] -> ShowS #

ElmRenderable EType Source # 
Instance details

Defined in Elm.TyRender

newtype ETCon Source #

Type constructor:

ETCon "Int"

Constructors

ETCon 

Fields

Instances
Eq ETCon Source # 
Instance details

Defined in Elm.TyRep

Methods

(==) :: ETCon -> ETCon -> Bool #

(/=) :: ETCon -> ETCon -> Bool #

Ord ETCon Source # 
Instance details

Defined in Elm.TyRep

Methods

compare :: ETCon -> ETCon -> Ordering #

(<) :: ETCon -> ETCon -> Bool #

(<=) :: ETCon -> ETCon -> Bool #

(>) :: ETCon -> ETCon -> Bool #

(>=) :: ETCon -> ETCon -> Bool #

max :: ETCon -> ETCon -> ETCon #

min :: ETCon -> ETCon -> ETCon #

Show ETCon Source # 
Instance details

Defined in Elm.TyRep

Methods

showsPrec :: Int -> ETCon -> ShowS #

show :: ETCon -> String #

showList :: [ETCon] -> ShowS #

ElmRenderable ETCon Source # 
Instance details

Defined in Elm.TyRender

newtype ETVar Source #

Type variable:

ETVar "a"

Constructors

ETVar 

Fields

Instances
Eq ETVar Source # 
Instance details

Defined in Elm.TyRep

Methods

(==) :: ETVar -> ETVar -> Bool #

(/=) :: ETVar -> ETVar -> Bool #

Ord ETVar Source # 
Instance details

Defined in Elm.TyRep

Methods

compare :: ETVar -> ETVar -> Ordering #

(<) :: ETVar -> ETVar -> Bool #

(<=) :: ETVar -> ETVar -> Bool #

(>) :: ETVar -> ETVar -> Bool #

(>=) :: ETVar -> ETVar -> Bool #

max :: ETVar -> ETVar -> ETVar #

min :: ETVar -> ETVar -> ETVar #

Show ETVar Source # 
Instance details

Defined in Elm.TyRep

Methods

showsPrec :: Int -> ETVar -> ShowS #

show :: ETVar -> String #

showList :: [ETVar] -> ShowS #

ElmRenderable ETVar Source # 
Instance details

Defined in Elm.TyRender

data ETypeName Source #

Type name:

ETypeName "Map" [ETVar "k", ETVar "v"]

Constructors

ETypeName 

Fields

Instances
Eq ETypeName Source # 
Instance details

Defined in Elm.TyRep

Ord ETypeName Source # 
Instance details

Defined in Elm.TyRep

Show ETypeName Source # 
Instance details

Defined in Elm.TyRep

ElmRenderable ETypeName Source # 
Instance details

Defined in Elm.TyRender

data EAlias Source #

Instances
Eq EAlias Source # 
Instance details

Defined in Elm.TyRep

Methods

(==) :: EAlias -> EAlias -> Bool #

(/=) :: EAlias -> EAlias -> Bool #

Ord EAlias Source # 
Instance details

Defined in Elm.TyRep

Show EAlias Source # 
Instance details

Defined in Elm.TyRep

ElmRenderable EAlias Source # 
Instance details

Defined in Elm.TyRender

data ESum Source #

Instances
Eq ESum Source # 
Instance details

Defined in Elm.TyRep

Methods

(==) :: ESum -> ESum -> Bool #

(/=) :: ESum -> ESum -> Bool #

Ord ESum Source # 
Instance details

Defined in Elm.TyRep

Methods

compare :: ESum -> ESum -> Ordering #

(<) :: ESum -> ESum -> Bool #

(<=) :: ESum -> ESum -> Bool #

(>) :: ESum -> ESum -> Bool #

(>=) :: ESum -> ESum -> Bool #

max :: ESum -> ESum -> ESum #

min :: ESum -> ESum -> ESum #

Show ESum Source # 
Instance details

Defined in Elm.TyRep

Methods

showsPrec :: Int -> ESum -> ShowS #

show :: ESum -> String #

showList :: [ESum] -> ShowS #

ElmRenderable ESum Source # 
Instance details

Defined in Elm.TyRender

unpackTupleType :: EType -> [EType] Source #

Transforms tuple types in a list of types. Otherwise returns a singleton list with the original type.

toElmType :: Typeable a => Proxy a -> EType Source #

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.