Difference between revisions of "Tangible Value"

From HaskellWiki
Jump to navigation Jump to search
m
Line 24: Line 24:
 
Image: reverseT.png
 
Image: 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".
+
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 runIO instead of
+
''Interfaces'' in TV are more than just GUIs. Here we use <hask>runIO</hask> instead of runUI (showing user input in ''italics''):
runUI (showing user input in ''italics''):
 
   
 
<blockquote><tt>
 
<blockquote><tt>
Line 36: Line 35:
 
</tt></blockquote>
 
</tt></blockquote>
   
What Ive 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, oTitle. Another one is showOut, which is an output for all Show types. For instance,
   
 
<haskell>
 
<haskell>
Line 86: Line 85:
 
</haskell>
 
</haskell>
   
The runIO 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
Line 99: Line 98:
 
</haskell>
 
</haskell>
   
In the examples above, weve used two different arrows, namely Phooeys UI arrow (<http://conal.net/Phooey>) and KIO, defined simply as
+
In the examples above, we've used two different arrows, namely Phooeys UI arrow (<http://conal.net/Phooey>) and KIO, defined simply as
   
 
<haskell>
 
<haskell>
Line 105: Line 104:
 
</haskell>
 
</haskell>
   
Any other monad may be used in place of IO, and other arrows in place of UI and KIO.
+
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 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.
+
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>
Line 139: Line 138:
 
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 lets look at composition of TVs.
   
First, wrap up the words and unwords functions:
+
First, wrap up the <hask>words</hask> and <hask>unwords</hask> functions:
   
 
<haskell>
 
<haskell>
Line 168: Line 167:
 
</haskell>
 
</haskell>
   
With runUI and runIO:
+
With <hask>runUI</hask> and <hask>runIO</hask>:
   
 
Image:sortWordsT
 
Image:sortWordsT

Revision as of 01:59, 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:

Introduction

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:

Image: 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".

Interfaces in TV are more than just GUIs. Here we use runIO instead of runUI (showing user input in italics):

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

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

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 int 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:

Image:shopping

And of runIO shopping:

*Examples> runIO shopping
shopping list: apples: 8
bananas: 5
total: 13

Heres 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:

Image:shoppingP


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.

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

Heres 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:

Image:sortT


So far, we done a little composition of interfaces and combined them with values to construct TVs. Now lets 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

Image:wordsT

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

Image:unwordsT

Finally, compose wordsT, unwordsT, and sortT

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

With runUI and runIO:

Image:sortWordsT

*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