Difference between revisions of "Tangible Value"

From HaskellWiki
Jump to navigation Jump to search
(Changed category from "Interfaces" to "User interfaces")
(47 intermediate revisions by 5 users not shown)
Line 1: Line 1:
  +
[[Category:User interfaces]]
  +
[[Category:IO]]
  +
[[Category:Arrow]]
  +
[[Category:Libraries]]
  +
[[Category:Packages]]
  +
 
== Abstract ==
 
== Abstract ==
   
'''TV''' is a library for composing ''tangible values'' ("TVs"), i.e., values that carry along external interfaces. In particular, TVs can be composed to create new TVs, ''and'' they can be directly executed with a friendly GUI, a process that reads and writes character streams, or many other kinds interfaces. Values and interfaces are ''combined'' for direct use, and ''separable'' for composition.
 
   
  +
'''TV''' is a library for composing ''tangible values'' ("TVs"), i.e., values that carry along external interfaces. In particular, TVs can be composed to create new TVs, ''and'' they can be directly executed with a friendly GUI, a process that reads and writes character streams, or many other kinds interfaces. Values and interfaces are ''combined'' for direct use, and ''separable'' for composition. This combination makes for software that is ''ready to use and ready to reuse''.
TV is for creating software that is ''ready to use and ready to reuse''.
 
  +
  +
TV can be thought of as a simple functional formulation of the Model-View-Controller pattern. (My thanks to an anonymous ICFP referee for pointing out this connection.) The value part of a TV is the ''model'', and the "interface" part, or "output" as it is called below, is the ''viewer''. Outputs are built up compositionally from other outputs and from inputs (the ''controllers''), as described below.
  +
  +
Besides this wiki page, here are more ways to learn about TV:
  +
