| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Clr.Inline
Contents
- csharp :: QuasiQuoter
- csharp' :: ClrInlineConfig -> QuasiQuoter
- fsharp :: QuasiQuoter
- fsharp' :: ClrInlineConfig -> QuasiQuoter
- startClr :: IO ()
- class Unmarshal marshal haskell => Quotable quoted clr marshal haskell | marshal -> haskell clr
- data FunPtr a :: * -> *
- newtype BStr :: * = BStr (Ptr Word16)
- newtype TextBStr = TextBStr BStr
- data Clr name = Clr (ClrPtr name) (IORef ())
- newtype ClrPtr name = ClrPtr Int64
Documentation
csharp :: QuasiQuoter Source #
Quasiquoter for C# declarations and expressions. A quasiquote is a block of C# statements wrapped in curly braces preceded by the C# return type. Examples:
example :: IO (Clr "int[]")
example = do
[csharp| Console.WriteLine("Hello CLR inline !!!"); |]
i <- [csharp| int { return 2; }|]
[csharp| int[] { int[] a = new int[4]{0,0,0,0};
for(int i=0; i < 4; i++) {
a[i] = i;
}
return a;
}|]
See the documentation for fsharp for details on the quotation
and antiquotation syntaxes.
This quasiquoter is implicitly configured with the defaultConfig.
csharp' :: ClrInlineConfig -> QuasiQuoter Source #
Explicit configuration version of csharp.
fsharp :: QuasiQuoter Source #
F# declaration and expression quasiquoter. Declarations can include open statements, types or even modules. Example declaration:
[fsharp|
open System
open System.Collections.Generic
module Globals =
let mutable today = DateTime.Today
|]
Expressions are wrapped in a curly braces block {} that
fixes the return type. An F# expression quotation can refer to
a Haskell binding x using the syntax ($x:type) where type is
a string denoting an F# type and is only required on the first usage, and the parentheses
are optional. F# types are mapped to Haskell types via the Quotable class.
An antiquotation $x:type
is well-scoped if there exists a variable x with a Haskell type U in
the Haskell context such that there exists an instance
Quotable type clr marshall U for some clr and marshall.
An F# expression returns an IO computation that
produces a value of the quoted result type if said type is Quotable.
Example expressions:
hello :: IO (Int, Clr "System.DateTime")
hello = do
let year = 2017 :: Int
aClr <- [fsharp| DateTime{ DateTime($year:int,04,10)} |]
anInt <- [fsharp| int{ ($aClr:System.DateTime).Year + $year:int + $year}|]
return (anInt, anClr)
CLR Reference types are modelled in Haskell as Clr values, indexed with the
name of their F# type as a type level symbol. String equivalence is a poor
substitute for type equality, so for two Clr values to have the same type
they must be indexed by exactly the same string.
This quasiquoter is implicitly configured with the defaultConfig.
fsharp' :: ClrInlineConfig -> QuasiQuoter Source #
Explicit configuration version of fsharp.
class Unmarshal marshal haskell => Quotable quoted clr marshal haskell | marshal -> haskell clr Source #
Extensible mapping between quotable CLR types and Haskell types
Instances
| Quotable "bool" "System.Boolean" Bool Bool Source # | |
| Quotable "double" "System.Double" Double Double Source # | |
| Quotable "int" "System.Int32" Int Int Source # | |
| Quotable "int16" "System.Int16" Int16 Int16 Source # | |
| Quotable "int32" "System.Int32" Int32 Int32 Source # | |
| Quotable "int64" "System.Int64" Int64 Int64 Source # | |
| Quotable "long" "System.Int64" Int64 Int64 Source # | |
| Quotable "string" "System.String" BStr String Source # | |
| Quotable "text" "System.String" TextBStr Text Source # | |
| Quotable "uint16" "System.UInt16" Word16 Word16 Source # | |
| Quotable "uint32" "System.UInt32" Word32 Word32 Source # | |
| Quotable "uint64" "System.UInt64" Word64 Word64 Source # | |
| Quotable "void" "System.Void" () () Source # | |
| Quotable "word16" "System.UInt16" Word16 Word16 Source # | |
| Quotable "word32" "System.UInt32" Word32 Word32 Source # | |
| Quotable "word64" "System.UInt64" Word64 Word64 Source # | |
| Quotable a a (ClrPtr a) (Clr a) Source # | All reference types are handled by this instance. |
Reexports for generated code
A value of type is a pointer to a function callable
from foreign code. The type FunPtr aa will normally be a foreign type,
a function type with zero or more arguments where
- the argument types are marshallable foreign types,
i.e.
Char,Int,Double,Float,Bool,Int8,Int16,Int32,Int64,Word8,Word16,Word32,Word64,,Ptra,FunPtraor a renaming of any of these usingStablePtranewtype. - the return type is either a marshallable foreign type or has the form
whereIOttis a marshallable foreign type or().
A value of type may be a pointer to a foreign function,
either returned by another foreign function or imported with a
a static address import likeFunPtr a
foreign import ccall "stdlib.h &free" p_free :: FunPtr (Ptr a -> IO ())
or a pointer to a Haskell function created using a wrapper stub
declared to produce a FunPtr of the correct type. For example:
type Compare = Int -> Int -> Bool foreign import ccall "wrapper" mkCompare :: Compare -> IO (FunPtr Compare)
Calls to wrapper stubs like mkCompare allocate storage, which
should be released with freeHaskellFunPtr when no
longer required.
To convert FunPtr values to corresponding Haskell functions, one
can define a dynamic stub for the specific foreign type, e.g.
type IntFunction = CInt -> IO () foreign import ccall "dynamic" mkFun :: FunPtr IntFunction -> IntFunction
A wrapper around a ClrPtr, which will be released once this
wrapper is no longer referenced.
The only way to access the contents is in clr-inline quotations.
A pointer to a Clr object. The only way to access the contents is via clr-inline quotations.