Skip to content

Commit

Permalink
untested and possibly incomplete patches for ghc7.10
Browse files Browse the repository at this point in the history
  • Loading branch information
atzedijkstra committed Mar 31, 2015
1 parent 5622cd1 commit 4a95bd8
Show file tree
Hide file tree
Showing 3 changed files with 26 additions and 7 deletions.
2 changes: 1 addition & 1 deletion src/UHC/Util/Lens.hs
Expand Up @@ -53,7 +53,7 @@ type Lens a b = a :-> b
-- * Operator interface for composition

infixl 9 ^*
-- | functional getter, which acts like a field accessor
-- | composition
(^*) :: (a :-> b) -> (b :-> c) -> (a :-> c)
f1 ^* f2 = f2 . f1
{-# INLINE (^*) #-}
Expand Down
7 changes: 6 additions & 1 deletion src/UHC/Util/ParseUtils.hs
@@ -1,4 +1,4 @@
{-# LANGUAGE RankNTypes, FlexibleContexts #-}
{-# LANGUAGE RankNTypes, FlexibleContexts, CPP #-}

module UHC.Util.ParseUtils
( -- * Specific parser types
Expand Down Expand Up @@ -27,6 +27,11 @@ module UHC.Util.ParseUtils
)
where

#if __GLASGOW_HASKELL__ >= 710
import Prelude hiding ( (<*>), (<*), (*>), (<$>), (<$) )
#else
#endif

import qualified Data.Map as Map
import Data.Maybe
import UU.Parsing
Expand Down
24 changes: 19 additions & 5 deletions src/UHC/Util/VarLookup.hs
Expand Up @@ -2,7 +2,11 @@
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 710
#else
{-# LANGUAGE OverlappingInstances #-}
#endif

module UHC.Util.VarLookup
( VarLookup (..)
Expand Down Expand Up @@ -79,11 +83,21 @@ infixr 7 |+>
class VarLookupCmb m1 m2 where
(|+>) :: m1 -> m2 -> m2

instance VarLookupCmb m1 m2 => VarLookupCmb m1 [m2] where
m1 |+> (m2:m2s) = (m1 |+> m2) : m2s

instance (VarLookupCmb m1 m1, VarLookupCmb m1 m2) => VarLookupCmb [m1] [m2] where
m1 |+> (m2:m2s) = (foldr1 (|+>) m1 |+> m2) : m2s
#if __GLASGOW_HASKELL__ >= 710
instance {-# OVERLAPPING #-}
#else
instance
#endif
VarLookupCmb m1 m2 => VarLookupCmb m1 [m2] where
m1 |+> (m2:m2s) = (m1 |+> m2) : m2s

#if __GLASGOW_HASKELL__ >= 710
instance {-# OVERLAPPING #-}
#else
instance
#endif
(VarLookupCmb m1 m1, VarLookupCmb m1 m2) => VarLookupCmb [m1] [m2] where
m1 |+> (m2:m2s) = (foldr1 (|+>) m1 |+> m2) : m2s

class VarLookupBase m k v | m -> k v where
varlookupEmpty :: m
Expand Down

0 comments on commit 4a95bd8

Please sign in to comment.