[Haskell-cafe] Fun with type functions

2009-07-02 Thread Simon Peyton-Jones
Friends

Ken, Oleg, and I have finished Version 2 of our paper Fun with Type 
Functions, which gives a programmer's tour of what type functions are and how 
they are useful.

http://haskell.org/haskellwiki/Simonpj/Talk:FunWithTypeFuns

If you have a moment to look at, and wanted to help us improve it, the above 
link goes to a wiki page where you can comment on the paper or discuss it.  We 
still have time to improve it.

Thanks

Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Fun with type functions

2009-05-14 Thread Simon Peyton-Jones
Friends

Ken, Oleg, and I have been working on a tutorial paper about type families (aka 
associated data types, or type functions). It's in draft at the moment, and 
we'd really appreciate feedback that would help us improve it.

Here it is: http://haskell.org/haskellwiki/Simonpj/Talk:FunWithTypeFuns

Thank you!

Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fun with type functions

2008-12-05 Thread Hugo Pacheco
Pointless Haskell a library for point-free programming with recursion
patterns that uses type synonym families to provide a view of data types as
the fixed points of  functors.
It defines two type functions

type family PF a :: * - * -- returns the pattern functor for a
data type
type family Rep (f :: * - *) x :: *  -- returns the result type of applying
a functor to a type argument

that can be combined to derive the structurally equivalent sum of products
for some type:

type F a x = Rep (PF a) x

class Mu a where
inn :: F a a - a
out :: a - F a a

For Haskell polymorphic lists, we need to define:

type instance PF [a] = Const One :+: Const a :*: Id

instance Mu [a] where
inn (Left _) = []
inn (Right (x,xs)) = x:xs
out [] = Left _L
out (x:xs) = Right (x,xs)

Some of the typical recursion patterns are:

hylo :: Functor (PF b) = b - (F b c - c) - (a - F b a) - a - c
cata :: (Mu a,Functor (PF a)) = a - (F a b - b) - a - b
ana :: (Mu b,Functor (PF b)) = b - (a - F b a) - a - b

One simple example is the foldr (catamorphism) for calculating the lenght of
a list:

length :: [a] - Int
length = cata (_L::[a]) f
where f = zero \/ succ . snd

 length [1,2,3,4]
4


