Arrow.hs: fix loopl/loopr transposition
[ghc-base.git] / GHC / HetMet / Arrow.hs
1 {-# OPTIONS -XRankNTypes -XMultiParamTypeClasses -XNoMonomorphismRestriction -XTypeOperators -XFlexibleInstances -XFunctionalDependencies -XEmptyDataDecls #-}
2 -----------------------------------------------------------------------------
3 -- |
4 -- Module      :  GHC.HetMet.Arrow
5 -- Copyright   :  none
6 -- License     :  public domain
7 --
8 -- Maintainer  :  Adam Megacz <megacz@acm.org>
9 -- Stability   :  experimental
10 -- Portability :  portable
11
12 module GHC.HetMet.Arrow where
13 import GHC.HetMet.GArrow
14 import Control.Arrow
15 import Control.Category
16
17 ------------------------------------------------------------------------------
18 -- GArrow instances for Control.Arrow; this is kept in a separate
19 -- module because having it available to GHC's instance-search
20 -- algorithm often creates overlapping or even undecidable
21 -- instance-search problems
22
23 type Id a = a
24
25 instance Arrow a => GArrow a (,) () where
26   ga_first     =  first
27   ga_second    =  second
28   ga_cancell   =  arr (\((),x) -> x)
29   ga_cancelr   =  arr (\(x,()) -> x)
30   ga_uncancell =  arr (\x -> ((),x))
31   ga_uncancelr =  arr (\x -> (x,()))
32   ga_assoc     =  arr (\((x,y),z) -> (x,(y,z)))
33   ga_unassoc   =  arr (\(x,(y,z)) -> ((x,y),z))
34   
35 instance Arrow a => GArrowDrop a (,) () where
36   ga_drop      =  arr (\x -> ())
37
38 instance Arrow a => GArrowCopy a (,) () where
39   ga_copy      =  arr (\x -> (x,x))
40
41 instance Arrow a => GArrowSwap a (,) () where
42   ga_swap      =  arr (\(x,y) -> (y,x))
43
44 instance Arrow a => GArrowConstant a (,) () t t where
45   ga_constant x = arr (\() -> x)
46
47 instance Arrow a => GArrowReify a (,) () x y x y where
48   ga_reify     =  arr
49
50 instance ArrowLoop a => GArrowLoop a (,) () where
51   ga_loopr     =  loop
52   ga_loopl  f  =  loop (ga_swap >>> f >>> ga_swap)
53
54 instance ArrowApply a => GArrowApply a (,) () a where
55   ga_applyl    = ga_swap >>> app
56   ga_applyr    = app
57
58 instance Arrow a => GArrowProd a (,) () where
59
60 -- The uninhabited type
61 data Void
62
63 -- In Coq we could simply prove that these cases are impossible; in Haskell we need to have some faith.
64 voidImpossible :: Void -> a
65 voidImpossible = error "this is impossible; you have a bug in your compiler"
66
67 instance ArrowChoice a => GArrow a Either Void where
68   ga_first     =  left
69   ga_second    =  right
70   ga_uncancell =  arr Right
71   ga_uncancelr =  arr Left
72   ga_cancell   =  arr unVoidLeft
73                    where
74                     unVoidLeft  (Left  v) = voidImpossible v
75                     unVoidRight (Right x) = x
76   ga_cancelr   =  arr unVoidRight
77                    where
78                     unVoidRight (Left  x) = x
79                     unVoidRight (Right v) = voidImpossible v
80   ga_assoc     =  arr eitherAssoc
81                    where
82                     eitherAssoc (Left (Left  x)) = Left         x
83                     eitherAssoc (Left (Right y)) = Right (Left  y)
84                     eitherAssoc (Right       z ) = Right (Right z)
85   ga_unassoc   =  arr eitherUnAssoc
86                    where
87                     eitherUnAssoc (Left         x ) = Left  (Left  x)
88                     eitherUnAssoc (Right (Left  y)) = Left  (Right y)
89                     eitherUnAssoc (Right (Right z)) = Right        z
90
91 instance ArrowChoice a => GArrowSum a Either Void where
92   ga_never = arr voidImpossible
93   ga_merge = arr merge
94               where
95                merge (Left  x) = x
96                merge (Right x) = x
97
98
99