* Visit the [http://hackage.haskell.org/package/project-foo Hackage page] for library documentation and to download & install.
  +
* Or install with <tt>cabal install project-foo</tt>.
  +
* See the use of TV in [[Eros]].
  +
  +
As of version 0.2, I have moved the GUI functionality out of TV and into a small new package [[GuiTV]]. I moved it out to eliminate the dependency of core TV on [[Phooey]] and hence on [[wxHaskell]], as the latter can be difficult to install. The GUI examples below require [[GuiTV]].
  +
  +
GuiTV (better named "wxTV") is bit-rotten. There is also a very similar [http://hackage.haskell.org/package/GtkTV package to generate Gtk-based GUIs].
   
  +
I'd love to hear your comments at the [[Talk:TV]] page.
Beside this page, here are some ways to explore TV:
 
* [http://darcs.haskell.org/packages/TV/doc/html Read the Haddock docs] (with source code, additional examples, and Comment/Talk links)
 
* Get the code repository: '''<tt>darcs get http://darcs.haskell.org/packages/TV</tt>'''
 
* Or grab a [http://darcs.haskell.org/packages/TV/dist distribution tarball].
 
   
== Tangible values ==
+
== First Example ==
   
As a first example, here is a tangible reverse function:
+
Here is a tangible reverse function:
   
 
<haskell>
 
<haskell>
Line 21: Line 34:
 
The <hask>tv</hask> function combines an interface and a value. In this example, the interface is the default for string functions, wrapped with the title "reverse".
 
The <hask>tv</hask> function combines an interface and a value. In this example, the interface is the default for string functions, wrapped with the title "reverse".
   
TV "interfaces" are more than just GUIs. Here are two different renderings of <hask>reverseT</hask>. (User input is shown <u>underlined</u> in the <hask>runIO</hask> version).
+
TV "interfaces" are more than just GUIs. Here are two different renderings of <hask>reverseT</hask>. (User input is shown <tt><b><i>in italics</i></b></tt> in the <hask>runIO</hask> version).
   
 
Running:
 
Running:
Line 31: Line 44:
 
| style="padding:20px;" |
 
| style="padding:20px;" |
 
*Examples> runIO reverseT
 
*Examples> runIO reverseT
reverse: <u>Hello, reversible world.</u>
+
reverse: <b><i>Hello, reversible world.</i></b>
 
.dlrow elbisrever ,olleH
 
.dlrow elbisrever ,olleH
 
*Examples>
 
*Examples>
Line 37: Line 50:
 
</blockquote>
 
</blockquote>
   
  +
We'll see [[#The_general_story|later]] that "<hask>runUI</hask>" and "<hask>runIO</hask>" are both type-specialized synonyms for a more general function.
=== Outputs ===
 
   
  +
== Outputs ==
What I've been calling an "interface" is a value of type <hask>COutput a</hask> for a type <hask>a</hask> (for <hask>reverseT</hask>, <hask>a == String->String</hask>). (The reason for the <hask>C</hask> prefix is explained below.) At the heart of TV is a small algebra for constructing these outputs. Weve already seen one output function, <hask>oTitle</hask>. Another one is <hask>showOut</hask>, which is an output for all <hask>Show</hask> types. For instance,
 
  +
  +
What I've been calling an "interface" is a value of type <hask>COutput a</hask> for a type <hask>a</hask>. For instance, for <hask>reverseT</hask>, <hask>a</hask> is <hask>String->String</hask>. The reason for the <hask>C</hask> prefix is explained below. At the heart of TV is a small algebra for constructing these outputs. Weve already seen one output function, <hask>oTitle</hask>. Another one is <hask>showOut</hask>, which is an output for all <hask>Show</hask> types. For instance,
   
 
<haskell>
 
<haskell>
Line 46: Line 61:
 
</haskell>
 
</haskell>
   
=== Inputs and function-valued outputs ===
+
== Inputs and function-valued outputs ==
   
Just as an output is a way to ''deliver'' a value, an "input" is a way to ''obtain'' a value. For example, here are two inputs, each specifying an initial value and a value range, and each given a title.
+
Just as an output is a way to ''deliver'' (or ''consume'') a value, an "input" is a way to ''obtain'' (or ''produce'') a value. For example, here are two inputs, each specifying an initial value and a value range, and each given a title.
   
 
<haskell>
 
<haskell>
Line 56: Line 71:
 
</haskell>
 
</haskell>
   
Now for the fun part. Lets combine the <hask>apples</hask> and <hask>bananas</hask> inputs and the <hask>total</hask> output to make a ''function-valued'' output.
+
Now for the fun part. Let's combine the <hask>apples</hask> and <hask>bananas</hask> inputs and the <hask>total</hask> output to make a ''function-valued'' output.
   
 
<haskell>
 
<haskell>
Line 77: Line 92:
 
| style="padding:20px;" | [[Image:shopping.png]]
 
| style="padding:20px;" | [[Image:shopping.png]]
 
| style="padding:20px;" |
 
| style="padding:20px;" |
shopping list: apples: <u>8</u>
+
shopping list: apples: <b><i>8</i></b>
bananas: <u>5</u>
+
bananas: <b><i>5</i></b>
 
total: 13
 
total: 13
 
|}
 
|}
 
</blockquote>
 
</blockquote>
   
=== A variation ===
+
== A variation ==
   
 
Here is an uncurried variation:
 
Here is an uncurried variation:
Line 93: Line 108:
 
(uncurry (+))
 
(uncurry (+))
 
</haskell>
 
</haskell>
However, there's a much more elegant formulation, using the [http://darcs.haskell.org/packages/DeepArrow/doc/html/Control-Arrow-DeepArrow.html#v%3AcurryA <hask>uncurryA</hask>] method and [http://darcs.haskell.org/packages/DeepArrow/doc/html/Data-FunArr.html#v%3A%24%24 <hask>$$</hask>] operator from [[DeepArrow]].
+
However, there's a much more elegant formulation, using <hask>uncurryA</hask> and <hask>$$</hask> from [[DeepArrow]]:
 
<haskell>
 
<haskell>
 
shoppingPr = uncurryA $$ shopping
 
shoppingPr = uncurryA $$ shopping
Line 105: Line 120:
 
| style="padding:20px;" | [[Image:shoppingPr.png]]
 
| style="padding:20px;" | [[Image:shoppingPr.png]]
 
| style="padding:20px;" |
 
| style="padding:20px;" |
shopping list: apples: <u>8</u>
+
shopping list -- uncurried: apples: <b><i>8</i></b>
bananas: <u>5</u>
+
bananas: <b><i>5</i></b>
 
total: 13
 
total: 13
 
|}
 
|}
 
