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

Safe HaskellNone
LanguageHaskell2010

Language.PureScript.Bridge

Synopsis

Documentation

bridgeSumType :: FullBridge -> SumType Haskell -> SumType PureScript Source #

Translate all TypeInfo values in a SumType to PureScript types.

Example usage, with defaultBridge:

data Foo = Foo | Bar Int | FooBar Int Text deriving (Generic, Typeable, Show)
bridgeSumType (buildBridge defaultBridge) (mkSumType (Proxy :: Proxy Foo))

defaultBridge :: BridgePart Source #

Default bridge for mapping primitive/common types: You can append your own bridges like this:

 defaultBridge <|> myBridge1 <|> myBridge2

Find examples for bridge definitions in Language.PureScript.Bridge.Primitives and Language.PureScript.Bridge.Tuple.

writePSTypes :: FilePath -> FullBridge -> [SumType Haskell] -> IO () Source #

Your entry point to this library and quite likely all you will need. Make sure all your types derive Generic and Typeable. Typeable is not needed from ghc-7.10 on.

Then list all your types you want to use in PureScript and call writePSTypes:

data Foo = Foo { ... } deriving (Eq, Generic)
data Bar = A | B | C deriving (Eq, Ord, Generic)
data Baz = ... deriving (Generic)

-- | All types will have a `Generic` instance produced in Purescript.
myTypes :: [SumType 'Haskell]
myTypes =
  [ let p = (Proxy :: Proxy Foo) in equal p (mkSumType p)  -- Also produce a `Eq` instance.
  , let p = (Proxy :: Proxy Bar) in order p (mkSumType p)  -- Produce both `Eq` and `Ord`.
  , mkSumType (Proxy :: Proxy Baz)  -- Just produce a `Generic` instance.
  ]

 writePSTypes "path/to/your/purescript/project" (buildBridge defaultBridge) myTypes

You can define your own type bridges based on defaultBridge:

 myBridge = defaultBridge <|> mySpecialTypeBridge

and use it with writePSTypes:

 writePSTypes "path/to/your/purescript/project" (buildBridge myBridge) myTypes

Find examples for implementing your own bridges in: Language.PureScript.Bridge.Primitives.

Result:

writePSTypes will write out PureScript modules to the given path, mirroring the hierarchy of the Haskell modules the types came from. In addition a list of needed PS packages is printed to the console.

The list of needed packages is retrieved from the bridged TypeInfo data, so make sure you set _typePackage correctly in your own bridges, in order for this feature to be useful.

Real world usage example (at time of this writing outdated, at time of reading hopefully fixed):

A real world use case of this library can be found here.

With custom bridges defined here and custom PS types defined here.

Parts of the generated output can be found here.

Note how Secret and Key get translated according to our custom rules, with correct imports and everything. Also the formatting is quite nice, would you have guessed that this code was generated?

WARNING:

This function overwrites files - make backups or use version control!

writePSTypesWith :: Switch -> FilePath -> FullBridge -> [SumType Haskell] -> IO () Source #

Works like writePSTypes but you can add additional switches to control the generation of your PureScript code

Switches/Settings:

  • noLenses and genLenses to control if the `purescript-profunctor-lenses` are generated for your types

WARNING:

This function overwrites files - make backups or use version control!

defaultSwitch :: Switch Source #

Default switches include code generation for lenses

noLenses :: Switch Source #

Switch off the generatation of profunctor-lenses

genLenses :: Switch Source #

Switch on the generatation of profunctor-lenses