[Haskell] ANNOUNCE: AppleScript-0.2.0.1

Reiner Pope reiner.pope at gmail.com
Wed Feb 15 12:29:45 CET 2012


Hello list,

I am pleased to announce a new release of the AppleScript package[1], which supports compiling and running AppleScript code from Haskell, and also supports calling back into Haskell from AppleScript. This release has many new features, including:

* AppleScript can now call back into Haskell, and return a final result to Haskell

* a quasiquoter for writing AppleScript code

* unicode support

Here is an example showcasing the main features:
> {-# LANGUAGE QuasiQuotes #-}
> import Foreign.AppleScript.Rich
> import qualified Data.Text.Lazy    as Text
> import qualified Data.Text.Lazy.IO as Text
>
> main = Text.putStrLn =<< evalScript mainScript
>
> mainScript = [applescript|
>   tell application "System Events"
>     -- Haskell value splices, and Unicode support.
>     display dialog "The value of π is $value{pi :: Double}$."
>
>     -- AppleScript can call back into Haskell.
>     set yourName to text returned of (display dialog "What is your name?" default answer "")
>     display dialog ("Your name in reverse is " & $callback{ \t -> return (Text.reverse t) }$[ yourName ]$)
>
>     -- Splice other AppleScript code into here
>     $applescript{ othergreeter }$
> 
>     -- Return text from AppleScript back to Haskell
>     return "Hello from AppleScript!"
>   end tell
>  |]
>
> othergreeter = [applescript|
>   display dialog "Hello from the other greeter!"
>  |]
With this release, I have taken over maintenance from Wouter Swierstra. Many thanks go to Wouter for his original work on this package.

[1]: http://hackage.haskell.org/package/AppleScript
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell/attachments/20120215/343fd95f/attachment.htm>


More information about the Haskell mailing list