1
1
mirror of https://github.com/gelisam/hawk.git synced 2024-12-03 15:44:30 +03:00

support for ghc 8.6

in the MonadFail proposal's transitional strategy
  (https://wiki.haskell.org/MonadFail_Proposal#Transitional_strategy),
they explain that in ghc 8.6, -XMonadFailDesugaring becomes on by
default, which means that failed pattern-matching in a do block now
desugars to "MonadFail.fail" instead of "Monad.fail". Thus, for
consistency, our explicit calls to the "fail" function should also call
"MonadFail.fail" instead of "Monad.fail".
This commit is contained in:
Samuel Gélineau 2021-05-07 22:30:06 -04:00
parent cc1ccebc0b
commit 81d8dae213
12 changed files with 81 additions and 24 deletions

View File

@ -1,8 +1,10 @@
cabal-version: 1.24
-- This file has been generated from package.yaml by hpack version 0.34.2.
-- This file has been generated from package.yaml by hpack version 0.33.0.
--
-- see: https://github.com/sol/hpack
--
-- hash: 7dd381c447e05d6cb34cf285e92876a4733dfdf88c0f8caf7e5a6b5945fca4fd
name: haskell-awk
version: 1.2
@ -47,7 +49,7 @@ library
base >=4.9 && <5
, bytestring >=0.10.6
, containers >=0.5.7
, ghc (>8.0 && <8.5) || >8.8
, ghc >8.0
, list-t >=0.4
, stringsearch >=0.3.6.6
if os(windows)
@ -104,7 +106,7 @@ executable hawk
, extra >=1.4
, filelock >=0.1
, filepath >=1.4
, ghc (>8.0 && <8.5) || >8.8
, ghc >8.0
, haskell-awk
, haskell-src-exts >=1.18
, hint >=0.4
@ -182,7 +184,7 @@ test-suite reference
, extra >=1.5
, filelock >=0.1
, filepath >=1.4.1
, ghc (>8.0 && <8.5) || >8.8
, ghc >8.0
, haskell-awk
, haskell-src-exts >=1.18
, hint >=0.6

View File

@ -20,7 +20,7 @@ dependencies:
- base >= 4.9 && < 5
- bytestring >= 0.10.6
- containers >= 0.5.7
- ghc (> 8.0 && < 8.5) || > 8.8
- ghc > 8.0
- list-t >= 0.4
# Windows is not currently supported, see issue #248

View File

@ -3,11 +3,15 @@
-- designed to look as if the options had more precise types than String.
module Control.Monad.Trans.OptionParser where
import Control.Monad
#if MIN_VERSION_base(4,13,0)
import qualified Control.Monad.Fail as Fail
import Prelude hiding (fail)
import Control.Monad hiding (fail)
#if MIN_VERSION_base(4,12,0)
import Control.Monad.Fail (MonadFail, fail)
#else
import Prelude (MonadFail, fail)
#endif
import "mtl" Control.Monad.Identity
import "mtl" Control.Monad.Identity hiding (fail)
import "mtl" Control.Monad.Trans
import Control.Monad.Trans.State
import Data.List
@ -76,9 +80,9 @@ instance Monad m => Monad (OptionParserT o m) where
OptionParserT mx >>= f = OptionParserT (mx >>= f')
where
f' = unOptionParserT . f
#if MIN_VERSION_base(4,13,0)
#if MIN_VERSION_base(4,12,0)
instance Monad m => Fail.MonadFail (OptionParserT o m) where
instance Monad m => MonadFail (OptionParserT o m) where
#endif
fail s = OptionParserT (fail s)
@ -370,7 +374,7 @@ filePath = Setting "path"
-- | The value assigned to the option if the check function doesn't fail with
-- an error. The check functions must return a file path.
--
-- >>> import Control.Monad
-- >>> import Control.Monad hiding (fail)
-- >>> import System.EasyFile (doesDirectoryExist)
-- >>> let testIO args tp p = runUncertainIO $ runOptionParserWith head id (const [""]) tp ["input-dir"] p args
-- >>> let inputDir = const filePath

View File

@ -4,6 +4,9 @@ module Control.Monad.Trans.State.Persistent where
import Control.Applicative
import Control.Monad
#if MIN_VERSION_base(4,12,0)
import Control.Monad.Fail (MonadFail)
#endif
import Control.Monad.IO.Class
import "mtl" Control.Monad.Trans
import Control.Monad.Trans.Maybe
@ -68,7 +71,7 @@ withPersistentState f default_s sx = do
--
-- >>> removeFile f
withPersistentStateT :: forall m s a. (Functor m, MonadIO m,
#if MIN_VERSION_base(4,13,0)
#if MIN_VERSION_base(4,12,0)
MonadFail m,
#endif
Read s, Show s, Eq s)

View File

@ -2,11 +2,15 @@
-- | A computation which may raise warnings or fail in error.
module Control.Monad.Trans.Uncertain where
#if MIN_VERSION_base(4,13,0)
import qualified Control.Monad.Fail as Fail
import Prelude hiding (fail)
#if MIN_VERSION_base(4,12,0)
import Control.Monad.Fail (MonadFail, fail)
#else
import Prelude (MonadFail, fail)
#endif
import "mtl" Control.Monad.Trans
import "mtl" Control.Monad.Identity
import "mtl" Control.Monad.Identity hiding (fail)
import "transformers" Control.Monad.Trans.Except
import "transformers" Control.Monad.Trans.Writer
import System.Exit
@ -34,9 +38,9 @@ instance Monad m => Monad (UncertainT m) where
UncertainT mx >>= f = UncertainT (mx >>= f')
where
f' = unUncertainT . f
#if MIN_VERSION_base(4,13,0)
#if MIN_VERSION_base(4,12,0)
instance Monad m => Fail.MonadFail (UncertainT m) where
instance Monad m => MonadFail (UncertainT m) where
#endif
fail s = UncertainT (throwE s)

View File

@ -1,7 +1,14 @@
{-# LANGUAGE OverloadedStrings, PackageImports, RecordWildCards, ScopedTypeVariables #-}
{-# LANGUAGE CPP, OverloadedStrings, PackageImports, RecordWildCards, ScopedTypeVariables #-}
-- | In which a Haskell module is deconstructed into extensions and imports.
module Data.HaskellModule.Parse (readModule) where
import Prelude hiding (fail)
#if MIN_VERSION_base(4,12,0)
import Control.Monad.Fail (fail)
#else
import Prelude (fail)
#endif
import "mtl" Control.Monad.Trans
import qualified Data.ByteString.Char8 as B
import Data.List

View File

@ -1,9 +1,17 @@
{-# LANGUAGE CPP #-}
-- | A representation of Haskell source code.
--
-- Unlike haskell-src-exts, our goal is not to reconstruct detailed semantics,
-- but to preserve original line numbers (if applicable).
module Data.HaskellSource where
import Prelude hiding (fail)
#if MIN_VERSION_base(4,12,0)
import Control.Monad.Fail (fail)
#else
import Prelude (fail)
#endif
import Control.Monad.Trans.Class
import Data.ByteString.Char8 as B
import System.Directory

View File

@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
-- Copyright 2013 Mario Pastorelli (pastorelli.mario@gmail.com) Samuel Gélineau (gelisam@gmail.com)
--
-- Licensed under the Apache License, Version 2.0 (the "License");
@ -18,7 +19,13 @@ module System.Console.Hawk
( processArgs
) where
import Prelude hiding (fail)
#if MIN_VERSION_base(4,12,0)
import Control.Monad.Fail (fail)
#else
import Prelude (fail)
#endif
import Control.Monad.Trans
import Data.List
import Language.Haskell.Interpreter

View File

@ -1,7 +1,14 @@
{-# LANGUAGE OverloadedStrings, PackageImports, ScopedTypeVariables #-}
{-# LANGUAGE CPP, OverloadedStrings, PackageImports, ScopedTypeVariables #-}
-- | In which Hawk's command-line arguments are structured into a `HawkSpec`.
module System.Console.Hawk.Args.Parse (parseArgs) where
import Prelude hiding (fail)
#if MIN_VERSION_base(4,12,0)
import Control.Monad.Fail (fail)
#else
import Prelude (fail)
#endif
import Data.Char (isSpace)
import Data.Maybe
import "mtl" Control.Monad.Trans

View File

@ -1,4 +1,4 @@
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE CPP, PackageImports #-}
-- | About the directory in which the context is persited.
module System.Console.Hawk.Context.Dir
( createDefaultContextDir
@ -6,7 +6,14 @@ module System.Console.Hawk.Context.Dir
, checkContextDir
) where
import Control.Monad
import Prelude hiding (fail)
import Control.Monad hiding (fail)
#if MIN_VERSION_base(4,12,0)
import Control.Monad.Fail (fail)
#else
import Prelude (fail)
#endif
import "mtl" Control.Monad.Trans
import System.Directory
import System.FilePath

View File

@ -1,10 +1,18 @@
{-# LANGUAGE CPP #-}
-- | A wrapper around the hint library, specialized for Hawk usage.
module System.Console.Hawk.Interpreter
( applyContext
, runHawkInterpreter
) where
import Control.Monad
import Prelude hiding (fail)
import Control.Monad hiding (fail)
#if MIN_VERSION_base(4,12,0)
import Control.Monad.Fail (fail)
#else
import Prelude (fail)
#endif
import Data.List
import Language.Haskell.Interpreter

View File

@ -1,6 +1,6 @@
{-# LANGUAGE CPP #-}
module System.Console.Hawk.UserExpr.CanonicalExpr where
import qualified Data.ByteString.Lazy.Char8 as B
import Data.HaskellExpr