| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
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 HaskellType with ^== or doCheck,
you have choice (<|>), you can fail (empty) and you can return a translated
PSType (return). The HaskellType can be accessed with:
view haskType
Find usage examples in Language.PureScript.Bridge.Primitives and Language.PureScript.Bridge.PSTypes
Synopsis
- data BridgeBuilder a
- type BridgePart = BridgeBuilder PSType
- data FixUpBuilder a
- type FixUpBridge = FixUpBuilder PSType
- data BridgeData
- fullBridge :: Lens' BridgeData FullBridge
- (^==) :: Eq a => Getter HaskellType a -> a -> BridgeBuilder ()
- doCheck :: Getter HaskellType a -> (a -> Bool) -> BridgeBuilder ()
- (<|>) :: Alternative f => f a -> f a -> f a
- psTypeParameters :: MonadReader BridgeData m => m [PSType]
- type FullBridge = HaskellType -> PSType
- buildBridge :: BridgePart -> FullBridge
- clearPackageFixUp :: MonadReader BridgeData m => m PSType
- errorFixUp :: MonadReader BridgeData m => m PSType
- buildBridgeWithCustomFixUp :: FixUpBridge -> BridgePart -> FullBridge
Documentation
data BridgeBuilder a Source #
Instances
type BridgePart = BridgeBuilder PSType Source #
data FixUpBuilder a Source #
Bridges to use when a BridgePart returns Nothing (See buildBridgeWithCustomFixUp).
It is similar to BridgeBuilder but does not offer choice or failure. It is used for constructing fallbacks
if a BridgePart evaluates to Nothing.
For type definitions you should use the more generic (MonadReader BridgeData m) constraint. This way your code will work
in both FixUpBuilder and BridgeBuilder:
{-# LANGUAGE FlexibleContexts #-}
import Control.Monad.Reader.Class
import Language.PureScript.Bridge.TypeInfoInstances
type FixUpBridge = FixUpBuilder PSType Source #
data BridgeData Source #
Instances
| HasHaskType BridgeData Source # | By implementing the Example: stringBridge :: BridgePart stringBridge = do -- Note: we are using the HaskellType instance here: haskType ^== mkTypeInfo (Proxy :: Proxy String) return psString |
Defined in Language.PureScript.Bridge.Builder Methods | |
| MonadReader BridgeData BridgeBuilder Source # | |
Defined in Language.PureScript.Bridge.Builder Methods ask :: BridgeBuilder BridgeData # local :: (BridgeData -> BridgeData) -> BridgeBuilder a -> BridgeBuilder a # reader :: (BridgeData -> a) -> BridgeBuilder a # | |
| MonadReader BridgeData FixUpBuilder Source # | |
Defined in Language.PureScript.Bridge.Builder Methods ask :: FixUpBuilder BridgeData # local :: (BridgeData -> BridgeData) -> FixUpBuilder a -> FixUpBuilder a # reader :: (BridgeData -> a) -> FixUpBuilder a # | |
fullBridge :: Lens' BridgeData FullBridge Source #
Lens for access to the complete bridge from within our Reader monad.
This is used for example for implementing psTypeParameters.
(^==) :: Eq a => Getter HaskellType 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
doCheck :: Getter HaskellType a -> (a -> Bool) -> BridgeBuilder () Source #
Do some check on properties of haskType.
(<|>) :: Alternative f => f a -> f a -> f a infixl 3 #
An associative binary operation
psTypeParameters :: MonadReader BridgeData m => m [PSType] Source #
Bridge haskType typeParameters over to PureScript types.
To be used for bridging type constructors.
type FullBridge = HaskellType -> PSType Source #
buildBridge :: BridgePart -> FullBridge Source #
Build a bridge.
This is a convenience wrapper for buildBridgeWithCustomFixUp and should normally be sufficient.
Definition:
buildBridgeWithCustomFixUp clearPackageFixUp
clearPackageFixUp :: MonadReader BridgeData m => m PSType 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. It works the same
as for BridgePart, but you can not have choice (<|>) or failure (empty).
errorFixUp :: MonadReader BridgeData m => m PSType Source #
A FixUpBridge which calles error when used.
Usage:
buildBridgeWithCustomFixUp errorFixUp yourBridge
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.