[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 10 commits: Ord docs: Add explanation on 'min' and 'max' operator interactions

Marge Bot gitlab at gitlab.haskell.org
Mon Apr 15 05:40:15 UTC 2019



 Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
d2271fe4 by Simon Jakobi at 2019-04-14T12:43:17Z
Ord docs: Add explanation on 'min' and 'max' operator interactions

[ci skip]

- - - - -
e7cad16c by Krzysztof Gogolewski at 2019-04-14T12:49:23Z
Add a safeguard to Core Lint

Lint returns a pair (Maybe a, WarnsAndErrs). The Maybe monad
allows to handle an unrecoverable failure.
In case of such a failure, the error should be added to the second
component of the pair. If this is not done, Lint will silently
accept bad programs. This situation actually happened during
development of linear types. This adds a safeguard.

- - - - -
c54a093f by Ben Gamari at 2019-04-14T12:55:29Z
CODEOWNERS: Add simonmar as owner of rts/linker

I suspect this is why @simonmar wasn't notified of !706.

[skip ci]

- - - - -
1825f50d by Alp Mestanogullari at 2019-04-14T13:01:38Z
Hadrian: don't accept p_dyn for executables, to fix --flavour=prof

- - - - -
fab24336 by Giles Anderson at 2019-04-15T05:40:09Z
Document how -O3 is handled by GHC

    -O2 is the highest value of optimization.
    -O3 will be reverted to -O2.

- - - - -
b5deeebe by Giles Anderson at 2019-04-15T05:40:09Z
Apply suggestion to docs/users_guide/using-optimisation.rst
- - - - -
ded0d8f4 by Fraser Tweedale at 2019-04-15T05:40:10Z
GHCi: fix load order of .ghci files

Directives in .ghci files in the current directory ("local .ghci")
can be overridden by global files.  Change the order in which the
configs are loaded: global and $HOME/.ghci first, then local.

Also introduce a new field to GHCiState to control whether local
.ghci gets sourced or ignored.  This commit does not add a way to
set this value (a subsequent commit will add this), but the .ghci
sourcing routine respects its value.

Fixes: https://gitlab.haskell.org/ghc/ghc/issues/14689
Related: https://gitlab.haskell.org/ghc/ghc/issues/6017
Related: https://gitlab.haskell.org/ghc/ghc/issues/14250

- - - - -
91170328 by Fraser Tweedale at 2019-04-15T05:40:10Z
users-guide: update startup script order

Update users guide to match the new startup script order.  Also
clarify that -ignore-dot-ghci does not apply to scripts specified
via the -ghci-script option.

Part of: https://gitlab.haskell.org/ghc/ghc/issues/14689

- - - - -
a1c6a6c6 by Fraser Tweedale at 2019-04-15T05:40:10Z
GHCi: add 'local-config' setting

Add the ':set local-config { source | ignore }' setting to control
whether .ghci file in current directory will be sourced or not.  The
directive can be set in global config or $HOME/.ghci, which are
processed before local .ghci files.

The default is "source", preserving current behaviour.

Related: https://gitlab.haskell.org/ghc/ghc/issues/6017
Related: https://gitlab.haskell.org/ghc/ghc/issues/14250

- - - - -
852107ad by Fraser Tweedale at 2019-04-15T05:40:10Z
users-guide: document :set local-config

Document the ':set local-config' command and add a warning about
sourcing untrusted local .ghci scripts.

Related: https://gitlab.haskell.org/ghc/ghc/issues/6017
Related: https://gitlab.haskell.org/ghc/ghc/issues/14250

- - - - -


9 changed files:

- CODEOWNERS
- compiler/coreSyn/CoreLint.hs
- docs/users_guide/ghci.rst
- docs/users_guide/using-optimisation.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Monad.hs
- hadrian/src/Settings.hs
- hadrian/src/Settings/Flavours/Profiled.hs
- libraries/ghc-prim/GHC/Classes.hs


Changes:

=====================================
CODEOWNERS
=====================================
@@ -12,7 +12,7 @@
 
 # RTS-like things
 /rts/                             @bgamari @simonmar @osa1 @Phyx @angerman
-/rts/linker/                      @angerman @Phyx
+/rts/linker/                      @angerman @Phyx @simonmar
 /includes/                        @bgamari @simonmar @osa1
 
 # The compiler


=====================================
compiler/coreSyn/CoreLint.hs
=====================================
@@ -2080,7 +2080,7 @@ defaultLintFlags = LF { lf_check_global_ids = False
 newtype LintM a =
    LintM { unLintM ::
             LintEnv ->
-            WarnsAndErrs ->           -- Error and warning messages so far
+            WarnsAndErrs ->           -- Warning and error messages so far
             (Maybe a, WarnsAndErrs) } -- Result and messages (if any)
 
 type WarnsAndErrs = (Bag MsgDoc, Bag MsgDoc)
@@ -2189,10 +2189,13 @@ data LintLocInfo
   | InCo   Coercion     -- Inside a coercion
 
 initL :: DynFlags -> LintFlags -> InScopeSet
-       -> LintM a -> WarnsAndErrs    -- Errors and warnings
+       -> LintM a -> WarnsAndErrs    -- Warnings and errors
 initL dflags flags in_scope m
   = case unLintM m env (emptyBag, emptyBag) of
-      (_, errs) -> errs
+      (Just _, errs) -> errs
+      (Nothing, errs@(_, e)) | not (isEmptyBag e) -> errs
+                             | otherwise -> pprPanic ("Bug in Lint: a failure occurred " ++
+                                                      "without reporting an error message") empty
   where
     env = LE { le_flags = flags
              , le_subst = mkEmptyTCvSubst in_scope


=====================================
docs/users_guide/ghci.rst
=====================================
@@ -2649,6 +2649,17 @@ commonly used commands.
 
     Sets the command used by :ghci-cmd:`:edit` to ⟨cmd⟩.
 
+.. ghci-cmd:: :set local-config; ⟨source|ignore⟩
+
+    If ``ignore``, :file:`./.ghci` files will be ignored (sourcing
+    untrusted local scripts is a security risk).   The default is
+    ``source``.  Set this directive in your user :file:`.ghci`
+    script, i.e. before the local script would be sourced.
+
+    Even when set to ``ignore``, a local script will still be
+    processed if given by :ghc-flag:`-ghci-script` on the command
+    line, or sourced via :ghci-cmd:`:script`.
+
 .. ghci-cmd:: :set prog; ⟨prog⟩
 
     .. index::
@@ -3101,15 +3112,14 @@ When it starts, unless the :ghc-flag:`-ignore-dot-ghci` flag is given, GHCi
 reads and executes commands from the following files, in this order, if
 they exist:
 
-1. :file:`./.ghci`
+1. :file:`{ghcappdata}/ghci.conf`, where ⟨ghcappdata⟩ depends on
+   your system, but is usually something like :file:`$HOME/.ghc` on
+   Unix or :file:`C:/Documents and Settings/user/Application
+   Data/ghc` on Windows.
 
-2. :file:`{appdata}/ghc/ghci.conf`, where ⟨appdata⟩ depends on your system,
-   but is usually something like
-   :file:`C:/Documents and Settings/user/Application Data`
+2. :file:`$HOME/.ghci`
 
-3. On Unix: :file:`$HOME/.ghc/ghci.conf`
-
-4. :file:`$HOME/.ghci`
+3. :file:`./.ghci`
 
 The :file:`ghci.conf` file is most useful for turning on favourite options
 (e.g. ``:set +s``), and defining useful macros.
@@ -3134,6 +3144,12 @@ three subdirectories A, B and C, you might put the following lines in
 fact it works to set it using :ghci-cmd:`:set` like this. The changes won't take
 effect until the next :ghci-cmd:`:load`, though.)
 
+.. warning::
+    Sourcing untrusted :file:`./.ghci` files is a security risk.
+    They can contain arbitrary commands that will be executed as the
+    user.  Use :ghci-cmd:`:set local-config` to inhibit the
+    processing of :file:`./.ghci` files.
+
 Once you have a library of GHCi macros, you may want to source them from
 separate files, or you may want to source your ``.ghci`` file into your
 running GHCi session while debugging it
@@ -3166,8 +3182,9 @@ read:
     :type: dynamic
     :category:
 
-    Read a specific file after the usual startup files. Maybe be
+    Read a specific file after the usual startup files.  May be
     specified repeatedly for multiple inputs.
+    :ghc-flag:`-ignore-dot-ghci` does not apply to these files.
 
 When defining GHCi macros, there is some important behavior you should
 be aware of when names may conflict with built-in commands, especially


=====================================
docs/users_guide/using-optimisation.rst
=====================================
@@ -88,6 +88,17 @@ So, for example, ``ghc -c Foo.hs``
     runtime or space *worse* if you're unlucky. They are normally turned
     on or off individually.
 
+.. ghc-flag:: -O⟨n⟩
+    :shortdesc: Any -On where n > 2 is the same as -O2.
+    :type: dynamic
+    :reverse: -O0
+    :category: optimization-levels
+
+    .. index::
+       single: optimise; aggressively
+
+    Any -On where n > 2 is the same as -O2.
+
 We don't use a ``-O*`` flag for day-to-day work. We use ``-O`` to get
 respectable speed; e.g., when we want to measure something. When we want
 to go for broke, we tend to use ``-O2`` (and we go for lots of coffee


=====================================
ghc/GHCi/UI.hs
=====================================
@@ -102,7 +102,7 @@ import Data.Char
 import Data.Function
 import Data.IORef ( IORef, modifyIORef, newIORef, readIORef, writeIORef )
 import Data.List ( find, group, intercalate, intersperse, isPrefixOf, nub,
-                   partition, sort, sortBy )
+                   partition, sort, sortBy, (\\) )
 import qualified Data.Set as S
 import Data.Maybe
 import Data.Map (Map)
@@ -351,13 +351,16 @@ defFullHelpText =
   "\n" ++
   "   :set <option> ...           set options\n" ++
   "   :seti <option> ...          set options for interactive evaluation only\n" ++
+  "   :set local-config { source | ignore }\n" ++
+  "                               set whether to source .ghci in current dir\n" ++
+  "                               (loading untrusted config is a security issue)\n" ++
   "   :set args <arg> ...         set the arguments returned by System.getArgs\n" ++
   "   :set prog <progname>        set the value returned by System.getProgName\n" ++
   "   :set prompt <prompt>        set the prompt used in GHCi\n" ++
   "   :set prompt-cont <prompt>   set the continuation prompt used in GHCi\n" ++
   "   :set prompt-function <expr> set the function to handle the prompt\n" ++
-  "   :set prompt-cont-function <expr>" ++
-                     "set the function to handle the continuation prompt\n" ++
+  "   :set prompt-cont-function <expr>\n" ++
+  "                               set the function to handle the continuation prompt\n" ++
   "   :set editor <cmd>           set the command used for :edit\n" ++
   "   :set stop [<n>] <cmd>       set the command to run when a breakpoint is hit\n" ++
   "   :unset <option> ...         unset options\n" ++
@@ -482,6 +485,7 @@ interactiveUI config srcs maybe_exprs = do
                    stop               = default_stop,
                    editor             = default_editor,
                    options            = [],
+                   localConfig        = SourceLocalConfig,
                    -- We initialize line number as 0, not 1, because we use
                    -- current line number while reporting errors which is
                    -- incremented after reading a line.
@@ -566,8 +570,6 @@ runGHCi paths maybe_exprs = do
   let
    ignore_dot_ghci = gopt Opt_IgnoreDotGhci dflags
 
-   current_dir = return (Just ".ghci")
-
    app_user_dir = liftIO $ withGhcAppData
                     (\dir -> return (Just (dir </> "ghci.conf")))
                     (return Nothing)
@@ -606,17 +608,44 @@ runGHCi paths maybe_exprs = do
 
   setGHCContextFromGHCiState
 
-  dot_cfgs <- if ignore_dot_ghci then return [] else do
-    dot_files <- catMaybes <$> sequence [ current_dir, app_user_dir, home_dir ]
-    liftIO $ filterM checkFileAndDirPerms dot_files
-  mdot_cfgs <- liftIO $ mapM canonicalizePath' dot_cfgs
+  processedCfgs <- if ignore_dot_ghci
+    then pure []
+    else do
+      userCfgs <- do
+        paths <- catMaybes <$> sequence [ app_user_dir, home_dir ]
+        checkedPaths <- liftIO $ filterM checkFileAndDirPerms paths
+        liftIO . fmap (nub . catMaybes) $ mapM canonicalizePath' checkedPaths
+
+      localCfg <- do
+        let path = ".ghci"
+        ok <- liftIO $ checkFileAndDirPerms path
+        if ok then liftIO $ canonicalizePath' path else pure Nothing
+
+      mapM_ sourceConfigFile userCfgs
+        -- Process the global and user .ghci
+        -- (but not $CWD/.ghci or CLI args, yet)
+
+      behaviour <- localConfig <$> getGHCiState
+
+      processedLocalCfg <- case localCfg of
+        Just path | path `notElem` userCfgs ->
+          -- don't read .ghci twice if CWD is $HOME
+          case behaviour of
+            SourceLocalConfig -> localCfg <$ sourceConfigFile path
+            IgnoreLocalConfig -> pure Nothing
+        _ -> pure Nothing
+
+      pure $ maybe id (:) processedLocalCfg userCfgs
 
   let arg_cfgs = reverse $ ghciScripts dflags
     -- -ghci-script are collected in reverse order
     -- We don't require that a script explicitly added by -ghci-script
     -- is owned by the current user. (#6017)
-  mapM_ sourceConfigFile $ nub $ (catMaybes mdot_cfgs) ++ arg_cfgs
-    -- nub, because we don't want to read .ghci twice if the CWD is $HOME.
+
+  mapM_ sourceConfigFile $ nub arg_cfgs \\ processedCfgs
+    -- Dedup, and remove any configs we already processed.
+    -- Importantly, if $PWD/.ghci was ignored due to configuration,
+    -- explicitly specifying it does cause it to be processed.
 
   -- Perform a :load for files given on the GHCi command line
   -- When in -e mode, if the load fails then we want to stop
@@ -2663,6 +2692,8 @@ setCmd str
 
     Right ("editor",  rest) -> setEditor  $ dropWhile isSpace rest
     Right ("stop",    rest) -> setStop    $ dropWhile isSpace rest
+    Right ("local-config", rest) ->
+        setLocalConfigBehaviour $ dropWhile isSpace rest
     _ -> case toArgs str of
          Left err -> liftIO (hPutStrLn stderr err)
          Right wds -> setOptions wds
@@ -2728,6 +2759,7 @@ showDynFlags show_all dflags = do
 
 setArgs, setOptions :: GhciMonad m => [String] -> m ()
 setProg, setEditor, setStop :: GhciMonad m => String -> m ()
+setLocalConfigBehaviour :: GhciMonad m => String -> m ()
 
 setArgs args = do
   st <- getGHCiState
@@ -2741,6 +2773,14 @@ setProg prog = do
 
 setEditor cmd = modifyGHCiState (\st -> st { editor = cmd })
 
+setLocalConfigBehaviour s
+  | s == "source" =
+      modifyGHCiState (\st -> st { localConfig = SourceLocalConfig })
+  | s == "ignore" =
+      modifyGHCiState (\st -> st { localConfig = IgnoreLocalConfig })
+  | otherwise = throwGhcException
+      (CmdLineError "syntax:  :set local-config { source | ignore }")
+
 setStop str@(c:_) | isDigit c
   = do let (nm_str,rest) = break (not.isDigit) str
            nm = read nm_str


=====================================
ghc/GHCi/UI/Monad.hs
=====================================
@@ -15,6 +15,7 @@ module GHCi.UI.Monad (
         GHCiState(..), GhciMonad(..),
         GHCiOption(..), isOptionSet, setOption, unsetOption,
         Command(..), CommandResult(..), cmdSuccess,
+        LocalConfigBehaviour(..),
         PromptFunction,
         BreakLocation(..),
         TickArray,
@@ -79,6 +80,7 @@ data GHCiState = GHCiState
         prompt_cont    :: PromptFunction,
         editor         :: String,
         stop           :: String,
+        localConfig    :: LocalConfigBehaviour,
         options        :: [GHCiOption],
         line_number    :: !Int,         -- ^ input line
         break_ctr      :: !Int,
@@ -197,6 +199,15 @@ data GHCiOption
                                 -- modules after load
         deriving Eq
 
+-- | Treatment of ./.ghci files.  For now we either load or
+-- ignore.  But later we could implement a "safe mode" where
+-- only safe operations are performed.
+--
+data LocalConfigBehaviour
+  = SourceLocalConfig
+  | IgnoreLocalConfig
+  deriving (Eq)
+
 data BreakLocation
    = BreakLocation
    { breakModule :: !GHC.Module


=====================================
hadrian/src/Settings.hs
=====================================
@@ -60,10 +60,14 @@ programContext :: Stage -> Package -> Action Context
 programContext stage pkg = do
     profiled <- ghcProfiled <$> flavour
     dynGhcProgs <- dynamicGhcPrograms =<< flavour
-    return . Context stage pkg . wayFromUnits . concat $
-        [ [ Profiling  | pkg == ghc && profiled && stage > Stage0 ]
-        , [ Dynamic    | dynGhcProgs && stage > Stage0 ]
-        ]
+    return $ Context stage pkg (wayFor profiled dynGhcProgs)
+
+    where wayFor prof dyn
+            | prof && dyn                          =
+                error "programContext: profiling+dynamic not supported"
+            | pkg == ghc && prof && stage > Stage0 = profiling
+            | dyn && stage > Stage0                = dynamic
+            | otherwise                            = vanilla
 
 -- TODO: switch to Set Package as the order of packages should not matter?
 -- Otherwise we have to keep remembering to sort packages from time to time.


=====================================
hadrian/src/Settings/Flavours/Profiled.hs
=====================================
@@ -10,7 +10,8 @@ profiledFlavour :: Flavour
 profiledFlavour = defaultFlavour
     { name        = "prof"
     , args        = defaultBuilderArgs <> profiledArgs <> defaultPackageArgs
-    , ghcProfiled = True }
+    , ghcProfiled = True
+    , dynamicGhcPrograms = pure False }
 
 profiledArgs :: Args
 profiledArgs = sourceArgs SourceArgs


=====================================
libraries/ghc-prim/GHC/Classes.hs
=====================================
@@ -331,6 +331,10 @@ instance Ord TyCon where
 -- 7. @min x y == if x <= y then x else y@ = 'True'
 -- 8. @max x y == if x >= y then x else y@ = 'True'
 --
+-- Note that (7.) and (8.) do /not/ require 'min' and 'max' to return either of
+-- their arguments. The result is merely required to /equal/ one of the
+-- arguments in terms of '(==)'.
+--
 -- Minimal complete definition: either 'compare' or '<='.
 -- Using 'compare' can be more efficient for complex types.
 --



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/fea4089eba89997d791a03759d082ccad40ed9d6...852107ad049d0d6fc250bbb86ad48b60b3b7255c

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/fea4089eba89997d791a03759d082ccad40ed9d6...852107ad049d0d6fc250bbb86ad48b60b3b7255c
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20190415/97768912/attachment-0001.html>


More information about the ghc-commits mailing list