I have promoted the library into a cabal package (pointless-haskell) today
and am creating an homepage (
http://haskell.di.uminho.pt/wiki/Pointless+Haskell) with examples.

cheers,
hugo

On Thu, Nov 27, 2008 at 9:29 AM, Simon Peyton-Jones
[EMAIL PROTECTED]wrote:

 Friends

 GHC has embodied data type families since 6.8, and now type synonym
 families (aka type functions) in 6.10.  However, apart from our initial
 papers there isn't much published material about how to *use* type families.
  But that hasn't stopped you: quite a few people are using them already, and
 of course there is a rich seam of work on using functional dependencies to
 express type-level computation.

 Ken Shan and Oleg Kiselyov and I are collaborating to write a paper for an
 upcoming workshop, under the general rubric of Fun with type functions (in
 homage to Thomas Hallgren's paper Fun with functional dependencies and
 Ralf Hinze's paper Fun with phantom types).

 So this message is to ask you:

can you tell us about the most persuasive, fun application
you've encountered, for type families or functional dependencies?

 Simple is good.  It doesn't have to be elaborate: just something that does
 something useful you could not have done otherwise.  Pointers to email
 threads are fine.  Don't assume we already know about them (even if we
 participated in the thread :-)  Part of what we're interested in is that
 *you* found the example compelling.

 Many thanks

 Simon, Ken, Oleg

 PS: I'm broadcasting this message to GHC-users and Haskell-cafe, but to
 avoid deluging ghc-users, please reply just to us and Haskell cafe.
  (Interested ghc-users can follow the threads there from the archives if
 they want.)
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
www.di.uminho.pt/~hpacheco
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fun with type functions

2008-12-04 Thread Conrad Parker
2008/11/27 Simon Peyton-Jones [EMAIL PROTECTED]:

can you tell us about the most persuasive, fun application
you've encountered, for type families or functional dependencies?

Hi,

I certainly had fun with the Instant Insanity puzzle, in Monad.Reader issue 8:

  http://www.haskell.org/haskellwiki/User:ConradParker/InstantInsanity

That was using functional dependencies. Then Pepe Iborra pasted a
version of Instant Insanity with type families: http://hpaste.org/2689

Looking back at this, Manuel left the following comment:

-- There is unfortunately, no simple way to print the normalised type.
-- In fact, GHC goes to great length to show types with as little
-- normalisation as possible to users.  (Especially for error messages,
-- that usually makes them much easier to understand.)  However, with
-- type families, I think we really ought to have a ghci command to
-- specifically request a normalised type.  I'll put that on my
-- TODO list!

-- For the moment, you can of course try forcing normalisation by
-- triggering type errors; eg
--  :t solution :: Int

(Does ghci now have a command for printing normalised types?)

There are also links to haskell-cafe discussion and some other
implementations (in C++ templates and D) to, um, compare:

http://www.haskell.org/haskellwiki/User_talk:ConradParker/InstantInsanity

cheers,

Conrad.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fun with type functions

2008-11-27 Thread Magnus Therning
On Thu, Nov 27, 2008 at 9:29 AM, Simon Peyton-Jones
[EMAIL PROTECTED] wrote:
 Friends

 GHC has embodied data type families since 6.8, and now type synonym families 
 (aka type functions) in 6.10.  However, apart from our initial papers there 
 isn't much published material about how to *use* type families.  But that 
 hasn't stopped you: quite a few people are using them already, and of course 
 there is a rich seam of work on using functional dependencies to express 
 type-level computation.

 Ken Shan and Oleg Kiselyov and I are collaborating to write a paper for an 
 upcoming workshop, under the general rubric of Fun with type functions (in 
 homage to Thomas Hallgren's paper Fun with functional dependencies and Ralf 
 Hinze's paper Fun with phantom types).

 So this message is to ask you:

can you tell us about the most persuasive, fun application
you've encountered, for type families or functional dependencies?

 Simple is good.  It doesn't have to be elaborate: just something that does 
 something useful you could not have done otherwise.  Pointers to email 
 threads are fine.  Don't assume we already know about them (even if we 
 participated in the thread :-)  Part of what we're interested in is that 
 *you* found the example compelling.

 Many thanks

I documented, [1] and [2], my first encounter with functional
dependencies.  Maybe not a persuasive example, but I felt it was a
fairly good introduction to them.

/M

[1]: http://therning.org/magnus/archives/354
[2]: http://therning.org/magnus/archives/355

-- 
Magnus Therning(OpenPGP: 0xAB4DFBA4)
magnus@therning.org  Jabber: magnus@therning.org
http://therning.org/magnus identi.ca|twitter: magthe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fun with type functions

2008-11-27 Thread Ryan Ingram
My work on lightweight session types (modeled after this year's ICFP
paper on the same subject) used type and data families extensively for
an elegant way of connecting communicating coroutines:

Empty types are used for sessions:

 data Eps  -- empty session
 data a :?: s -- read an a followed by session s
 data a :!: s -- write an a followed by session s
 -- etc.

These have kind *, which makes them easy to use in other type-level
code; my first formulation had the session types as functors directly,
but that led to needing kind signatures elsewhere and made working
with these types much more difficult..

Type families are used to represent the dual of a session; that is, a
session that reads an Int can connect with a session that writes an
Int.

 type family Dual s
 type instance Dual Eps = Eps
 type instance Dual (a :?: s) = a :!: Dual s
 type instance Dual (a :!: s) = a :?: Dual s
 -- etc.

Then data families give structure to the session:

 data family Rep s a
 newtype instance Rep Eps a = Done a
 data instance Rep (x :!: s) a = Send x (Rep s a)
 newtype instance Rep (x :?: s) a = Receive (x - Rep s a)
 -- etc.

Rep s converts a sessions (kind *) into a functor (kind * - *).  It
also allows easy experimentation with alternate formulations of the
problem that potentially have different kinds.

Finally, a typeclass allows interpretation of these types, connecting
two sessions together to run as coroutines:

 class Coroutine s where
connect :: (Dual s ~ c, Dual c ~ s) = Rep s a - Rep c b - (a,b)

 instance Coroutine Eps where
connect (Done a) (Done b) = (a,b)
 instance Coroutine s = Coroutine (x :!: s) where
connect (Send x s) (Receive k) = connect s (k x)
 instance Coroutine s = Coroutine (x :?: s) where
connect (Receive k) (Send x c) = connect (k x) c

The proof that two routines can safely connect is done entirely at
compile time; the connection routine just takes care of routing data
between the two processes.

  -- ryan

On Thu, Nov 27, 2008 at 1:29 AM, Simon Peyton-Jones
[EMAIL PROTECTED] wrote:
 Friends

 GHC has embodied data type families since 6.8, and now type synonym families 
 (aka type functions) in 6.10.  However, apart from our initial papers there 
 isn't much published material about how to *use* type families.  But that 
 hasn't stopped you: quite a few people are using them already, and of course 
 there is a rich seam of work on using functional dependencies to express 
 type-level computation.

 Ken Shan and Oleg Kiselyov and I are collaborating to write a paper for an 
 upcoming workshop, under the general rubric of Fun with type functions (in 
 homage to Thomas Hallgren's paper Fun with functional dependencies and Ralf 
 Hinze's paper Fun with phantom types).

 So this message is to ask you:

can you tell us about the most persuasive, fun application
you've encountered, for type families or functional dependencies?

 Simple is good.  It doesn't have to be elaborate: just something that does 
 something useful you could not have done otherwise.  Pointers to email 
 threads are fine.  Don't assume we already know about them (even if we 
 participated in the thread :-)  Part of what we're interested in is that 
 *you* found the example compelling.

 Many thanks

 Simon, Ken, Oleg

 PS: I'm broadcasting this message to GHC-users and Haskell-cafe, but to avoid 
 deluging ghc-users, please reply just to us and Haskell cafe.  (Interested 
 ghc-users can follow the threads there from the archives if they want.)
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe