Difference between revisions of "Tangible Value"

From HaskellWiki
Jump to navigation Jump to search
m
Line 11: Line 11:
 
* See the [http://darcs.haskell.org/packages/TV/README README].
 
* See the [http://darcs.haskell.org/packages/TV/README README].
   
== Introduction ==
+
== Tangible values ==
   
 
As a first example, here is a tangible reverse function:
 
As a first example, here is a tangible reverse function:
Line 20: Line 20:
 
</haskell>
 
</haskell>
   
The result of <hask>runUI reverseT</hask> looks like this:
+
The result of <hask>runUI reverseT</hask> looks like this:
   
Image: reverseT.png
+
: [[Image:reverseT.png]]
   
 
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".
   
''Interfaces'' in TV are more than just GUIs. Here we use <hask>runIO</hask> instead of runUI (showing user input in ''italics''):
+
TV "interfaces" are more than just GUIs. Here we use <hask>runIO</hask> instead of <hask>runUI</hask> (<u>underlining</u> user input):
   
 
<blockquote><tt>
 
<blockquote><tt>
 
*Examples> runIO reverseT<br>
 
*Examples> runIO reverseT<br>
reverse: ''Hello, reversible world!''<br>
+
reverse: <u>Hello, reversible world!</u><br>
 
!dlrow elbisrever ,olleH<br>
 
!dlrow elbisrever ,olleH<br>
 
*Examples>
 
*Examples>
 
</tt></blockquote>
 
</tt></blockquote>
   
  +
=== 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, oTitle. Another one is showOut, which is an output for all Show 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 <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,
   
 
<haskell>
 
<haskell>
Line 42: Line 44:
 
</haskell>
 
</haskell>
   
  +
=== Inputs and function-valued outputs ===
Beside outputs, there are also inputs. 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 <hask>int</hask> inputs, each specifying an initial value and a value range, and each given a title.
 
  +
 
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.
   
 
<haskell>
 
<haskell>
Line 66: Line 70:
 
The result of <hask>runUI shopping</hask>:
 
The result of <hask>runUI shopping</hask>:
   
Image:shopping
+
: [[Image:shopping.png]]
   
 
And of <hask>runIO shopping</hask>:
 
And of <hask>runIO shopping</hask>:
 
<blockquote><tt>
 
<blockquote><tt>
 
*Examples> runIO shopping<br>
 
*Examples> runIO shopping<br>
shopping list: apples: ''8''<br>
+
shopping list: apples: <u>8</u><br>
bananas: ''5''<br>
+
bananas: <u>5</u><br>
 
total: 13
 
total: 13
 
</tt></blockquote>
 
</tt></blockquote>
   
Heres an uncurried variation:
+
=== A variation ===
  +
  +
Here is an uncurried variation:
   
 
<haskell>
 
<haskell>
Line 87: Line 93:
 
The <hask>runIO</hask> presentation is identical to that of <hask>shopping</hask>. The runUI presentation:
 
The <hask>runIO</hask> presentation is identical to that of <hask>shopping</hask>. The runUI presentation:
   
Image:shoppingP
+
: [[Image:shoppingP.png]]
   
  +
=== 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, theyre parameterized by an arrow.
Line 105: Line 112:
   
 
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>.
 
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>.
  +
  +
=== 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.
 
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.
Line 118: Line 127:
 
</haskell>
 
</haskell>
   
  +
=== Sorting examples ===
Heres a sorting TV:
 
  +
 
Here's a sorting TV:
   
 
<haskell>
 
<haskell>
Line 133: Line 144:
 
With runUI:
 
With runUI:
   
Image:sortT
+
: [[Image:sortT.png]]
   
  +
=== Composition of TVs ===
   
So far, we done a little composition of interfaces and combined them with values to construct TVs. Now lets 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.
   
 
First, wrap up the <hask>words</hask> and <hask>unwords</hask> functions:
 
First, wrap up the <hask>words</hask> and <hask>unwords</hask> functions:
Line 148: Line 160:
 
</haskell>
 
</haskell>
   
Image:wordsT
+
: [[Image:wordsT.png]]
   
 
<haskell>
 
<haskell>
Line 158: Line 170:
 
</haskell>
 
</haskell>
   
Image:unwordsT
+
: [[Image:unwordsT.png]]
   
 
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 169: Line 181:
 
With <hask>runUI</hask> and <hask>runIO</hask>:
 
With <hask>runUI</hask> and <hask>runIO</hask>:
   
Image:sortWordsT
+
: [[Image:sortWordsT.png]]
   
 
<blockquote><tt>
 
<blockquote><tt>
 
*Examples> runIO sortWordsT<br>
 
*Examples> runIO sortWordsT<br>
sentence in: ''The night Max wore his wolf suit''<br>
+
sentence in: <u>The night Max wore his wolf suit</u><br>
 
sentence out: Max The his night suit wolf wore<br>
 
sentence out: Max The his night suit wolf wore<br>
 
</tt></blockquote>
 
</tt></blockquote>

Revision as of 02:26, 17 January 2007

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, or a *nix-like process that reads and writes character streams. Values and interfaces are combined for direct use, and separable for composition.

TV is for creating software that is ready to use and ready to reuse.

Beside this page, here are some ways to explore TV:

Tangible values

As a first example, here is a tangible reverse function:

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

The result of runUI reverseT looks like this:

ReverseT.png

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 we use runIO instead of runUI (underlining user input):

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

Outputs

What I've been calling an "interface" is a value of type COutput a for a type a (for reverseT, a == 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 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.

apples, bananas :: CInput Int
apples  = iTitle "apples"  (intIn 3 (0,10))
bananas = iTitle "bananas" (intIn 7 (0,10))

Now for the fun part. Lets 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 (+)

The result of runUI shopping:

Shopping.png

And of runIO shopping:

*Examples> runIO shopping
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" $ 
                  oLambda (iPair apples bananas) total )
                (uncurry (+))

The runIO presentation is identical to that of shopping. The runUI presentation:

ShoppingP.png

The general story

TVs, outputs and inputs are not restricted to GUIs and IO. In general, theyre parameterized by an arrow.

data Output (~>) a
data Input  (~>) a
type TV     (~>) a

In the examples above, we've used two different arrows, namely Phooeys UI arrow (<http://conal.net/Phooey>) and KIO, defined simply as

type KIO = Kleisli IO

Any other monad may be used in place of IO, and other arrows in place of UI and KIO.

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 arrows belonging to the CommonInsOuts class, which includes UI and KIO. The type constructors CInput, COutput, and CTV are universally quantified over CommonInsOuts arrows.

type Common f a = forall (~>). CommonInsOuts (~>) => f (~>) a
type CInput  a = Common Input a
type COutput a = Common Output a
type CTV     a = Common TV a

Sorting examples

Here's a sorting TV:

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

Since sortT is polymorphic in value, you may want to type-annotate its uses, e.g.,

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

Otherwise, a will default to Int.

With runUI:

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.

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

With runUI and runIO:

SortWordsT.png

*Examples> runIO sortWordsT
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.

Motivation

Portability

Known Problems

Plans