</blockquote>
 
</blockquote>
   
=== The general story ===
+
== The general story ==
   
TVs, outputs and inputs are not restricted to GUIs and IO. In general, theyre parameterized by an arrow.
+
TVs, outputs, and inputs are not restricted to GUIs and IO. In general, they are parameterized by the mechanics of "transmitting values", i.e., delivering ("sinking") output and gathering ("sourcing") input.
   
 
<haskell>
 
<haskell>
data Output (~>) a
+
data Input src a
data Input (~>) a
+
data Output src snk a
type TV (~>) a
+
type TV src snk a
 
</haskell>
 
</haskell>
   
  +
The "sources" will be [[applicative functor]]s (AFs), and the "sinks" will be contravariant functors.
In the examples above, we've used two different arrows, namely [[Phooey]]'s <hask>UI</hask> arrow and <hask>KIO</hask>, defined simply as
 
   
  +
In the examples above, we've used two different mechanisms, namely [[Phooey]]'s <hask>UI</hask> AF and <hask>IO</hask>. The sinks are counterparts <hask>IU</hask> and <hask>OI</hask>.
  +
  +
The functions <hask>runUI</hask> and <hask>runIO</hask> used in examples above are simply type-specialized synonyms for [http://hackage.haskell.org/package/TV/latest/doc/html/Interface-TV.html#v%3ArunTV <hask>runTV</hask>].
 
<haskell>
 
<haskell>
type KIO = Kleisli IO
+
runUI :: TV UI IU a -> IO ()
  +
runUI = runTV
  +
  +
runIO :: TV IO OI a -> IO ()
  +
runIO = runTV
 
</haskell>
 
</haskell>
   
  +
== Common Ins and Outs ==
Any other monad may be used in place of <hask>IO</hask>, and other arrows in place of <hask>UI</hask> and <hask>KIO</hask>.
 
   
  +
The examples <hask>reverseT</hask> and <hask>shoppingT</hask> above used not only the generic <hask>Output</hask> and <hask>Input</hask> operations, but also some operations that apply to AFs having a few methods for sourcing and sinking a few common types (strings, readables, showables, and booleans). The type constructors <hask>CInput</hask>, <hask>COutput</hask>, and <hask>CTV</hask> are universally quantified over sources and sinks having the required methods.
=== Common Ins and Outs ===
 
 
The examples <hask>reverseT</hask> and <hask>shoppingT</hask> above used not only the generic <hask>Output</hask> and <hask>Input</hask> operations, but also some operations that apply to arrows belonging to the <hask>CommonInsOuts</hask> class, which includes <hask>UI</hask> and <hask>KIO</hask>. The type constructors <hask>CInput</hask>, <hask>COutput</hask>, and <hask>CTV</hask> are universally quantified over <hask>CommonInsOuts</hask> arrows.
 
   
 
<haskell>
 
<haskell>
type Common f a = forall (~>). CommonInsOuts (~>) => f (~>) a
+
type CInput a = forall src.
  +
(CommonIns src) => Input src a
  +
type COutput a = forall src snk.
  +
(CommonIns src, CommonOuts snk) => Output src snk a
  +
type CTV a = forall src snk.
  +
(CommonIns src, CommonOuts snk) => TV src snk a
 
</haskell>
 
</haskell>
   
  +
== Sorting examples ==
<haskell>
 
type CInput a = Common Input a
 
type COutput a = Common Output a
 
type CTV a = Common TV a
 
</haskell>
 
   
  +
Here's a sorting TV (see [http://hackage.haskell.org/packages/archive/TV/latest/doc/html/Interface-TV-Common.html#v:interactLineRS <hask>interactLineRS</hask>]), tested with <hask>runUI</hask>:
=== Sorting examples ===
 
 
Here's a sorting TV:
 
   
  +
<blockquote>
  +
{| class="wikitable"
  +
| style="padding-right:2em;" |
 
<haskell>
 
<haskell>
 
sortT :: (Read a, Show a, Ord a) => CTV ([a] -> [a])
 
sortT :: (Read a, Show a, Ord a) => CTV ([a] -> [a])
sortT = tv (oTitle "sort" $ interactRSOut []) sort
+
sortT = tv (oTitle "sort" $ interactLineRS []) sort
 
</haskell>
 
</haskell>
  +
|-
  +
| style="padding:20px;text-align:center;" | [[Image:sortT.png]]
  +
|}
  +
</blockquote>
   
Since <hask>sortT</hask> is polymorphic in value, you may want to type-annotate its uses, e.g.,
+
Note that <hask>sortT</hask> is polymorphic in value, and the type variable <hask>a</hask> as defaulted to <hask>Int</hask>. You could instead type-annotate its uses, e.g.,
   
<hask> runUI (sortT :: CTV ([String] -> [String]))</hask>
+
: <hask>runUI (sortT :: CTV ([String] -> [String]))</hask>
   
  +
== Composition of TVs ==
Otherwise, <hask>a</hask> will default to <hask>Int</hask>.
 
 
With <hask>runUI</hask>:
 
 
: [[Image:sortT.png]]
 
 
=== Composition of TVs ===
 
   
 
So far, we done a little composition of interfaces and combined them with values to construct TVs. Now let's look at composition of TVs.
 
So far, we done a little composition of interfaces and combined them with values to construct TVs. Now let's look at composition of TVs.
Line 168: Line 188:
 
First, wrap up the <hask>words</hask> and <hask>unwords</hask> functions:
 
First, wrap up the <hask>words</hask> and <hask>unwords</hask> functions:
   
  +
<blockquote>
  +
{| class="wikitable"
  +
| style="padding-right:2em;" |
 
<haskell>
 
<haskell>
 
wordsT :: CTV (String -> [String])
 
wordsT :: CTV (String -> [String])
 
wordsT = tv ( oTitle "function: words" $
 
wordsT = tv ( oTitle "function: words" $
oLambda (iTitle "sentence in" defaultIn)
+
oLambda (iTitle "sentence in" defaultIn)
(oTitle "words out" defaultOut))
+
(oTitle "words out" defaultOut))
words
+
words
 
</haskell>
 
</haskell>
  +
|-
  +
| style="padding:20px;text-align:center;" | [[Image:wordsT.png]]
  +
|}
  +
</blockquote>
   
  +
<blockquote>
: [[Image:wordsT.png]]
 
  +
{| class="wikitable"
 
  +
| style="padding-right:2em;" |
 
<haskell>
 
<haskell>
 
unwordsT :: CTV ([String] -> String)
 
unwordsT :: CTV ([String] -> String)
 
unwordsT = tv ( oTitle "function: unwords" $
 
unwordsT = tv ( oTitle "function: unwords" $
oLambda (iTitle "words in" defaultIn)
+
oLambda (iTitle "words in" defaultIn)
(oTitle "sentence out" defaultOut))
+
(oTitle "sentence out" defaultOut))
 
unwords
 
unwords
 
</haskell>
 
</haskell>
  +
|-
 
: [[Image:unwordsT.png]]
+
| style="padding:20px;text-align:center;" | [[Image:unwordsT.png]]
  +
|}
  +
</blockquote>
   
 
Finally, compose <hask>wordsT</hask>, <hask>unwordsT</hask>, and <hask>sortT</hask>
 
Finally, compose <hask>wordsT</hask>, <hask>unwordsT</hask>, and <hask>sortT</hask>
Line 202: Line 232:
 
| style="padding:20px;" | [[Image:sortWordsT.png]]
 
| style="padding:20px;" | [[Image:sortWordsT.png]]
 
| style="padding:20px;" |
 
| style="padding:20px;" |
  +
sentence in: <b><i>The night Max wore his wolf suit</i></b>
*Examples> runIO sortWordsT
 
sentence in: <u>The night Max wore his wolf suit</u>
 
 
sentence out: Max The his night suit wolf wore
 
sentence out: Max The his night suit wolf wore
 
|}
 
