Skip to content

Commit

Permalink
Clear out new base-4.8 warnings
Browse files Browse the repository at this point in the history
  • Loading branch information
glguy committed Aug 28, 2015
1 parent f7e6093 commit f312c4f
Show file tree
Hide file tree
Showing 3 changed files with 31 additions and 6 deletions.
10 changes: 9 additions & 1 deletion src/Text/LLVM.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE RecursiveDo #-}
{-# LANGUAGE TypeOperators #-}
Expand All @@ -7,6 +8,10 @@
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeSynonymInstances #-}

#ifndef MIN_VERSION_base
#define MIN_VERSION_base(x,y,z) 1
#endif

module Text.LLVM (
-- * LLVM Monad
LLVM()
Expand Down Expand Up @@ -103,7 +108,6 @@ module Text.LLVM (

import Text.LLVM.AST

import Control.Applicative ( Applicative )
import Control.Monad.Fix (MonadFix)
import Data.Char (ord)
import Data.Int (Int8,Int16,Int32,Int64)
Expand All @@ -114,6 +118,10 @@ import qualified Data.Foldable as F
import qualified Data.Sequence as Seq
import qualified Data.Map.Strict as Map

#if !(MIN_VERSION_base(4,8,0))
import Control.Applicative ( Applicative )
#endif


-- Fresh Names -----------------------------------------------------------------

Expand Down
16 changes: 12 additions & 4 deletions src/Text/LLVM/AST.hs
Original file line number Diff line number Diff line change
@@ -1,23 +1,31 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RecordWildCards #-}

#ifndef MIN_VERSION_base
#define MIN_VERSION_base(x,y,z) 1
#endif

module Text.LLVM.AST where

import Control.Applicative ((<$))
import Control.Monad (MonadPlus(mzero),(<=<),msum,guard,liftM,liftM3)
import Data.Char (isAscii,isPrint,ord,toUpper)
import Data.Foldable (Foldable(foldMap))
import Data.Int (Int32)
import Data.List (intersperse,genericIndex,genericLength,unfoldr)
import Data.Maybe (fromMaybe)
import Data.Monoid (Monoid(..))
import Data.String (IsString(fromString))
import Data.Traversable (Traversable(sequenceA))
import Numeric (showHex)
import Text.PrettyPrint.HughesPJ

#if !(MIN_VERSION_base(4,8,0))
import Control.Applicative ((<$))
import Data.Foldable (Foldable(foldMap))
import Data.Monoid (Monoid(..))
import Data.Traversable (Traversable(sequenceA))
#endif


commas :: [Doc] -> Doc
commas = hsep . punctuate (char ',')
Expand Down
11 changes: 10 additions & 1 deletion src/Text/LLVM/Labels.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,19 @@
{-# LANGUAGE CPP #-}

#ifndef MIN_VERSION_base
#define MIN_VERSION_base(x,y,z) 1
#endif

module Text.LLVM.Labels where

import Text.LLVM.AST

import Control.Applicative ((<$>),Applicative(..))
import qualified Data.Traversable as T

#if !(MIN_VERSION_base(4,8,0))
import Control.Applicative ((<$>),Applicative(..))
#endif

class Functor f => HasLabel f where
-- | Given a function for resolving labels, where the presence of a symbol
-- denotes a label in a different function, rename all labels in a function.
Expand Down

0 comments on commit f312c4f

Please sign in to comment.