Type operators in GHC

Iavor Diatchki iavor.diatchki at gmail.com
Mon Sep 17 18:28:05 CEST 2012


Hello,

I think that it would be a mistake to have two pragmas with incompatible
behaviors:  for example, we would not be able to write modules that use
Conal's libraries and, say, the type nats I've been working on.
If the main issue is the notation for arrows, has anoyone played with what
can be done with the current (7.6) system?  I just thought of two
variations that seem to provide a decent notation for writing arrow-ish
programs.  The second one, in particular, mirrors the arrow notation at the
value level, so perhaps that would be enough?

-Iavor


{-# LANGUAGE TypeOperators, KindSignatures #-}
module Test where

import Control.Category

-- Variant 1: Post-fix annotation

type (a ---> b) c = c a b

f :: Category c => (x ---> y) c -> (y ---> z) c -> (x ---> z) c
f = undefined


-- Variant 2: Arrow notation

type a >-- (c :: * -> * -> *) = c a
type c --> b                  = c b

infix 2 >--
infix 1 -->

g :: Category c => (x >--c--> y) -> (y >--c--> z) -> (x >--c--> z)
g = undefined
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20120917/05040c95/attachment.htm>


More information about the Glasgow-haskell-users mailing list