|}
 
</blockquote>
 
</blockquote>
   
The operator [http://darcs.haskell.org/packages/DeepArrow/doc/html/Control-Arrow-DeepArrow.html#v%3A-%3E%7C "<hask>->|</hask>"] is part of a general approach to value composition from [[DeepArrow]].
+
The operator "[http://hackage.haskell.org/package/DeepArrow/latest/doc/html/Control-Arrow-DeepArrow.html#v%3A-%3E%7C <hask>->|</hask>]" is part of a general approach to value composition from [[DeepArrow]].
  +
  +
== Transmission-specific interfaces ==
  +
  +
While some interfaces can be implemented for different means of transmission, others are more specialized.
   
=== Arrow-specific interfaces ===
+
=== GUIs ===
   
While some interfaces can be implemented for different kinds of interfaces, others are more specialized. Here are inputs for our shopping example above that specifically work with [[Phooey]]'s UI arrow.
+
Here are inputs for our shopping example above that specifically work with [[Phooey]]'s UI applicative functor.
 
<haskell>
 
<haskell>
 
applesU, bananasU :: Input UI Int
 
applesU, bananasU :: Input UI Int
Line 219: Line 252:
   
 
shoppingUO :: Output UI (Int -> Int -> Int)
 
shoppingUO :: Output UI (Int -> Int -> Int)
shoppingUO = oTitle "shopping list" $
+
shoppingUO = oTitle "shopping list" $ oLambda applesU (oLambda bananasU total)
oLambda applesU (oLambda bananasU total)
 
 
</haskell>
 
</haskell>
   
 
We can then make curried and uncurried TVs:
 
We can then make curried and uncurried TVs:
  +
<blockquote>
  +
{| class="wikitable"
  +
! code !! runUI rendering
  +
|-
  +
| style="padding:20px;" align=right| <hask>tv shoppingUO (+)</hask>
  +
| style="padding:20px;" align="center" | [[Image:shoppingU.png]]
  +
|-
  +
| style="padding:20px;" align=right | <hask>uncurryA $$ tv shoppingUO (+)</hask>
  +
| style="padding:20px;" align="center" | [[Image:shoppingPrU.png]]
  +
|}
  +
</blockquote>
  +
  +
'''Note''': We could define other type classes, besides <hask>CommonInsOuts</hask>. For instance, <hask>islider</hask> could be made a method of a <hask>GuiArrow</hask> class, allowing it to be rendered in different ways with different GUI toolkits or even using HTML and Javascript.
  +
  +
=== IO ===
  +
  +
We can use <hask>IO</hask> operations in TV interfaces. The corresponding sink is <hask>OI</hask>, defined in [[TypeCompose]]. TV provides a few functions in its [http://hackage.haskell.org/package/TV/latest/doc/html/Interface-TV-IO.html <hask>IO</hask> module], including a close counterpart to the standard <hask>interact</hask> function.
 
<haskell>
 
<haskell>
shoppingU :: TV UI (Int -> Int -> Int)
+
interactOut :: Output IO OI (String -> String)
  +
interactOut = oLambda contentsIn stringOut
shoppingU = tv shoppingUO (+)
 
  +
</haskell>
   
  +
Assuming we have a file <tt>"test.txt"</tt> containing some lines of text, we can use it to test string transformations.
shoppingPrU :: TV UI ((Int,Int) -> Int)
 
  +
<haskell>
shoppingPrU = uncurryA $$ shoppingU
 
  +
testO :: Output IO OI (String -> String)
  +
testO = oLambda (fileIn "test.txt") defaultOut
 
</haskell>
 
</haskell>
   
  +
First, let's define higher-order functions that apply another function to the lines or on the words of a string.
'''Note''': We could define other type classes, besides <hask>CommonInsOuts</hask>. For instance, <hask>islider</hask> could be made a method of a <hask>GuiArrow</hask> class, allowing it to be rendered in different ways with different GUI toolkits or even using HTML and Javascript.
 
  +
<haskell>
  +
onLines, onWords :: ([String] -> [String]) -> (String -> String)
  +
onLines f = unlines . f . lines
  +
onWords f = unwords . f . words
  +
</haskell>
  +
Next, specializations that operate on ''each'' line or word:
  +
<haskell>
  +
perLine,perWord :: (String -> String) -> (String -> String)
  +
perLine f = onLines (map f)
  +
perWord f = onWords (map f)
  +
</haskell>
   
  +
Some examples:
== Motivation ==
 
   
  +
<blockquote>
== Portability ==
 
  +
{| class="wikitable"
  +
! string function <hask>f</hask> !! <hask>runIO (tv test0 f)</hask>
  +
|-
  +
| style="padding:20px;" align=right| <hask>id</hask>
  +
| style="padding:20px;" align="center" |
  +
To see a World in a Grain of Sand
  +
And a Heaven in a Wild Flower,
  +
Hold Infinity in the palm of your hand
  +
And Eternity in an hour.
  +
- William Blake
  +
|-
  +
| style="padding:20px;" align=right| <hask>reverse</hask>
  +
| style="padding:20px;" align="center" |
   
  +
ekalB mailliW -
== Known Problems ==
 
  +
.ruoh na ni ytinretE dnA
  +
dnah ruoy fo mlap eht ni ytinifnI dloH
  +
,rewolF dliW a ni nevaeH a dnA
  +
dnaS fo niarG a ni dlroW a ees oT
  +
|-
  +
| style="padding:20px;" align=right| <hask>onLines reverse</hask>
  +
| style="padding:20px;" align="center" |
  +
- William Blake
  +
And Eternity in an hour.
  +
Hold Infinity in the palm of your hand
  +
And a Heaven in a Wild Flower,
  +
To see a World in a Grain of Sand
  +
|-
  +
| style="padding:20px;" align=right| <hask>perLine reverse</hask>
  +
| style="padding:20px;" align="center" |
  +
dnaS fo niarG a ni dlroW a ees oT
  +
,rewolF dliW a ni nevaeH a dnA
  +
dnah ruoy fo mlap eht ni ytinifnI dloH
  +
.ruoh na ni ytinretE dnA
  +
ekalB mailliW -
  +
|-
  +
| style="padding:20px;" align=right| <hask>perLine (perWord reverse)</hask>
  +
| style="padding:20px;" align="center" |
  +
oT ees a dlroW ni a niarG fo dnaS
  +
dnA a nevaeH ni a dliW ,rewolF
  +
dloH ytinifnI ni eht mlap fo ruoy dnah
  +
dnA ytinretE ni na .ruoh
  +
- mailliW ekalB
  +
|}
  +
</blockquote>
   
  +
There are more examples [http://code.haskell.org/~conal/code/TV/src/Examples.hs in the TV repository] and in the [http://code.haskell.org/~conal/code/GuiTV/src/Examples.hs in the GuiTV repository]. See also "[http://journal.conal.net/#%5B%5Bseparating%20IO%20from%20logic%20--%20example%5D%5D separating IO from logic -- example]".
== Plans ==
 
 
[[Category:Interfaces]]
 
[[Category:User Interfaces]]
 
[[Category:IO]]
 
[[Category:Arrow]]
 
[[Category:Libraries]]
 
[[Category:Packages]]
 

Revision as of 21:12, 19 October 2011


Abstract

TV is a library for composing tangible values ("TVs"), i.e., values that carry along external interfaces. In particular, TVs can be composed to create new TVs, and they can be directly executed with a friendly GUI, a process that reads and writes character streams, or many other kinds interfaces. Values and interfaces are combined for direct use, and separable for composition. This combination makes for software that is ready to use and ready to reuse.

TV can be thought of as a simple functional formulation of the Model-View-Controller pattern. (My thanks to an anonymous ICFP referee for pointing out this connection.) The value part of a TV is the model, and the "interface" part, or "output" as it is called below, is the viewer. Outputs are built up compositionally from other outputs and from inputs (the controllers), as described below.

Besides this wiki page, here are more ways to learn about TV:

  • Visit the Hackage page for library documentation and to download & install.
  • Or install with cabal install project-foo.
  • See the use of TV in Eros.

As of version 0.2, I have moved the GUI functionality out of TV and into a small new package GuiTV. I moved it out to eliminate the dependency of core TV on Phooey and hence on wxHaskell, as the latter can be difficult to install. The GUI examples below require GuiTV.

GuiTV (better named "wxTV") is bit-rotten. There is also a very similar package to generate Gtk-based GUIs.

I'd love to hear your comments at the Talk:TV page.

First Example

Here is a tangible reverse function:

reverseT :: CTV (String -> String)
reverseT = tv (oTitle "reverse" defaultOut) reverse

The tv function combines an interface and a value. In this example, the interface is the default for string functions, wrapped with the title "reverse".

TV "interfaces" are more than just GUIs. Here are two different renderings of reverseT. (User input is shown in italics in the runIO version).

Running:

runUI reverseT runIO reverseT
ReverseT.png

*Examples> runIO reverseT reverse: Hello, reversible world. .dlrow elbisrever ,olleH *Examples>

We'll see later that "runUI" and "runIO" are both type-specialized synonyms for a more general function.

Outputs

What I've been calling an "interface" is a value of type COutput a for a type a. For instance, for reverseT, a is String->String. The reason for the C prefix is explained below. At the heart of TV is a small algebra for constructing these outputs. Weve already seen one output function, oTitle. Another one is showOut, which is an output for all Show types. For instance,

total :: Show a => COutput a
total = oTitle "total" showOut

Inputs and function-valued outputs

Just as an output is a way to deliver (or consume) a value, an "input" is a way to obtain (or produce) a value. For example, here are two inputs, each specifying an initial value and a value range, and each given a title.

apples, bananas :: CInput Int
apples  = iTitle "apples"  defaultIn
bananas = iTitle "bananas" defaultIn

Now for the fun part. Let's combine the apples and bananas inputs and the total output to make a function-valued output.

shoppingO :: COutput (Int -> Int -> Int)
shoppingO = oTitle "shopping list" $
            oLambda apples (oLambda bananas total)

And a TV:

shopping :: CTV (Int -> Int -> Int)
shopping = tv shoppingO (+)

Running:

runUI shopping runIO shopping
Shopping.png

shopping list: apples: 8 bananas: 5 total: 13

A variation

Here is an uncurried variation:

shoppingPr :: CTV ((Int,Int) -> Int)
shoppingPr = tv ( oTitle "shopping list -- uncurried" $ 
                  oLambda (iPair apples bananas) total )
                (uncurry (+))

However, there's a much more elegant formulation, using uncurryA and $$ from DeepArrow:

shoppingPr = uncurryA $$ shopping

Running:

runUI shoppingPr runIO shoppingPr
ShoppingPr.png

shopping list -- uncurried: apples: 8 bananas: 5 total: 13

The general story

TVs, outputs, and inputs are not restricted to GUIs and IO. In general, they are parameterized by the mechanics of "transmitting values", i.e., delivering ("sinking") output and gathering ("sourcing") input.

data Input  src     a
data Output src snk a
type TV     src snk a

The "sources" will be applicative functors (AFs), and the "sinks" will be contravariant functors.

In the examples above, we've used two different mechanisms, namely Phooey's UI AF and IO. The sinks are counterparts IU and OI.

The functions runUI and runIO used in examples above are simply type-specialized synonyms for runTV.

runUI :: TV UI IU a -> IO ()
runUI = runTV

runIO :: TV IO OI a -> IO ()
runIO = runTV

Common Ins and Outs

The examples reverseT and shoppingT above used not only the generic Output and Input operations, but also some operations that apply to AFs having a few methods for sourcing and sinking a few common types (strings, readables, showables, and booleans). The type constructors CInput, COutput, and CTV are universally quantified over sources and sinks having the required methods.

type CInput a = forall src.
  (CommonIns src)                 => Input  src     a
type COutput a = forall src snk.
  (CommonIns src, CommonOuts snk) => Output src snk a
type CTV a = forall src snk.
  (CommonIns src, CommonOuts snk) => TV     src snk a

Sorting examples

Here's a sorting TV (see interactLineRS), tested with runUI:

sortT :: (Read a, Show a, Ord a) => CTV ([a] -> [a])
sortT = tv (oTitle "sort" $ interactLineRS []) sort
SortT.png

Note that sortT is polymorphic in value, and the type variable a as defaulted to Int. You could instead type-annotate its uses, e.g.,

runUI (sortT :: CTV ([String] -> [String]))

Composition of TVs

So far, we done a little composition of interfaces and combined them with values to construct TVs. Now let's look at composition of TVs.

First, wrap up the words and unwords functions:

wordsT :: CTV (String -> [String]) 
wordsT = tv ( oTitle "function: words" $
                oLambda (iTitle "sentence in" defaultIn)
                        (oTitle "words out"   defaultOut))
              words
WordsT.png
unwordsT :: CTV ([String] -> String) 
unwordsT = tv ( oTitle "function: unwords" $
                  oLambda (iTitle "words in"     defaultIn)
                          (oTitle "sentence out" defaultOut))
              unwords
UnwordsT.png

Finally, compose wordsT, unwordsT, and sortT

sortWordsT :: CTV (String -> String)
sortWordsT = wordsT ->| sortT ->| unwordsT

Running:

runUI sortWordsT runIO sortWordsT
SortWordsT.png

sentence in: The night Max wore his wolf suit sentence out: Max The his night suit wolf wore

The operator "->|" is part of a general approach to value composition from DeepArrow.

Transmission-specific interfaces

While some interfaces can be implemented for different means of transmission, others are more specialized.

GUIs

Here are inputs for our shopping example above that specifically work with Phooey's UI applicative functor.

applesU, bananasU :: Input UI Int
applesU  = iTitle "apples"  (islider 3 (0,10))
bananasU = iTitle "bananas" (islider 7 (0,10))

shoppingUO :: Output UI (Int -> Int -> Int)
shoppingUO = oTitle "shopping list" $ oLambda applesU (oLambda bananasU total)

We can then make curried and uncurried TVs:

code runUI rendering
tv shoppingUO (+) ShoppingU.png
uncurryA $$ tv shoppingUO (+) ShoppingPrU.png

Note: We could define other type classes, besides CommonInsOuts. For instance, islider could be made a method of a GuiArrow class, allowing it to be rendered in different ways with different GUI toolkits or even using HTML and Javascript.

IO

We can use IO operations in TV interfaces. The corresponding sink is OI, defined in TypeCompose. TV provides a few functions in its IO module, including a close counterpart to the standard interact function.

interactOut :: Output IO OI (String -> String)
interactOut = oLambda contentsIn stringOut

Assuming we have a file "test.txt" containing some lines of text, we can use it to test string transformations.

testO :: Output IO OI (String -> String)
testO = oLambda (fileIn "test.txt") defaultOut

First, let's define higher-order functions that apply another function to the lines or on the words of a string.

onLines, onWords :: ([String] -> [String]) -> (String -> String)
onLines f = unlines . f . lines
onWords f = unwords . f . words

Next, specializations that operate on each line or word:

perLine,perWord :: (String -> String) -> (String -> String)
perLine f = onLines (map f)
perWord f = onWords (map f)

Some examples:

string function f runIO (tv test0 f)
id

To see a World in a Grain of Sand And a Heaven in a Wild Flower, Hold Infinity in the palm of your hand And Eternity in an hour. - William Blake

reverse

ekalB mailliW - .ruoh na ni ytinretE dnA dnah ruoy fo mlap eht ni ytinifnI dloH ,rewolF dliW a ni nevaeH a dnA dnaS fo niarG a ni dlroW a ees oT

onLines reverse

- William Blake And Eternity in an hour. Hold Infinity in the palm of your hand And a Heaven in a Wild Flower, To see a World in a Grain of Sand

perLine reverse

dnaS fo niarG a ni dlroW a ees oT ,rewolF dliW a ni nevaeH a dnA dnah ruoy fo mlap eht ni ytinifnI dloH .ruoh na ni ytinretE dnA ekalB mailliW -

perLine (perWord reverse)

oT ees a dlroW ni a niarG fo dnaS dnA a nevaeH ni a dliW ,rewolF dloH ytinifnI ni eht mlap fo ruoy dnah dnA ytinretE ni na .ruoh - mailliW ekalB

There are more examples in the TV repository and in the in the GuiTV repository. See also "separating IO from logic -- example".