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

Safe HaskellNone
LanguageHaskell2010

Clr.Inline

Contents

Synopsis

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.

startClr :: IO () #

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

data FunPtr a :: * -> * #

A value of type FunPtr a is a pointer to a function callable from foreign code. The type a will normally be a foreign type, a function type with zero or more arguments where

A value of type FunPtr a may be a pointer to a foreign function, either returned by another foreign function or imported with a a static address import like

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

Instances

IArray UArray (FunPtr a) 

Methods

bounds :: Ix i => UArray i (FunPtr a) -> (i, i) #

numElements :: Ix i => UArray i (FunPtr a) -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, FunPtr a)] -> UArray i (FunPtr a)

unsafeAt :: Ix i => UArray i (FunPtr a) -> Int -> FunPtr a

unsafeReplace :: Ix i => UArray i (FunPtr a) -> [(Int, FunPtr a)] -> UArray i (FunPtr a)

unsafeAccum :: Ix i => (FunPtr a -> e' -> FunPtr a) -> UArray i (FunPtr a) -> [(Int, e')] -> UArray i (FunPtr a)

unsafeAccumArray :: Ix i => (FunPtr a -> e' -> FunPtr a) -> FunPtr a -> (i, i) -> [(Int, e')] -> UArray i (FunPtr a)

Eq (FunPtr a) 

Methods

(==) :: FunPtr a -> FunPtr a -> Bool #

(/=) :: FunPtr a -> FunPtr a -> Bool #

Ord (FunPtr a) 

Methods

compare :: FunPtr a -> FunPtr a -> Ordering #

(<) :: FunPtr a -> FunPtr a -> Bool #

(<=) :: FunPtr a -> FunPtr a -> Bool #

(>) :: FunPtr a -> FunPtr a -> Bool #

(>=) :: FunPtr a -> FunPtr a -> Bool #

max :: FunPtr a -> FunPtr a -> FunPtr a #

min :: FunPtr a -> FunPtr a -> FunPtr a #

Show (FunPtr a) 

Methods

showsPrec :: Int -> FunPtr a -> ShowS #

show :: FunPtr a -> String #

showList :: [FunPtr a] -> ShowS #

Storable (FunPtr a) 

Methods

sizeOf :: FunPtr a -> Int #

alignment :: FunPtr a -> Int #

peekElemOff :: Ptr (FunPtr a) -> Int -> IO (FunPtr a) #

pokeElemOff :: Ptr (FunPtr a) -> Int -> FunPtr a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (FunPtr a) #

pokeByteOff :: Ptr b -> Int -> FunPtr a -> IO () #

peek :: Ptr (FunPtr a) -> IO (FunPtr a) #

poke :: Ptr (FunPtr a) -> FunPtr a -> IO () #

MArray (STUArray s) (FunPtr a) (ST s) 

Methods

getBounds :: Ix i => STUArray s i (FunPtr a) -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i (FunPtr a) -> ST s Int

newArray :: Ix i => (i, i) -> FunPtr a -> ST s (STUArray s i (FunPtr a)) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i (FunPtr a)) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i (FunPtr a))

unsafeRead :: Ix i => STUArray s i (FunPtr a) -> Int -> ST s (FunPtr a)

unsafeWrite :: Ix i => STUArray s i (FunPtr a) -> Int -> FunPtr a -> ST s ()

newtype BStr :: * #

Constructors

BStr (Ptr Word16) 

Instances

Show BStr 

Methods

showsPrec :: Int -> BStr -> ShowS #

show :: BStr -> String #

showList :: [BStr] -> ShowS #

Marshal String BStr 

Methods

marshal :: String -> (BStr -> IO c) -> IO c #

Marshal Text BStr 

Methods

marshal :: Text -> (BStr -> IO c) -> IO c #

Unmarshal BStr String 

Methods

unmarshal :: BStr -> IO String #

Unmarshal BStr Text 

Methods

unmarshal :: BStr -> IO Text #

Quotable "string" "System.String" BStr String Source # 

newtype TextBStr Source #

Constructors

TextBStr BStr 

Instances

Marshal Text TextBStr Source # 

Methods

marshal :: Text -> (TextBStr -> IO c) -> IO c #

Unmarshal TextBStr Text Source # 

Methods

unmarshal :: TextBStr -> IO Text #

Quotable "text" "System.String" TextBStr Text Source # 

data Clr name Source #

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.

Constructors

Clr (ClrPtr name) (IORef ()) 

Instances

Quotable a a (ClrPtr a) (Clr a) Source #

All reference types are handled by this instance.

Marshal (Clr n) (ClrPtr n) Source # 

Methods

marshal :: Clr n -> (ClrPtr n -> IO c) -> IO c #

Unmarshal (ClrPtr n) (Clr n) Source # 

Methods

unmarshal :: ClrPtr n -> IO (Clr n) #

newtype ClrPtr name Source #

A pointer to a Clr object. The only way to access the contents is via clr-inline quotations.

Constructors

ClrPtr Int64 

Instances

Quotable a a (ClrPtr a) (Clr a) Source #

All reference types are handled by this instance.

Marshal (Clr n) (ClrPtr n) Source # 

Methods

marshal :: Clr n -> (ClrPtr n -> IO c) -> IO c #

Unmarshal (ClrPtr n) (Clr n) Source # 

Methods

unmarshal :: ClrPtr n -> IO (Clr n) #