Skip to content

Commit

Permalink
Bring back GHC 7.4+ support
Browse files Browse the repository at this point in the history
  • Loading branch information
bergmark committed Dec 6, 2015
1 parent e629527 commit c73708e
Show file tree
Hide file tree
Showing 22 changed files with 73 additions and 66 deletions.
1 change: 1 addition & 0 deletions fay.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -136,6 +136,7 @@ library

build-depends:
base >= 4 && < 4.9
, base-compat == 0.8.*
, aeson > 0.6 && < 0.11
, bytestring < 0.11
, containers < 0.6
Expand Down
5 changes: 4 additions & 1 deletion src/Fay.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeSynonymInstances #-}
Expand All @@ -23,14 +24,16 @@ module Fay
,getRuntime
) where

import Fay.Compiler.Prelude

import Fay.Compiler
import Fay.Compiler.Misc (ioWarn, printSrcSpanInfo)
import Fay.Compiler.Packages
import Fay.Compiler.Prelude
import Fay.Compiler.Typecheck
import Fay.Config
import qualified Fay.Exts as F
import Fay.Types

import Data.Aeson (encode)
import qualified Data.ByteString.Lazy as L
import Language.Haskell.Exts.Annotated (prettyPrint)
Expand Down
6 changes: 3 additions & 3 deletions src/Fay/Compiler.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,12 +42,12 @@ import Fay.Exts.NoAnnotation (unAnn)
import qualified Fay.Exts.NoAnnotation as N
import Fay.Types

import Control.Monad.Except
import Control.Monad.RWS
import Control.Monad.Except (throwError)
import Control.Monad.RWS (gets, modify)

import qualified Data.Set as S
import Language.Haskell.Exts.Annotated hiding (name)
import Language.Haskell.Names (annotateModule)
import Language.Haskell.Names (annotateModule)

--------------------------------------------------------------------------------
-- Top level entry points
Expand Down
6 changes: 3 additions & 3 deletions src/Fay/Compiler/Decl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,8 +21,8 @@ import Fay.Exts.NoAnnotation (unAnn)
import qualified Fay.Exts.Scoped as S
import Fay.Types

import Control.Monad.Except
import Control.Monad.RWS
import Control.Monad.Except (throwError)
import Control.Monad.RWS (gets, modify)
import Language.Haskell.Exts.Annotated hiding (binds, loc, name)

-- | Compile Haskell declaration.
Expand Down Expand Up @@ -161,7 +161,7 @@ compileDataDecl toplevel tyvars constructors =
JsSetConstructor qname $
JsFun (Just $ JsConstructor qname)
fields
(for fields $ \field -> JsSetProp JsThis field (JsName field))
(flip fmap fields $ \field -> JsSetProp JsThis field (JsName field))
Nothing

-- Creates a function to initialize the record by regular application
Expand Down
2 changes: 1 addition & 1 deletion src/Fay/Compiler/Desugar.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ import Fay.Compiler.QName (unQual, unname)
import Fay.Exts.NoAnnotation (unAnn)
import Fay.Types (CompileError (..))

import Control.Monad.Except
import Control.Monad.Except (throwError)
import Control.Monad.Reader (asks)
import qualified Data.Generics.Uniplate.Data as U
import Language.Haskell.Exts.Annotated hiding (binds, loc, name)
Expand Down
6 changes: 3 additions & 3 deletions src/Fay/Compiler/Exp.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,11 +27,11 @@ import Fay.Exts.Scoped (noI)
import qualified Fay.Exts.Scoped as S
import Fay.Types

import Control.Monad.Except (throwError)
import Control.Monad.Except (throwError)
import Control.Monad.RWS (asks, gets)
import qualified Data.Char as Char
import Language.Haskell.Exts.Annotated hiding (alt, binds, name, op)
import Language.Haskell.Names (Scoped (Scoped), NameInfo (RecExpWildcard))
import Language.Haskell.Names (NameInfo (RecExpWildcard), Scoped (Scoped))

