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

Safe HaskellNone
LanguageHaskell2010

Language.PureScript.Bridge.Builder

Description

A bridge builder DSL, powered by Monad, Alternative and lens.

Bridges can be built within the BridgeBuilder monad. You can check properties of the to be bridged Haskell TypeInfo with ^== or doCheck, you have choice (<|>), you can fail (empty) and you can return a translated PureScript TypeInfo (return). The Haskell TypeInfo can be accessed with:

view haskType

Find usage examples in Language.PureScript.Bridge.Primitives and Language.PureScript.Bridge.PSTypes

Synopsis

Documentation

type FixUpBridge = FullBridge Source

Bridges to use when a BridgePart returns Nothing.

data BridgeData Source

Instances

HasHaskType BridgeData Source

By implementing the haskType lens in the HasHaskType class, we are able to use it for both BridgeData and a plain 'TypeInfo Haskell', therefore you can use it with doCheck and ^== for checks on the complete 'TypeInfo Haskell' value.

Example:

stringBridge :: BridgePart
stringBridge = do
  -- Note: we are using the TypeInfo 'Haskell instance here:
  haskType ^== mkTypeInfo (Proxy :: Proxy String)
  return psString
MonadReader BridgeData BridgeBuilder Source 

data BridgeBuilder a Source

Instances

Monad BridgeBuilder Source 
Functor BridgeBuilder Source 
Applicative BridgeBuilder Source 
Alternative BridgeBuilder Source

Alternative instance for BridgeBuilder so you can construct bridges with <|>, which behaves like a logical or (||). If the left-hand side results in Nothing the right-hand side is used, otherwise the left-hand side. For usage examples see Language.PureScript.Bridge.Primitives.

MonadPlus BridgeBuilder Source 
MonadReader BridgeData BridgeBuilder Source 

clearPackageFixUp :: FixUpBridge Source

Bridge to PureScript by simply clearing out the _typePackage field. This bridge is used by default as FixUpBridge by buildBridge:

buildBridge = buildBridgeWithCustomFixUp clearPackageFixUp

Thus, if no bridge matches a type, it gets optimistically translated to a PureScript type which is idential to the Haskell type. Only the _typePackage field gets cleared, as it is very unlikely that the PureScript package is called the same as the Haskell package.

Alternatively, if you are not that optimistic, you can use errorFixUp - which simply calls error when used.

buildBridgeWithCustomFixUp errorFixUp yourBridge

Of course you can also write your own FixUpBridge. In this case it is highly recommended that you build your custom FixUpBridge from BridgePart with buildBridgeWithCustomFixUp too, with FixUpBridge being finally errorFixUp. This way you get all the builder convenience and proper bridging of typeParameters. For an example have a look at the implementation of clearPackageFixup.

errorFixUp :: FixUpBridge Source

A FixUpBridge which calles error when used. Usage:

buildBridgeWithCustomFixUp errorFixUp yourBridge

buildBridge :: BridgePart -> FullBridge Source

Build a bridge.

This is a convenience wrapper for buildBridgeWithCustomFixUp.

Definition:

buildBridgeWithCustomFixUp clearPackageFixUp

buildBridgeWithCustomFixUp :: FixUpBridge -> BridgePart -> FullBridge Source

Takes a constructed BridgePart and makes it a total function (FullBridge) by using the supplied FixUpBridge when BridgePart returns Nothing.

The supplied BridgePart also gets passed through fixTypeParameters in order to support translation of type constructors.

doCheck :: Getter (TypeInfo Haskell) a -> (a -> Bool) -> BridgeBuilder () Source

Do some check on properties of haskType.

(^==) :: Eq a => Getter (TypeInfo Haskell) a -> a -> BridgeBuilder () infix 4 Source

Check parts of haskType for equality:

textBridge :: BridgePart
textBridge = do
  typeName ^== "Text"
  typeModule ^== "Data.Text.Internal" <|> typeModule ^== "Data.Text.Internal.Lazy"
  return psString

(<|>) :: Alternative f => forall a. f a -> f a -> f a

An associative binary operation

psTypeParameters :: BridgeBuilder [TypeInfo PureScript] Source

Bridge haskType typeParameters over to PureScript types.

To be used for bridging type constructors.

fixTypeParameters :: BridgePart -> BridgePart Source

Translate types that come from any module named Something.TypeParameters to lower case:

Also drop the 1 at the end if present. This method gets called by buildBridge and buildBridgeWithCustomFixUp for you - you should not need to call it.

It enables you to even bridge type constructor definitions, see Language.PureScript.Bridge.TypeParameters for more details.