purescript-bridge-0.10.1.0: Generate PureScript data types from Haskell data types

Safe HaskellNone
LanguageHaskell2010

Language.PureScript.Bridge.SumType

Synopsis

Documentation

data SumType lang Source #

Generic representation of your Haskell types.

Constructors

SumType (TypeInfo lang) [DataConstructor lang] 

Instances

Eq (SumType lang) Source # 

Methods

(==) :: SumType lang -> SumType lang -> Bool #

(/=) :: SumType lang -> SumType lang -> Bool #

Show (SumType lang) Source # 

Methods

showsPrec :: Int -> SumType lang -> ShowS #

show :: SumType lang -> String #

showList :: [SumType lang] -> ShowS #

mkSumType :: forall t. (Generic t, Typeable t, GDataConstructor (Rep t)) => Proxy t -> SumType Haskell Source #

Create a representation of your sum (and product) types, for doing type translations and writing it out to your PureScript modules. In order to get the type information we use a dummy variable of type Proxy (YourType).

data DataConstructor lang Source #

Constructors

DataConstructor 

Fields

data RecordEntry lang Source #

Constructors

RecordEntry 

Fields

Instances

Eq (RecordEntry lang) Source # 

Methods

(==) :: RecordEntry lang -> RecordEntry lang -> Bool #

(/=) :: RecordEntry lang -> RecordEntry lang -> Bool #

Show (RecordEntry lang) Source # 

Methods

showsPrec :: Int -> RecordEntry lang -> ShowS #

show :: RecordEntry lang -> String #

showList :: [RecordEntry lang] -> ShowS #

getUsedTypes :: SumType lang -> Set (TypeInfo lang) Source #

Get all used types in a sum type.

This includes all types found at the right hand side of a sum type definition, not the type parameters of the sum type itself

sigValues :: forall lang lang. Lens (DataConstructor lang) (DataConstructor lang) (Either [TypeInfo lang] [RecordEntry lang]) (Either [TypeInfo lang] [RecordEntry lang]) Source #

sumTypeInfo :: Functor f => (TypeInfo lang -> f (TypeInfo lang)) -> SumType lang -> f (SumType lang) Source #

TypInfo lens for SumType.

sumTypeConstructors :: Functor f => ([DataConstructor lang] -> f [DataConstructor lang]) -> SumType lang -> f (SumType lang) Source #

DataConstructor lens for SumType.

recLabel :: forall lang. Lens' (RecordEntry lang) Text Source #

recValue :: forall lang lang. Lens (RecordEntry lang) (RecordEntry lang) (TypeInfo lang) (TypeInfo lang) Source #