-- | Compile Haskell expression.
compileExp :: S.Exp -> Compile JsExp
Expand Down Expand Up @@ -291,7 +291,7 @@ compileRecConstr origExp name fieldUpdates = do
exp <- compileExp value
return [JsSetProp (JsNameVar $ withIdent lowerFirst $ unQualify o) (JsNameVar $ unQualify field) exp]
updateStmt o (FieldWildcard (wildcardFields -> fields)) =
return $ for fields $ \fieldName -> JsSetProp (JsNameVar . withIdent lowerFirst . unQualify . unAnn $ o)
return $ flip fmap fields $ \fieldName -> JsSetProp (JsNameVar . withIdent lowerFirst . unQualify . unAnn $ o)
(JsNameVar fieldName)
(JsName $ JsNameVar fieldName)
-- I couldn't find a code that generates (FieldUpdate (FieldPun ..))
Expand Down
4 changes: 2 additions & 2 deletions src/Fay/Compiler/FFI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,8 +25,8 @@ import qualified Fay.Exts.NoAnnotation as N
import qualified Fay.Exts.Scoped as S
import Fay.Types

import Control.Monad.Except
import Control.Monad.Writer
import Control.Monad.Except (throwError)
import Control.Monad.Writer (tell)
import Data.Generics.Schemes
import Language.ECMAScript3.Parser as JS
import Language.ECMAScript3.Syntax
Expand Down
8 changes: 4 additions & 4 deletions src/Fay/Compiler/Import.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,8 +7,8 @@
-- which at this point is InitialPass's preprocessing
-- and Compiler's code generation
module Fay.Compiler.Import
(startCompile
,compileWith
( startCompile
, compileWith
) where

import Fay.Compiler.Prelude
Expand All @@ -20,8 +20,8 @@ import qualified Fay.Exts as F
import Fay.Exts.NoAnnotation (unAnn)
import Fay.Types

import Control.Monad.Except
import Control.Monad.RWS
import Control.Monad.Except (throwError)
import Control.Monad.RWS (ask, get, gets, lift, listen, modify)
import Language.Haskell.Exts.Annotated hiding (name, var)
import System.Directory
import System.FilePath
Expand Down
6 changes: 3 additions & 3 deletions src/Fay/Compiler/InitialPass.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,8 +19,8 @@ import qualified Fay.Exts as F
import Fay.Exts.NoAnnotation (unAnn)
import Fay.Types

import Control.Monad.Except
import Control.Monad.RWS
import Control.Monad.Except (throwError)
import Control.Monad.RWS (modify)
import qualified Data.Map as M
import Language.Haskell.Exts.Annotated hiding (name, var)
import qualified Language.Haskell.Names as HN (getInterfaces)
Expand Down Expand Up @@ -90,7 +90,7 @@ scanRecordDecls :: F.Decl -> Compile ()
scanRecordDecls decl = do
case decl of
DataDecl _loc ty _ctx (F.declHeadName -> name) qualcondecls _deriv -> do
let addIt = let ns = for qualcondecls (\(QualConDecl _loc' _tyvarbinds _ctx' condecl) -> conDeclName condecl)
let addIt = let ns = flip fmap qualcondecls (\(QualConDecl _loc' _tyvarbinds _ctx' condecl) -> conDeclName condecl)
in addRecordTypeState name ns
case ty of
DataType{} -> addIt
Expand Down
2 changes: 1 addition & 1 deletion src/Fay/Compiler/Misc.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ import qualified Fay.Exts.NoAnnotation as N
import qualified Fay.Exts.Scoped as S
import Fay.Types

import Control.Monad.Except
import Control.Monad.Except (runExceptT, throwError)
import Control.Monad.RWS (asks, gets, modify, runRWST)
import Data.Version (parseVersion)
import Language.Haskell.Exts.Annotated hiding (name)
Expand Down
4 changes: 2 additions & 2 deletions src/Fay/Compiler/Optimizer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,8 +13,8 @@ import Fay.Compiler.Prelude
import Fay.Compiler.Misc
import Fay.Types

import Control.Monad.State
import Control.Monad.Writer
import Control.Monad.State (State, modify, runState)
import Control.Monad.Writer (runWriter, tell)
import qualified Fay.Exts.NoAnnotation as N
import Language.Haskell.Exts.Annotated hiding (app, name, op)

Expand Down
5 changes: 2 additions & 3 deletions src/Fay/Compiler/Packages.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
{-# LANGUAGE TupleSections #-}

{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE TupleSections #-}
-- | Dealing with Cabal packages in Fay's own special way.

module Fay.Compiler.Packages where

import Fay.Compiler.Prelude
Expand Down
6 changes: 3 additions & 3 deletions src/Fay/Compiler/Pattern.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,10 +15,10 @@ import qualified Fay.Exts.NoAnnotation as N
import qualified Fay.Exts.Scoped as S
import Fay.Types

import Control.Monad.Except
import Control.Monad.Reader
import Control.Monad.Except (throwError)
import Control.Monad.Reader (ask)
import Language.Haskell.Exts.Annotated hiding (name)
import Language.Haskell.Names (Scoped (Scoped), NameInfo (RecPatWildcard))
import Language.Haskell.Names (NameInfo (RecPatWildcard), Scoped (Scoped))

-- | Compile the given pattern against the given expression.
compilePat :: JsExp -> S.Pat -> [JsStmt] -> Compile [JsStmt]
Expand Down
36 changes: 17 additions & 19 deletions src/Fay/Compiler/Prelude.hs
Original file line number Diff line number Diff line change
@@ -1,46 +1,48 @@
-- | Re-exports of base functionality. Note that this module is just
-- used inside the compiler. It's not compiled to JavaScript.
-- Based on the base-extended package (c) 2013 Simon Meier, licensed as BSD3.
{-# LANGUAGE NoImplicitPrelude #-}
module Fay.Compiler.Prelude
( module Prelude -- Partial
( module Prelude.Compat -- Partial

-- * Control modules
, module Control.Applicative
, module Control.Arrow -- Partial
, module Control.Monad
, module Control.Monad.Compat

-- * Data modules
, module Data.Char -- Partial
, module Data.Data -- Partial
, module Data.Char -- Partial
, module Data.Data -- Partial
, module Data.Either
, module Data.Function
, module Data.List -- Partial
, module Data.List.Compat -- Partial
, module Data.Maybe
, module Data.Monoid -- Partial
, module Data.Monoid -- Partial
, module Data.Ord
, module Data.Traversable

-- * Safe
, module Safe

-- * Additions
, anyM
, for
, io
, readAllFromProcess
) where

import Control.Applicative
import Control.Arrow (first, second, (&&&), (***), (+++), (|||))
import Control.Monad hiding (guard)
import Data.Char hiding (GeneralCategory (..))
import Data.Data (Data (..), Typeable)
import Control.Arrow (first, second, (&&&), (***), (+++), (|||))
import Control.Monad.Compat hiding (guard)
import Data.Char hiding (GeneralCategory (..))
import Data.Data (Data (..), Typeable)
import Data.Either
import Data.Function (on)
import Data.List hiding (delete)
import Data.Function (on)
import Data.List.Compat
import Data.Maybe
import Data.Monoid (Monoid (..), (<>))
import Data.Monoid (Monoid (..), (<>))
import Data.Ord
import Prelude hiding (exp, mod)
import Data.Traversable
import Prelude.Compat hiding (exp, mod)
import Safe

import Control.Monad.Except
Expand All @@ -55,10 +57,6 @@ io = liftIO
anyM :: Monad m => (a -> m Bool) -> [a] -> m Bool
anyM p l = return . not . null =<< filterM p l

-- | Flip of map.
for :: (Functor f) => f a -> (a -> b) -> f b
for = flip fmap

-- | Read from a process returning both std err and out.
readAllFromProcess :: FilePath -> [String] -> String -> IO (Either (String,String) (String,String))
readAllFromProcess program flags input = do
Expand Down
5 changes: 2 additions & 3 deletions src/Fay/Compiler/Print.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,11 @@
{-# OPTIONS -fno-warn-orphans #-}
{-# LANGUAGE OverloadedStrings #-}

{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
-- | Code printers. Can be used to produce both pretty and not
-- pretty output.
--
-- Special constructors and symbols in Haskell are encoded to
-- JavaScript appropriately.

module Fay.Compiler.Print where

import Fay.Compiler.Prelude
Expand Down
2 changes: 1 addition & 1 deletion src/Fay/Config.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}
-- | Configuring the compiler

module Fay.Config
( Config
( configOptimize
Expand Down
3 changes: 2 additions & 1 deletion src/Fay/Convert.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RankNTypes #-}
Expand All @@ -18,7 +19,7 @@ module Fay.Convert

import Fay.Compiler.Prelude

import Control.Monad.State
import Control.Monad.State (evalStateT, get, lift, put)
import Control.Spoon
import Data.Aeson
import Data.Aeson.Types (parseEither)
Expand Down
10 changes: 6 additions & 4 deletions src/haskell-names/Language/Haskell/Names/Exports.hs
Original file line number Diff line number Diff line change
@@ -1,20 +1,22 @@
{-# OPTIONS -fno-warn-name-shadowing #-}
{-# LANGUAGE NoMonoLocalBinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE NoMonoLocalBinds #-}
{-# LANGUAGE TypeFamilies #-}
module Language.Haskell.Names.Exports
( processExports
) where

import Fay.Compiler.ModuleT
import Fay.Compiler.Prelude

import Fay.Compiler.ModuleT
import Language.Haskell.Names.GlobalSymbolTable as Global
import Language.Haskell.Names.ModuleSymbols
import Language.Haskell.Names.ScopeUtils
import Language.Haskell.Names.SyntaxUtils
import Language.Haskell.Names.Types (Error (..), GName (..), ModuleNameS, NameInfo (..),
Scoped (..), Symbols (..), mkTy, mkVal, st_origName)

import Control.Monad.Writer
import Control.Monad.Writer (WriterT (WriterT), runWriterT)
import qualified Data.Map as Map
import qualified Data.Set as Set
import Language.Haskell.Exts.Annotated
Expand Down
1 change: 1 addition & 0 deletions src/haskell-names/Language/Haskell/Names/GetBound.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UndecidableInstances #-}
module Language.Haskell.Names.GetBound
Expand Down
10 changes: 6 additions & 4 deletions src/haskell-names/Language/Haskell/Names/Imports.hs
Original file line number Diff line number Diff line change
@@ -1,17 +1,19 @@
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS -fno-warn-name-shadowing #-}
{-# OPTIONS -fno-warn-orphans #-} -- ModName (ModuleName l)
module Language.Haskell.Names.Imports (processImports) where

import Fay.Compiler.ModuleT
import Fay.Compiler.Prelude

import Fay.Compiler.ModuleT
import qualified Language.Haskell.Names.GlobalSymbolTable as Global
import Language.Haskell.Names.ScopeUtils
import Language.Haskell.Names.SyntaxUtils
import Language.Haskell.Names.Types

import Control.Monad.Writer
import Control.Monad.Writer (WriterT (WriterT), runWriterT)
import Data.Foldable (fold)
import Data.Lens.Light
import qualified Data.Map as Map
Expand Down
5 changes: 2 additions & 3 deletions src/haskell-names/Language/Haskell/Names/Open/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@
{-# LANGUAGE ImplicitParams #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverlappingInstances #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
Expand Down Expand Up @@ -38,6 +39,7 @@ module Language.Haskell.Names.Open.Base
, lTable
) where

import Fay.Compiler.Prelude
import Language.Haskell.Names.GetBound
import qualified Language.Haskell.Names.GlobalSymbolTable as Global
import qualified Language.Haskell.Names.LocalSymbolTable as Local
Expand All @@ -46,9 +48,6 @@ import Language.Haskell.Names.RecordWildcards
import Control.Monad.Identity
import Data.Generics.Traversable
import Data.Lens.Light
import Data.List
import Data.Monoid
import Data.Typeable
import GHC.Exts (Constraint)
import Language.Haskell.Exts.Annotated

Expand Down
Loading

0 comments on commit c73708e

Please sign in to comment.