clr-inline: Quasiquoters for inline C# and F#

[ .net, bsd3, clr, ffi, language, library ] [ Propose Tags ]

Please see README.md


[Skip to Readme]

Downloads

Note: This package has metadata revisions in the cabal description newer than included in the tarball. To unpack the package including the revisions, use 'cabal get'.

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.2.0, 0.2.0.1
Change log CHANGELOG.md
Dependencies base (>=4.9 && <5), bytestring, Cabal, clr-host, clr-marshal, containers, directory, extra, filepath, here, lens, process, template-haskell, temporary, text, transformers [details]
License BSD-3-Clause
Copyright 2017 Jose Iborra
Author Jose Iborra
Maintainer pepeiborra@gmail.com
Revised Revision 1 made by PepeIborra at 2017-07-27T22:00:15Z
Category Language, FFI, CLR, .NET
Home page https://gitlab.com/tim-m89/clr-haskell
Bug tracker https://gitlab.com/tim-m89/clr-haskell/issues
Source repo head: git clone https://gitlab.com/tim-m89/clr-haskell/tree/master
Uploaded by PepeIborra at 2017-04-25T17:32:32Z
Distributions
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 2498 total (12 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user [build log]
All reported builds failed as of 2017-04-25 [all 3 reports]

Readme for clr-inline-0.1.0.0

[back to package description]

clr-inline

Unix build status Windows Build Status

**NOTE: you will need GHC >= 8.2 to use this package in Windows.

What is clr-inline

clr-inline provides a quasiquoter to inline F# and C# code in Haskell modules. It was inspired by [inline-java], [inline-c] and [inline-r], and it is implemented on top of clr-host and clr-marshal packages.

Example

Graphical hello world using F# Winforms:

{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
module Main where

import Clr.Inline

[fsharp|
  open System.Windows.Forms
       |]

main = do
  startClr
  let text = "Hello from Haskell"
  [fsharp|
        let form = new Form(Text=$text:string)
        let button = new Button(Text="Click Me!", Dock=DockStyle.Fill)
        button.Click.Add(fun _ -> MessageBox.Show($text, "Hey!") |> ignore)
        form.Controls.Add(button)
        Application.Run(form)
         |]

Features

  • Inline F# / C# in Haskell.
  • Automatic unmarshalling of CLR primitive types into Haskell.
  • Reference types support including arrays and generics.
  • Refer to Haskell non-function values inside F# / C# quotations.

Getting Started

Install the clr-inline package from Hackage using your preferred package manager:

$ cabal install clr-inline
$ stack install clr-inline

By default, .Net is used in Windows and mono in other systems. This is driven by Cabal flags in the clr-host package.

Requirements

clr-inline requires GHC >=8.0 for mono, and either GHC >=8.2 or a linker preprocessor for .Net.

Cabal requires that the CLR compiler is in the application path at cabal configure time. The module Clr.Inline.Cabal provides an optional Cabal user hook that can be added to a cabal Setup script to check for this automatically

The quasiquoters look for the F#/C# compiler binaries in the application path. External dependencies and additional search paths can be provided to the quasiquoter as configuration. Configuration creates a new quasiquoter; since GHC does not allow calling a quasiquoter from the same module where it is defined, the recommended practice is to configure the quasiquoters in a dedicated Config module. Example configuration for WPF dependencies:

module WpfDeps where

import Clr.Inline
import Clr.Inline.Config

wpf =
  fsharp' $
    defaultConfig
    { configDependencies =
        [ "System.Xaml"
        , "WindowsBase"
        , "PresentationCore"
        , "PresentationFramework"
        ]
    }

LICENSE

Copyright (c) 2017 Jose Iborra

clr-inline is free software and may be redistributed under the terms specified in the LICENSE file.