"These widgets can be used to represent a Boolean value. The idea is pretty simple, the widget can be in one of two states which represent the two boolean values.\n",
"\n",
" Checked / On : True\n",
" Unchecked / Off : False"
]
},
{
"cell_type": "code",
"execution_count": 1,
"metadata": {
"collapsed": true
},
"outputs": [],
"source": [
"{-# LANGUAGE OverloadedStrings #-}\n",
"import IHaskell.Display.Widgets\n",
"import Data.Text (pack, unpack)\n",
"import Text.Printf (printf)"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"### Simple demonstration"
]
},
{
"cell_type": "code",
"execution_count": 2,
"metadata": {
"collapsed": false
},
"outputs": [
{
"data": {
"text/plain": []
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
"-- Constructors\n",
"chk <- mkCheckBox\n",
"tgb <- mkToggleButton\n",
"\n",
"-- For demonstration\n",
"o <- mkHTMLWidget"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"Below, we represent one boolean using a checkbox, and the other using a toggle button. The logical and (`&&`) of the two is displayed below."
]
},
{
"cell_type": "code",
"execution_count": 3,
"metadata": {
"collapsed": false
},
"outputs": [
{
"data": {},
"metadata": {},
"output_type": "display_data"
},
{
"data": {},
"metadata": {},
"output_type": "display_data"
},
{
"data": {},
"metadata": {},
"output_type": "display_data"
},
{
"data": {},
"metadata": {},
"output_type": "display_data"
},
{
"data": {},
"metadata": {},
"output_type": "display_data"
},
{
"data": {},
"metadata": {},
"output_type": "display_data"
},
{
"data": {},
"metadata": {},
"output_type": "display_data"
},
{
"data": {},
"metadata": {},
"output_type": "display_data"
},
{
"data": {},
"metadata": {},
"output_type": "display_data"
},
{
"data": {},
"metadata": {},
"output_type": "display_data"
},
{
"data": {},
"metadata": {},
"output_type": "display_data"
},
{
"data": {},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
"-- Display\n",
"chk\n",
"tgb\n",
"o"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"The `BoolValue` field represents the underlying boolean value."
" in setField o SStringValue $ pack $ printf fmt stat (show b)\n",
"\n",
" -- Cosmetic changes\n",
"setField o SDescription \"Bool 1 && Bool 2\"\n",
"setField o SPadding 10\n",
"\n",
" -- And (&&) the two values, and send output to html widget\n",
"setHandler w = setField w SChangeHandler $ do\n",
" b1 <- getField chk SBoolValue\n",
" b2 <- getField tgb SBoolValue\n",
" refresh (b1 && b2)\n",
"\n",
"setHandler chk\n",
"setHandler tgb"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"### Extended example"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"Let's try to create a graphical 8-bit-binary to decimal converter. We'll represent seven bits using `ToggleButton` widgets, and the negative bit using a `CheckBox`. The binary number is represented using 1+7-bit sign-and-magnitude representation for simplicity.\n",
"\n",
"Boxes are used to layout the widgets in an appealing manner, and the output widget is used to display the result."
]
},
{
"cell_type": "code",
"execution_count": 5,
"metadata": {
"collapsed": false
},
"outputs": [],
"source": [
"-- First, some library functions\n",
"import Control.Monad (replicateM, forM_)\n",
"import Data.IORef\n",
"import IHaskell.Display (plain)"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"Now, we create a `CheckBox` and seven `ToggleButton`s."
]
},
{
"cell_type": "code",
"execution_count": 6,
"metadata": {
"collapsed": false
},
"outputs": [
{
"data": {
"text/plain": []
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
"sign <- mkCheckBox\n",
"bits <- replicateM 7 mkToggleButton\n",
"\n",
"setField sign SDescription \"Negative\"\n",
"forM_ bits $ \\t -> do\n",
" setField t SButtonStyle PrimaryButton\n",
" setField t SBorderRadius 20"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"Then we create a `FlexBox` to hold the widgets, and an `HTMLWidget` to display the output."
"This widget can be used to display images given in the form of base64 encoded `Text`. The widget has a `B64Value` field, which can be changed to display images to it. It also has an `ImageFormat` field, which is set to `PNG` by default."
]
},
{
"cell_type": "code",
"execution_count": 21,
"metadata": {
"collapsed": false
},
"outputs": [
{
"data": {
"text/html": [
"<style>/*\n",
"Custom IHaskell CSS.\n",
"*/\n",
"\n",
"/* Styles used for the Hoogle display in the pager */\n",
".hoogle-doc {\n",
" display: block;\n",
" padding-bottom: 1.3em;\n",
" padding-left: 0.4em;\n",
"}\n",
".hoogle-code {\n",
" display: block;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
"}\n",
".hoogle-text {\n",
" display: block;\n",
"}\n",
".hoogle-name {\n",
" color: green;\n",
" font-weight: bold;\n",
"}\n",
".hoogle-head {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-sub {\n",
" display: block;\n",
" margin-left: 0.4em;\n",
"}\n",
".hoogle-package {\n",
" font-weight: bold;\n",
" font-style: italic;\n",
"}\n",
".hoogle-module {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-class {\n",
" font-weight: bold;\n",
"}\n",
"\n",
"/* Styles used for basic displays */\n",
".get-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" display: block;\n",
" white-space: pre-wrap;\n",
"}\n",
"\n",
".show-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" margin-left: 1em;\n",
"}\n",
"\n",
".mono {\n",
" font-family: monospace;\n",
" display: block;\n",
"}\n",
"\n",
".err-msg {\n",
" color: red;\n",
" font-style: italic;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
" display: block;\n",
"}\n",
"\n",
"#unshowable {\n",
" color: red;\n",
" font-weight: bold;\n",
"}\n",
"\n",
".err-msg.in.collapse {\n",
" padding-top: 0.7em;\n",
"}\n",
"\n",
"/* Code that will get highlighted before it is highlighted */\n",
"jpg <- get \"http://imgs.xkcd.com/comics/functional.png\"\n",
"\n",
"img <- mkImageWidget\n",
"setField img SB64Value (encode64 jpg)\n",
"img"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"Replace the call to undefined by the path to an image, and it will be displayed in an image widget."
]
},
{
"cell_type": "code",
"execution_count": 5,
"metadata": {
"collapsed": false
},
"outputs": [
{
"data": {
"text/html": [
"<style>/*\n",
"Custom IHaskell CSS.\n",
"*/\n",
"\n",
"/* Styles used for the Hoogle display in the pager */\n",
".hoogle-doc {\n",
" display: block;\n",
" padding-bottom: 1.3em;\n",
" padding-left: 0.4em;\n",
"}\n",
".hoogle-code {\n",
" display: block;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
"}\n",
".hoogle-text {\n",
" display: block;\n",
"}\n",
".hoogle-name {\n",
" color: green;\n",
" font-weight: bold;\n",
"}\n",
".hoogle-head {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-sub {\n",
" display: block;\n",
" margin-left: 0.4em;\n",
"}\n",
".hoogle-package {\n",
" font-weight: bold;\n",
" font-style: italic;\n",
"}\n",
".hoogle-module {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-class {\n",
" font-weight: bold;\n",
"}\n",
"\n",
"/* Styles used for basic displays */\n",
".get-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" display: block;\n",
" white-space: pre-wrap;\n",
"}\n",
"\n",
".show-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" margin-left: 1em;\n",
"}\n",
"\n",
".mono {\n",
" font-family: monospace;\n",
" display: block;\n",
"}\n",
"\n",
".err-msg {\n",
" color: red;\n",
" font-style: italic;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
" display: block;\n",
"}\n",
"\n",
"#unshowable {\n",
" color: red;\n",
" font-weight: bold;\n",
"}\n",
"\n",
".err-msg.in.collapse {\n",
" padding-top: 0.7em;\n",
"}\n",
"\n",
"/* Code that will get highlighted before it is highlighted */\n",
".highlight-code {\n",
" white-space: pre;\n",
" font-family: monospace;\n",
"}\n",
"\n",
"/* Hlint styles */\n",
".suggestion-warning { \n",
" font-weight: bold;\n",
" color: rgb(200, 130, 0);\n",
"}\n",
".suggestion-error { \n",
" font-weight: bold;\n",
" color: red;\n",
"}\n",
".suggestion-name {\n",
" font-weight: bold;\n",
"}\n",
"</style><span class='err-msg'>Couldn't match type ‘String’ with ‘B.ByteString’<br/>Expected type: B.ByteString -> IHaskell.Display.Base64<br/> Actual type: String -> IHaskell.Display.Base64<br/>In the second argument of ‘(.)’, namely ‘encode64’<br/>In the second argument of ‘(>>=)’, namely ‘setField i SB64Value . encode64’</span>"
],
"text/plain": [
"Couldn't match type ‘String’ with ‘B.ByteString’\n",
" Actual type: String -> IHaskell.Display.Base64\n",
"In the second argument of ‘(.)’, namely ‘encode64’\n",
"In the second argument of ‘(>>=)’, namely ‘setField i SB64Value . encode64’"
]
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
"imgpath = undefined\n",
"\n",
"import qualified Data.ByteString as B\n",
"import IHaskell.Display (encode64)\n",
"\n",
"i <- mkImageWidget\n",
"B.readFile imgpath >>= setField i SB64Value . encode64"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"### The `Selection` Widgets"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"These widgets can be used to select one from many. The `SelectMultiple` widget allows multiple selections, whereas `Dropdown`, `RadioButtons`, `ToggleButtons`, and `Select` only allow one selection."
]
},
{
"cell_type": "code",
"execution_count": 23,
"metadata": {
"collapsed": true
},
"outputs": [],
"source": [
"-- Allows single selection\n",
"tgbs <- mkToggleButtons\n",
"\n",
"-- Allows multiple selections\n",
"msel <- mkSelectMultiple"
]
},
{
"cell_type": "code",
"execution_count": 24,
"metadata": {
"collapsed": false
},
"outputs": [
{
"data": {
"text/plain": []
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
"setField msel SDescription \"Functions to show (One or more)\"\n",
"The `Dropdown`, `RadioButtons` and `Select` widgets behave just like the `ToggleButtons` widget. They have the same properties, and the same functionality."
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"### The Numeric Widgets"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"**NOTE**: The following examples use widgets with `Int` in their names. There are also analogous widgets with `Float` in their names.\n",
"\n",
"As the widgets are the same operationally, only the `Int` widgets are shown."
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"#### `IntText` and `BoundedIntText`"
]
},
{
"cell_type": "code",
"execution_count": 27,
"metadata": {
"collapsed": true
},
"outputs": [],
"source": [
"int <- mkIntText\n",
"bit <- mkBoundedIntText"
]
},
{
"cell_type": "code",
"execution_count": 28,
"metadata": {
"collapsed": false
},
"outputs": [],
"source": [
"int\n",
"bit"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"Both the widgets are similar, but the second one possesses some additional properties."
]
},
{
"cell_type": "code",
"execution_count": 29,
"metadata": {
"collapsed": false
},
"outputs": [
{
"data": {
"text/plain": []
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
"setField bit SMaxInt 20\n",
"setField bit SMinInt 10\n",
"setField bit SChangeHandler (getField bit SIntValue >>= print)"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"Now, the first widget will accept arbitrary input whereas the second one wil accept input the the 10-20 range. For example, try entering large values and hitting return/enter in the second widget."
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"#### `IntSlider` and `IntRangeSlider`"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"Both these widgets are sliders (duh!). `IntSlider` represents a single value, whereas `IntRangeSlider` represents a pair (range) of values."
]
},
{
"cell_type": "code",
"execution_count": 30,
"metadata": {
"collapsed": true
},
"outputs": [],
"source": [
"ins <- mkIntSlider\n",
"irs <- mkIntRangeSlider"
]
},
{
"cell_type": "code",
"execution_count": 31,
"metadata": {
"collapsed": false
},
"outputs": [],
"source": [
"ins\n",
"irs"
]
},
{
"cell_type": "code",
"execution_count": 32,
"metadata": {
"collapsed": false
},
"outputs": [
{
"data": {
"text/plain": [
"(25,75)"
]
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
"getField irs SIntPairValue"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"#### `IntProgress`"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"This widget is meant to be used as a progress bar."
"It is highly recommended that users new to jupyter/ipython take the *User Interface Tour* from the toolbar above (Help -> User Interface Tour)."
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"> This notebook introduces the [IPython widgets](https://github.com/ipython/ipywidgets), as implemented in [IHaskell](https://github.com/gibiansky/IHaskell). The `Button` widget is also demonstrated as a live action example."
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"### The Widget Hierarchy\n",
"\n",
"These are all the widgets available from IPython/Jupyter."
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"#### Uncategorized Widgets\n",
"\n",
"+ Button\n",
"+ Image*Widget*\n",
"+ Output*Widget*\n",
"\n",
"#### Box Widgets\n",
"\n",
"+ Box\n",
"+ FlexBox\n",
"+ Accordion\n",
"+ Tab*Widget*\n",
"\n",
"#### Boolean Widgets\n",
"\n",
"+ CheckBox\n",
"+ ToggleButton\n",
"\n",
"#### Integer Widgets\n",
"\n",
"+ IntText\n",
"+ BoundedIntText\n",
"+ IntProgress\n",
"+ IntSlider\n",
"+ IntRangeSlider\n",
"\n",
"#### Float Widgets\n",
"\n",
"+ FloatText\n",
"+ BoundedFloatText\n",
"+ FloatProgress\n",
"+ FloatSlider\n",
"+ FloatRangeSlider\n",
"\n",
"#### Selection Widgets\n",
"\n",
"+ Selection\n",
"+ Dropdown\n",
"+ RadioButtons\n",
"+ Select\n",
"+ SelectMultiple\n",
"+ ToggleButtons\n",
"\n",
"#### String Widgets\n",
"\n",
"+ HTML*Widget*\n",
"+ Latex*Widget*\n",
"+ TextArea\n",
"+ Text*Widget*"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"### Using Widgets"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"#### Necessary Extensions and Imports\n",
"\n",
"All the widgets and related functions are available from a single module, `IHaskell.Display.Widgets`. It is strongly recommended that users use the `OverloadedStrings` extension, as widgets make extensive use of `Text`."
]
},
{
"cell_type": "code",
"execution_count": 1,
"metadata": {
"collapsed": true
},
"outputs": [],
"source": [
"{-# LANGUAGE OverloadedStrings #-}\n",
"import IHaskell.Display.Widgets"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"The module can be imported unqualified. Widgets with common names, such as `Text`, `Image` etc. have a `-Widget` suffix to prevent name collisions."
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"#### Widget interface\n",
"\n",
"Each widget has different properties, but the surface level API is the same.\n",
"\n",
"Every widget has:\n",
"\n",
"1. A constructor:\n",
" An `IO <widget>` value/function of the form `mk<widget_name>`.\n",
"2. A set of properties, which can be manipulated using `setField` and `getField`.\n",
"\n",
"The `setField` and `getField` functions have nasty type signatures, but they can be used by just intuitively understanding them."
]
},
{
"cell_type": "code",
"execution_count": 2,
"metadata": {
"collapsed": false
},
"outputs": [
{
"data": {
"text/html": [
"<style>/*\n",
"Custom IHaskell CSS.\n",
"*/\n",
"\n",
"/* Styles used for the Hoogle display in the pager */\n",
".hoogle-doc {\n",
" display: block;\n",
" padding-bottom: 1.3em;\n",
" padding-left: 0.4em;\n",
"}\n",
".hoogle-code {\n",
" display: block;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
"}\n",
".hoogle-text {\n",
" display: block;\n",
"}\n",
".hoogle-name {\n",
" color: green;\n",
" font-weight: bold;\n",
"}\n",
".hoogle-head {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-sub {\n",
" display: block;\n",
" margin-left: 0.4em;\n",
"}\n",
".hoogle-package {\n",
" font-weight: bold;\n",
" font-style: italic;\n",
"}\n",
".hoogle-module {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-class {\n",
" font-weight: bold;\n",
"}\n",
"\n",
"/* Styles used for basic displays */\n",
".get-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" display: block;\n",
" white-space: pre-wrap;\n",
"}\n",
"\n",
".show-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" margin-left: 1em;\n",
"}\n",
"\n",
".mono {\n",
" font-family: monospace;\n",
" display: block;\n",
"}\n",
"\n",
".err-msg {\n",
" color: red;\n",
" font-style: italic;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
" display: block;\n",
"}\n",
"\n",
"#unshowable {\n",
" color: red;\n",
" font-weight: bold;\n",
"}\n",
"\n",
".err-msg.in.collapse {\n",
" padding-top: 0.7em;\n",
"}\n",
"\n",
"/* Code that will get highlighted before it is highlighted */\n",
".highlight-code {\n",
" white-space: pre;\n",
" font-family: monospace;\n",
"}\n",
"\n",
"/* Hlint styles */\n",
".suggestion-warning { \n",
" font-weight: bold;\n",
" color: rgb(200, 130, 0);\n",
"}\n",
".suggestion-error { \n",
" font-weight: bold;\n",
" color: red;\n",
"}\n",
".suggestion-name {\n",
" font-weight: bold;\n",
"}\n",
"</style><span class='get-type'>setField :: forall (w :: WidgetType) (f :: Field). (RElem f (WidgetFields w) (RIndex f (WidgetFields w)), ToPairs (Attr f), IHaskellWidget (IPythonWidget w)) => IPythonWidget w -> SField f -> FieldType f -> IO ()</span>"
],
"text/plain": [
"setField :: forall (w :: WidgetType) (f :: Field). (RElem f (WidgetFields w) (RIndex f (WidgetFields w)), ToPairs (Attr f), IHaskellWidget (IPythonWidget w)) => IPythonWidget w -> SField f -> FieldType f -> IO ()"
]
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
":t setField"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"The `setField` function takes three arguments:\n",
"\n",
"1. A widget\n",
"2. A `singleton` for a `Field`\n",
"3. A value for the `Field`"
]
},
{
"cell_type": "code",
"execution_count": 3,
"metadata": {
"collapsed": false,
"scrolled": true
},
"outputs": [
{
"data": {
"text/html": [
"<style>/*\n",
"Custom IHaskell CSS.\n",
"*/\n",
"\n",
"/* Styles used for the Hoogle display in the pager */\n",
".hoogle-doc {\n",
" display: block;\n",
" padding-bottom: 1.3em;\n",
" padding-left: 0.4em;\n",
"}\n",
".hoogle-code {\n",
" display: block;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
"}\n",
".hoogle-text {\n",
" display: block;\n",
"}\n",
".hoogle-name {\n",
" color: green;\n",
" font-weight: bold;\n",
"}\n",
".hoogle-head {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-sub {\n",
" display: block;\n",
" margin-left: 0.4em;\n",
"}\n",
".hoogle-package {\n",
" font-weight: bold;\n",
" font-style: italic;\n",
"}\n",
".hoogle-module {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-class {\n",
" font-weight: bold;\n",
"}\n",
"\n",
"/* Styles used for basic displays */\n",
".get-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" display: block;\n",
" white-space: pre-wrap;\n",
"}\n",
"\n",
".show-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" margin-left: 1em;\n",
"}\n",
"\n",
".mono {\n",
" font-family: monospace;\n",
" display: block;\n",
"}\n",
"\n",
".err-msg {\n",
" color: red;\n",
" font-style: italic;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
" display: block;\n",
"}\n",
"\n",
"#unshowable {\n",
" color: red;\n",
" font-weight: bold;\n",
"}\n",
"\n",
".err-msg.in.collapse {\n",
" padding-top: 0.7em;\n",
"}\n",
"\n",
"/* Code that will get highlighted before it is highlighted */\n",
".highlight-code {\n",
" white-space: pre;\n",
" font-family: monospace;\n",
"}\n",
"\n",
"/* Hlint styles */\n",
".suggestion-warning { \n",
" font-weight: bold;\n",
" color: rgb(200, 130, 0);\n",
"}\n",
".suggestion-error { \n",
" font-weight: bold;\n",
" color: red;\n",
"}\n",
".suggestion-name {\n",
" font-weight: bold;\n",
"}\n",
"</style><span class='get-type'>getField :: forall (w :: WidgetType) (f :: Field). RElem f (WidgetFields w) (RIndex f (WidgetFields w)) => IPythonWidget w -> SField f -> IO (FieldType f)</span>"
],
"text/plain": [
"getField :: forall (w :: WidgetType) (f :: Field). RElem f (WidgetFields w) (RIndex f (WidgetFields w)) => IPythonWidget w -> SField f -> IO (FieldType f)"
]
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
":t getField"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"The `getField` function takes a `Widget`, and a singleton for a `Field` and returns the value of that `Field` for the `Widget`."
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"Another utility function is `properties`, which shows all properties of a widget."
]
},
{
"cell_type": "code",
"execution_count": 4,
"metadata": {
"collapsed": false
},
"outputs": [
{
"data": {
"text/html": [
"<style>/*\n",
"Custom IHaskell CSS.\n",
"*/\n",
"\n",
"/* Styles used for the Hoogle display in the pager */\n",
".hoogle-doc {\n",
" display: block;\n",
" padding-bottom: 1.3em;\n",
" padding-left: 0.4em;\n",
"}\n",
".hoogle-code {\n",
" display: block;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
"}\n",
".hoogle-text {\n",
" display: block;\n",
"}\n",
".hoogle-name {\n",
" color: green;\n",
" font-weight: bold;\n",
"}\n",
".hoogle-head {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-sub {\n",
" display: block;\n",
" margin-left: 0.4em;\n",
"}\n",
".hoogle-package {\n",
" font-weight: bold;\n",
" font-style: italic;\n",
"}\n",
".hoogle-module {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-class {\n",
" font-weight: bold;\n",
"}\n",
"\n",
"/* Styles used for basic displays */\n",
".get-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" display: block;\n",
" white-space: pre-wrap;\n",
"}\n",
"\n",
".show-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" margin-left: 1em;\n",
"}\n",
"\n",
".mono {\n",
" font-family: monospace;\n",
" display: block;\n",
"}\n",
"\n",
".err-msg {\n",
" color: red;\n",
" font-style: italic;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
" display: block;\n",
"}\n",
"\n",
"#unshowable {\n",
" color: red;\n",
" font-weight: bold;\n",
"}\n",
"\n",
".err-msg.in.collapse {\n",
" padding-top: 0.7em;\n",
"}\n",
"\n",
"/* Code that will get highlighted before it is highlighted */\n",
".highlight-code {\n",
" white-space: pre;\n",
" font-family: monospace;\n",
"}\n",
"\n",
"/* Hlint styles */\n",
".suggestion-warning { \n",
" font-weight: bold;\n",
" color: rgb(200, 130, 0);\n",
"}\n",
".suggestion-error { \n",
" font-weight: bold;\n",
" color: red;\n",
"}\n",
".suggestion-name {\n",
" font-weight: bold;\n",
"}\n",
"</style><span class='get-type'>properties :: forall (w :: WidgetType). IPythonWidget w -> IO [Field]</span>"
],
"text/plain": [
"properties :: forall (w :: WidgetType). IPythonWidget w -> IO [Field]"
]
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
":t properties"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"#### Singletons\n",
"\n",
"For the purpose of using widgets, singletons are a way of representing properties. To represent a `Field`, we use its singleton, which is written as `S<fieldname>`, i.e `S` followed by the field.\n",
"\n",
"For example, the singleton for `Description` would be `SDescription`."
]
},
{
"cell_type": "code",
"execution_count": 5,
"metadata": {
"collapsed": false
},
"outputs": [
{
"data": {
"text/html": [
"<style>/*\n",
"Custom IHaskell CSS.\n",
"*/\n",
"\n",
"/* Styles used for the Hoogle display in the pager */\n",
".hoogle-doc {\n",
" display: block;\n",
" padding-bottom: 1.3em;\n",
" padding-left: 0.4em;\n",
"}\n",
".hoogle-code {\n",
" display: block;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
"}\n",
".hoogle-text {\n",
" display: block;\n",
"}\n",
".hoogle-name {\n",
" color: green;\n",
" font-weight: bold;\n",
"}\n",
".hoogle-head {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-sub {\n",
" display: block;\n",
" margin-left: 0.4em;\n",
"}\n",
".hoogle-package {\n",
" font-weight: bold;\n",
" font-style: italic;\n",
"}\n",
".hoogle-module {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-class {\n",
" font-weight: bold;\n",
"}\n",
"\n",
"/* Styles used for basic displays */\n",
".get-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" display: block;\n",
" white-space: pre-wrap;\n",
"}\n",
"\n",
".show-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" margin-left: 1em;\n",
"}\n",
"\n",
".mono {\n",
" font-family: monospace;\n",
" display: block;\n",
"}\n",
"\n",
".err-msg {\n",
" color: red;\n",
" font-style: italic;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
" display: block;\n",
"}\n",
"\n",
"#unshowable {\n",
" color: red;\n",
" font-weight: bold;\n",
"}\n",
"\n",
".err-msg.in.collapse {\n",
" padding-top: 0.7em;\n",
"}\n",
"\n",
"/* Code that will get highlighted before it is highlighted */\n",
"/* Styles used for the Hoogle display in the pager */\n",
".hoogle-doc {\n",
" display: block;\n",
" padding-bottom: 1.3em;\n",
" padding-left: 0.4em;\n",
"}\n",
".hoogle-code {\n",
" display: block;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
"}\n",
".hoogle-text {\n",
" display: block;\n",
"}\n",
".hoogle-name {\n",
" color: green;\n",
" font-weight: bold;\n",
"}\n",
".hoogle-head {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-sub {\n",
" display: block;\n",
" margin-left: 0.4em;\n",
"}\n",
".hoogle-package {\n",
" font-weight: bold;\n",
" font-style: italic;\n",
"}\n",
".hoogle-module {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-class {\n",
" font-weight: bold;\n",
"}\n",
"\n",
"/* Styles used for basic displays */\n",
".get-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" display: block;\n",
" white-space: pre-wrap;\n",
"}\n",
"\n",
".show-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" margin-left: 1em;\n",
"}\n",
"\n",
".mono {\n",
" font-family: monospace;\n",
" display: block;\n",
"}\n",
"\n",
".err-msg {\n",
" color: red;\n",
" font-style: italic;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
" display: block;\n",
"}\n",
"\n",
"#unshowable {\n",
" color: red;\n",
" font-weight: bold;\n",
"}\n",
"\n",
".err-msg.in.collapse {\n",
" padding-top: 0.7em;\n",
"}\n",
"\n",
"/* Code that will get highlighted before it is highlighted */\n",
".highlight-code {\n",
" white-space: pre;\n",
" font-family: monospace;\n",
"}\n",
"\n",
"/* Hlint styles */\n",
".suggestion-warning { \n",
" font-weight: bold;\n",
" color: rgb(200, 130, 0);\n",
"}\n",
".suggestion-error { \n",
" font-weight: bold;\n",
" color: red;\n",
"}\n",
".suggestion-name {\n",
" font-weight: bold;\n",
"}\n",
"</style><span class='get-type'>SDescription :: Sing 'Description</span>"
],
"text/plain": [
"SDescription :: Sing 'Description"
]
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
":t Description\n",
":t SDescription"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"**PS:** Don't blame me for the naming `:)`. The singletons are generated using Template Haskell."
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"#### Displaying Widgets\n",
"\n",
"IHaskell automatically displays anything *displayable* given to it directly."
]
},
{
"cell_type": "code",
"execution_count": 6,
"metadata": {
"collapsed": false
},
"outputs": [
{
"data": {
"text/plain": [
"3"
]
},
"metadata": {},
"output_type": "display_data"
},
{
"data": {
"text/plain": [
"\"abc\""
]
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
"-- Showables\n",
"1 + 2\n",
"\"abc\""
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"Widgets can either be displayed this way, or explicitly using the `display` function from `IHaskell.Display`."
]
},
{
"cell_type": "code",
"execution_count": 7,
"metadata": {
"collapsed": false
},
"outputs": [
{
"data": {
"text/html": [
"<style>/*\n",
"Custom IHaskell CSS.\n",
"*/\n",
"\n",
"/* Styles used for the Hoogle display in the pager */\n",
".hoogle-doc {\n",
" display: block;\n",
" padding-bottom: 1.3em;\n",
" padding-left: 0.4em;\n",
"}\n",
".hoogle-code {\n",
" display: block;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
"}\n",
".hoogle-text {\n",
" display: block;\n",
"}\n",
".hoogle-name {\n",
" color: green;\n",
" font-weight: bold;\n",
"}\n",
".hoogle-head {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-sub {\n",
" display: block;\n",
" margin-left: 0.4em;\n",
"}\n",
".hoogle-package {\n",
" font-weight: bold;\n",
" font-style: italic;\n",
"}\n",
".hoogle-module {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-class {\n",
" font-weight: bold;\n",
"}\n",
"\n",
"/* Styles used for basic displays */\n",
".get-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" display: block;\n",
" white-space: pre-wrap;\n",
"}\n",
"\n",
".show-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" margin-left: 1em;\n",
"}\n",
"\n",
".mono {\n",
" font-family: monospace;\n",
" display: block;\n",
"}\n",
"\n",
".err-msg {\n",
" color: red;\n",
" font-style: italic;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
" display: block;\n",
"}\n",
"\n",
"#unshowable {\n",
" color: red;\n",
" font-weight: bold;\n",
"}\n",
"\n",
".err-msg.in.collapse {\n",
" padding-top: 0.7em;\n",
"}\n",
"\n",
"/* Code that will get highlighted before it is highlighted */\n",
".highlight-code {\n",
" white-space: pre;\n",
" font-family: monospace;\n",
"}\n",
"\n",
"/* Hlint styles */\n",
".suggestion-warning { \n",
" font-weight: bold;\n",
" color: rgb(200, 130, 0);\n",
"}\n",
".suggestion-error { \n",
" font-weight: bold;\n",
" color: red;\n",
"}\n",
".suggestion-name {\n",
" font-weight: bold;\n",
"}\n",
"</style><span class='get-type'>display :: forall a. IHaskellDisplay a => a -> IO Display</span>"
],
"text/plain": [
"display :: forall a. IHaskellDisplay a => a -> IO Display"
]
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
"import IHaskell.Display\n",
":t display"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"#### Multiple displays\n",
"\n",
"A widget can be displayed multiple times. All these *views* are representations of a single object, and thus are linked.\n",
"\n",
"When a widget is created, a model representing it is created in the frontend. This model is used by all the views, and any modification to it propagates to all of them."
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"#### Closing widgets\n",
"\n",
"Widgets can be closed using the `closeWidget` function."
]
},
{
"cell_type": "code",
"execution_count": 8,
"metadata": {
"collapsed": false
},
"outputs": [
{
"data": {
"text/html": [
"<style>/*\n",
"Custom IHaskell CSS.\n",
"*/\n",
"\n",
"/* Styles used for the Hoogle display in the pager */\n",
".hoogle-doc {\n",
" display: block;\n",
" padding-bottom: 1.3em;\n",
" padding-left: 0.4em;\n",
"}\n",
".hoogle-code {\n",
" display: block;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
"}\n",
".hoogle-text {\n",
" display: block;\n",
"}\n",
".hoogle-name {\n",
" color: green;\n",
" font-weight: bold;\n",
"}\n",
".hoogle-head {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-sub {\n",
" display: block;\n",
" margin-left: 0.4em;\n",
"}\n",
".hoogle-package {\n",
" font-weight: bold;\n",
" font-style: italic;\n",
"}\n",
".hoogle-module {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-class {\n",
" font-weight: bold;\n",
"}\n",
"\n",
"/* Styles used for basic displays */\n",
".get-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" display: block;\n",
" white-space: pre-wrap;\n",
"}\n",
"\n",
".show-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" margin-left: 1em;\n",
"}\n",
"\n",
".mono {\n",
" font-family: monospace;\n",
" display: block;\n",
"}\n",
"\n",
".err-msg {\n",
" color: red;\n",
" font-style: italic;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
" display: block;\n",
"}\n",
"\n",
"#unshowable {\n",
" color: red;\n",
" font-weight: bold;\n",
"}\n",
"\n",
".err-msg.in.collapse {\n",
" padding-top: 0.7em;\n",
"}\n",
"\n",
"/* Code that will get highlighted before it is highlighted */\n",
".highlight-code {\n",
" white-space: pre;\n",
" font-family: monospace;\n",
"}\n",
"\n",
"/* Hlint styles */\n",
".suggestion-warning { \n",
" font-weight: bold;\n",
" color: rgb(200, 130, 0);\n",
"}\n",
".suggestion-error { \n",
" font-weight: bold;\n",
" color: red;\n",
"}\n",
".suggestion-name {\n",
" font-weight: bold;\n",
"}\n",
"</style><span class='get-type'>closeWidget :: forall w. IHaskellWidget w => w -> IO ()</span>"
],
"text/plain": [
"closeWidget :: forall w. IHaskellWidget w => w -> IO ()"
]
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
":t closeWidget"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"### Our first widget: `Button`"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"Let's play with buttons as a starting example:\n",
"\n",
"As noted before, all widgets have a constructor of the form `mk<Widget>`. Thus, to create a `Button`, we use `mkButton`."
]
},
{
"cell_type": "code",
"execution_count": 9,
"metadata": {
"collapsed": false
},
"outputs": [
{
"data": {
"text/html": [
"<style>/*\n",
"Custom IHaskell CSS.\n",
"*/\n",
"\n",
"/* Styles used for the Hoogle display in the pager */\n",
".hoogle-doc {\n",
" display: block;\n",
" padding-bottom: 1.3em;\n",
" padding-left: 0.4em;\n",
"}\n",
".hoogle-code {\n",
" display: block;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
"}\n",
".hoogle-text {\n",
" display: block;\n",
"}\n",
".hoogle-name {\n",
" color: green;\n",
" font-weight: bold;\n",
"}\n",
".hoogle-head {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-sub {\n",
" display: block;\n",
" margin-left: 0.4em;\n",
"}\n",
".hoogle-package {\n",
" font-weight: bold;\n",
" font-style: italic;\n",
"}\n",
".hoogle-module {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-class {\n",
" font-weight: bold;\n",
"}\n",
"\n",
"/* Styles used for basic displays */\n",
".get-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" display: block;\n",
" white-space: pre-wrap;\n",
"}\n",
"\n",
".show-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" margin-left: 1em;\n",
"}\n",
"\n",
".mono {\n",
" font-family: monospace;\n",
" display: block;\n",
"}\n",
"\n",
".err-msg {\n",
" color: red;\n",
" font-style: italic;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
" display: block;\n",
"}\n",
"\n",
"#unshowable {\n",
" color: red;\n",
" font-weight: bold;\n",
"}\n",
"\n",
".err-msg.in.collapse {\n",
" padding-top: 0.7em;\n",
"}\n",
"\n",
"/* Code that will get highlighted before it is highlighted */\n",
"Widgets can be displayed by just entering them into a cell."
]
},
{
"cell_type": "code",
"execution_count": 10,
"metadata": {
"collapsed": false
},
"outputs": [],
"source": [
"button -- Display the button"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"To view a widget's properties, we use the `properties` function:"
]
},
{
"cell_type": "code",
"execution_count": 11,
"metadata": {
"collapsed": false,
"scrolled": false
},
"outputs": [
{
"data": {
"text/plain": [
"ViewModule\n",
"ViewName\n",
"MsgThrottle\n",
"Version\n",
"DisplayHandler\n",
"Visible\n",
"CSS\n",
"DOMClasses\n",
"Width\n",
"Height\n",
"Padding\n",
"Margin\n",
"Color\n",
"BackgroundColor\n",
"BorderColor\n",
"BorderWidth\n",
"BorderRadius\n",
"BorderStyle\n",
"FontStyle\n",
"FontWeight\n",
"FontSize\n",
"FontFamily\n",
"Description\n",
"Tooltip\n",
"Disabled\n",
"Icon\n",
"ButtonStyle\n",
"ClickHandler"
]
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
"-- The button widget has many properties.\n",
"properties button >>= mapM_ print"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"The properties shown above are actually types, and we have to use singletons to pass them to `setField`. Let's try making the button widget wider. As mentioned before, we can create a singleton by just pre-pending a `Field` with an uppercase `S`."
]
},
{
"cell_type": "code",
"execution_count": 12,
"metadata": {
"collapsed": false
},
"outputs": [],
"source": [
"-- 250 pixels wide\n",
"-- Singleton for Width == (SWidth :: SField Width)\n",
"setField button SWidth 250"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"There is a lot that can be customized. For example:"
]
},
{
"cell_type": "code",
"execution_count": 13,
"metadata": {
"collapsed": false,
"scrolled": true
},
"outputs": [
{
"data": {
"text/plain": []
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
"setField button SDescription \"Click Me (._.\\\")\"\n",
"setField button SButtonStyle SuccessButton\n",
"setField button SBorderStyle RidgeBorder\n",
"setField button SBorderWidth 20\n",
"setField button SBorderRadius 30\n",
"setField button SPadding 10\n",
"setField button SHeight 125\n",
"setField button SFontFamily \"cursive\"\n",
"setField button SFontSize 30"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"The button widget also provides a click handler. We can make it do anything, except console input."
"**NOTE**: Only the `Int` widgets are shown in this notebook. The `Float` widgets are the same as their `Int` counterparts, but hold `Float`s instead of `Int`s."
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"#### `IntText` and `BoundedIntText`"
]
},
{
"cell_type": "code",
"execution_count": 1,
"metadata": {
"collapsed": true
},
"outputs": [],
"source": [
"int <- mkIntText\n",
"int"
]
},
{
"cell_type": "code",
"execution_count": 2,
"metadata": {
"collapsed": false
},
"outputs": [],
"source": [
"bit <- mkBoundedIntText\n",
"bit"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"Both the widgets are similar, but the second one possesses some additional properties."
]
},
{
"cell_type": "code",
"execution_count": 29,
"metadata": {
"collapsed": false
},
"outputs": [
{
"data": {
"text/plain": []
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
"setField bit SMaxInt 20\n",
"setField bit SMinInt 10\n",
"setField bit SChangeHandler (getField bit SIntValue >>= print)"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"Now, the first widget will accept arbitrary input whereas the second one wil accept input the the 10-20 range. For example, try entering large values and hitting return/enter in the second widget."
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"#### `IntSlider` and `IntRangeSlider`"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"Both these widgets are sliders (duh!). `IntSlider` represents a single value, whereas `IntRangeSlider` represents a pair (range) of values."
]
},
{
"cell_type": "code",
"execution_count": 30,
"metadata": {
"collapsed": true
},
"outputs": [],
"source": [
"ins <- mkIntSlider\n",
"irs <- mkIntRangeSlider"
]
},
{
"cell_type": "code",
"execution_count": 31,
"metadata": {
"collapsed": false
},
"outputs": [],
"source": [
"ins\n",
"irs"
]
},
{
"cell_type": "code",
"execution_count": 32,
"metadata": {
"collapsed": false
},
"outputs": [
{
"data": {
"text/plain": [
"(25,75)"
]
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
"getField irs SIntPairValue"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"#### `IntProgress`"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"This widget is meant to be used as a progress bar."
"These widgets can be used to choose between multiple alternatives. The `SelectMultiple` widget allows multiple selections, whereas `Dropdown`, `RadioButtons`, `ToggleButtons`, and `Select` only allow one selection."
]
},
{
"cell_type": "code",
"execution_count": 1,
"metadata": {
"collapsed": true
},
"outputs": [],
"source": [
"{-# LANGUAGE OverloadedStrings #-}\n",
"import IHaskell.Display.Widgets"
]
},
{
"cell_type": "code",
"execution_count": 2,
"metadata": {
"collapsed": true
},
"outputs": [],
"source": [
"-- Allows single selection\n",
"tgbs <- mkToggleButtons\n",
"\n",
"-- Allows multiple selections\n",
"msel <- mkSelectMultiple"
]
},
{
"cell_type": "code",
"execution_count": 3,
"metadata": {
"collapsed": false
},
"outputs": [
{
"data": {
"text/plain": []
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
"setField msel SDescription \"Functions to show (One or more)\"\n",
"The `Dropdown`, `RadioButtons` and `Select` widgets behave just like the `ToggleButtons` widget. They have the same properties, and the same functionality."
"/* Styles used for the Hoogle display in the pager */\n",
".hoogle-doc {\n",
" display: block;\n",
" padding-bottom: 1.3em;\n",
" padding-left: 0.4em;\n",
"}\n",
".hoogle-code {\n",
" display: block;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
"}\n",
".hoogle-text {\n",
" display: block;\n",
"}\n",
".hoogle-name {\n",
" color: green;\n",
" font-weight: bold;\n",
"}\n",
".hoogle-head {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-sub {\n",
" display: block;\n",
" margin-left: 0.4em;\n",
"}\n",
".hoogle-package {\n",
" font-weight: bold;\n",
" font-style: italic;\n",
"}\n",
".hoogle-module {\n",
" font-weight: bold;\n",
"}\n",
".hoogle-class {\n",
" font-weight: bold;\n",
"}\n",
"\n",
"/* Styles used for basic displays */\n",
".get-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" display: block;\n",
" white-space: pre-wrap;\n",
"}\n",
"\n",
".show-type {\n",
" color: green;\n",
" font-weight: bold;\n",
" font-family: monospace;\n",
" margin-left: 1em;\n",
"}\n",
"\n",
".mono {\n",
" font-family: monospace;\n",
" display: block;\n",
"}\n",
"\n",
".err-msg {\n",
" color: red;\n",
" font-style: italic;\n",
" font-family: monospace;\n",
" white-space: pre;\n",
" display: block;\n",
"}\n",
"\n",
"#unshowable {\n",
" color: red;\n",
" font-weight: bold;\n",
"}\n",
"\n",
".err-msg.in.collapse {\n",
" padding-top: 0.7em;\n",
"}\n",
"\n",
"/* Code that will get highlighted before it is highlighted */\n",
".highlight-code {\n",
" white-space: pre;\n",
" font-family: monospace;\n",
"}\n",
"\n",
"/* Hlint styles */\n",
".suggestion-warning { \n",
" font-weight: bold;\n",
" color: rgb(200, 130, 0);\n",
"}\n",
".suggestion-error { \n",
" font-weight: bold;\n",
" color: red;\n",
"}\n",
".suggestion-name {\n",
" font-weight: bold;\n",
"}\n",
"</style><span class='get-type'>SStringValue :: Sing 'StringValue</span>"
],
"text/plain": [
"SStringValue :: Sing 'StringValue"
]
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
":t StringValue\n",
":t SStringValue -- singleton"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"### HTML and Latex"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"The `HTMLWidget` and `LatexWidget` display `Text` as rich formatted *HTML* and *LaTeX* respectively."
]
},
{
"cell_type": "code",
"execution_count": 4,
"metadata": {
"collapsed": true
},
"outputs": [],
"source": [
"-- Display the widgets\n",
"html\n",
"latex"
]
},
{
"cell_type": "code",
"execution_count": 5,
"metadata": {
"collapsed": false
},
"outputs": [],
"source": [
"-- Set some html string\n",
"setField html SStringValue \"<b>Bold</b>\""
]
},
{
"cell_type": "code",
"execution_count": 6,
"metadata": {
"collapsed": false
},
"outputs": [],
"source": [
"-- Set some latex string\n",
"setField latex SStringValue \"$x + y$\""
]
},
{
"cell_type": "code",
"execution_count": 7,
"metadata": {
"collapsed": true
},
"outputs": [],
"source": [
"-- The default width of LatexWidget is somewhat small\n",
"setField latex SWidth 400"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"We can also add some padding to the widgets."
]
},
{
"cell_type": "code",
"execution_count": 8,
"metadata": {
"collapsed": false
},
"outputs": [],
"source": [
"setField html SPadding 10\n",
"setField latex SPadding 10"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"### `TextWidget` and `TextArea`"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"First, let's see what they look like:"
]
},
{
"cell_type": "code",
"execution_count": 9,
"metadata": {
"collapsed": false
},
"outputs": [],
"source": [
"text\n",
"area"
]
},
{
"cell_type": "code",
"execution_count": 10,
"metadata": {
"collapsed": false,
"scrolled": true
},
"outputs": [
{
"data": {
"text/plain": []
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
"-- Some padding\n",
"setField text SPadding 5"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"The `TextWidget` and `TextArea` also have a `Placeholder` property, which represents the text displayed in empty widgets."
]
},
{
"cell_type": "code",
"execution_count": 11,
"metadata": {
"collapsed": false
},
"outputs": [
{
"data": {
"text/plain": []
},
"metadata": {},
"output_type": "display_data"
}
],
"source": [
"setField text SPlaceholder \"Enter your text here...\"\n",
"setField area SPlaceholder \"Parsed output will appear here...\""
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"Both the widgets also accept input. The `StringValue` of the widget is automatically updated on every change to the widget. Additionally, the `TextWidget` also has a `SubmitHandler` which is triggered on hitting the return/enter key."
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"Below we set up the `TextWidget` and `TextArea` for parsing phone numbers using parsec. The `TextWidget` is used to recieve input, and the `TextArea` is used to display output."
]
},
{
"cell_type": "code",
"execution_count": 12,
"metadata": {
"collapsed": true
},
"outputs": [],
"source": [
"-- Import parsec and other required libraries\n",
"\n",
"import Text.Parsec\n",
"import Text.Parsec.String\n",
"import Data.Text (pack, unpack)\n",
"import Control.Applicative ((<$>))"
]
},
{
"cell_type": "markdown",
"metadata": {},
"source": [
"Now, we can write some parsers:"
]
},
{
"cell_type": "code",
"execution_count": 13,
"metadata": {
"collapsed": true
},
"outputs": [],
"source": [
"-- Parse a single digit\n",
"digit :: Parser Char\n",
"digit = oneOf ['0'..'9']\n",
"\n",
"-- Parse a multi-digit number.\n",
"number :: Parser Integer\n",
"number = do\n",
" digits <- many1 digit -- At least one digit\n",
" return (read digits) -- Convert [Char] to Integer\n",
" \n",
"-- Parse a country code, starting with a +.\n",
"countryCode :: Parser Integer\n",
"countryCode = do\n",
" char '+'\n",
" number\n",
" \n",
"-- Parse an area code, optionally with parentheses.\n",