summaryrefslogtreecommitdiff
path: root/libraries/base
Commit message (Collapse)AuthorAgeFilesLines
* Testsuite: fix T12010 for realThomas Miedema2016-05-223-11/+7
| | | | | | | | | | | | | | | | | * Use `extra_files` instead of (the deprecated) `extra_clean` (#11980). * Don't depend on generated files from build tree (libraries/base/include/HsBaseConfig.h). Running 'make test TEST=T12010' should work, even without building GHC first (it will use the system installed ghc). Test Plan: 'make test TEST=T12010' on Linux and Windows. Reviewed by: Phyx Differential Revision: https://phabricator.haskell.org/D2256 GHC Trac Issues: #12010
* Fix failing T12010Tamar Christina2016-05-213-5/+6
| | | | | | | | | | | | | | | | Summary: T12010 seems to be failing because it can't find the correct paths. This gives the test some more qualified paths. Test Plan: make TEST=12010 Reviewers: hvr, bgamari, austin, thomie Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D2252 GHC Trac Issues: #12010
* Use the correct return type for Windows' send()/recv() (Fix #12010)Tamar Christina2016-05-197-29/+131
| | | | | | | | | | | | | | | | | | | | | | | | | | Summary: They return signed 32 bit ints on Windows, even on a 64 bit OS, rather than Linux's 64 bit ssize_t. This means when recv() returned -1 to signal an error we thought it was 4294967295. It was converted to an int, -1 and the buffer was memcpy'd which caused a segfault. Other bad stuff happened with send()s. See also note CSsize in System.Posix.Internals. Add a test for #12010 Test Plan: - GHC testsuite (T12010) - http-conduit test (https://github.com/snoyberg/http-client/issues/191) Reviewers: austin, hvr, bgamari, Phyx Reviewed By: Phyx Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2170 GHC Trac Issues: #12010
* Testsuite: don't skip concio001 and concio001_thrThomas Miedema2016-05-172-4/+4
| | | | | I think they were skipped before because they write to the same output file (concio001). This is no longer a problem.
* Make Generic1 poly-kindedRyanGlScott2016-05-123-48/+73
| | | | | | | | | | | | | | | | | | | | | | | This generalizes the `Generic1` typeclass to be of kind `k -> *`, and this also makes the relevant datatypes and typeclasses in `GHC.Generics` poly-kinded. If `PolyKinds` is enabled, `DeriveGeneric` derives `Generic1` instances such that they use the most general kind possible. Otherwise, deriving `Generic1` defaults to make an instance where the argument is of kind `* -> *` (the current behavior). Fixes #10604. Depends on D2117. Test Plan: ./validate Reviewers: kosmikus, dreixel, goldfire, austin, hvr, simonpj, bgamari Reviewed By: simonpj, bgamari Subscribers: thomie, ekmett Differential Revision: https://phabricator.haskell.org/D2168 GHC Trac Issues: #10604
* base: Export runRW# from GHC.ExtsBen Gamari2016-05-041-0/+3
| | | | | | | | | | | | | | | Seems like this should be available in GHC.Exts. Thanks for @carter for pointing this out. Test Plan: Validate Reviewers: rwbarton, hvr, austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D2171
* Export oneShot from GHC.ExtsJoachim Breitner2016-05-041-1/+1
| | | | as suggested by carter in #12011.
* StaticPointers: Allow closed vars in the static form.Facundo Domínguez2016-05-022-9/+20
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: With this patch closed variables are allowed regardless of whether they are bound at the top level or not. The FloatOut pass is always performed. When optimizations are disabled, only expressions that go to the top level are floated. Thus, the applications of the StaticPtr data constructor are always floated. The CoreTidy pass makes sure the floated applications appear in the symbol table of object files. It also collects the floated bindings and inserts them in the static pointer table. The renamer does not check anymore if free variables appearing in the static form are top-level. Instead, the typechecker looks at the tct_closed flag to decide if the free variables are closed. The linter checks that applications of StaticPtr only occur at the top of top-level bindings after the FloatOut pass. The field spInfoName of StaticPtrInfo has been removed. It used to contain the name of the top-level binding that contains the StaticPtr application. However, this information is no longer available when the StaticPtr is constructed, as the binding name is determined now by the FloatOut pass. Test Plan: ./validate Reviewers: goldfire, simonpj, austin, hvr, bgamari Reviewed By: simonpj Subscribers: thomie, mpickering, mboes Differential Revision: https://phabricator.haskell.org/D2104 GHC Trac Issues: #11656
* Export constructors for IntPtr and WordPtrRyanGlScott2016-05-024-5/+40
| | | | | | | | | | | | | | | | | | | | This finishes what #5529 started by exporting the constructors for `IntPtr` and `WordPtr` from `Foreign.Ptr`, allowing them to be used in `foreign` declarations. Fixes #11983. Test Plan: `make TEST=T11983` Reviewers: simonpj, hvr, bgamari, austin Reviewed By: simonpj Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D2142 GHC Trac Issues: #11983
* Testsuite: fixup lots of testsThomas Miedema2016-04-264-11/+11
| | | | | | | | | These aren't run very often, because they require external libraries. https://ghc.haskell.org/trac/ghc/wiki/Building/RunningTests/Running#AdditionalPackages maessen-hashtab still doesn't compile, QuickCheck api changed. Update submodule hpc.
* Testsuite: Delete test for deprecated "packedstring"Thomas Miedema2016-04-263-15/+1
|
* Mark GHC.Stack.Types TrustworthyHerbert Valerio Riedel2016-04-191-1/+2
| | | | | | | GHC can't infer this module safe due to the `GHC.Types (Char, Int)` and the (dummy) `GHC.Integer ()` import. If only `GHC.Types` was marked Trustworthy or Safe...
* Use `@since` annotation in GHC.ExecutionStackHerbert Valerio Riedel2016-04-112-2/+2
| | | | | While ad532ded871a9a5180388a2b7cdbdc26e053284c fixed the version number, this fixes the markup...
* Deriving Functor-like classes should unify kind variablesRyanGlScott2016-04-111-6/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | While the deriving machinery always unifies the kind of the typeclass argument with the kind of the datatype, this proves not to be sufficient to produce well kinded instances for some poly-kinded datatypes. For example: ``` newtype Compose (f :: k2 -> *) (g :: k1 -> k2) (a :: k1) = Compose (f (g a)) deriving Functor ``` would fail because only `k1` would get unified with `*`, causing the following ill kinded instance to be generated: ``` instance (Functor (f :: k2 -> *), Functor (g :: * -> k2)) => Functor (Compose f g) where ... ``` To prevent this, we need to take the subtypes and unify their kinds with `* -> *`. Fixes #10524 for good. Test Plan: ./validate Reviewers: simonpj, hvr, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2097 GHC Trac Issues: #10524, #10561
* Added (more) missing instances for Identity and ConstShane O'Brien2016-04-114-8/+19
| | | | | | | | | | | | | | | | | | | * `Identity` and `Const` now have `Num`, `Real`, `Integral`, `Fractional`, `Floating`, `RealFrac` and `RealFloat` instances * `Identity` and `Const` now have `Bits` and `FiniteBits` instances * `Identity` and `Const` now have `IsString` instances Reviewers: RyanGlScott, austin, hvr, bgamari, ekmett Reviewed By: ekmett Subscribers: nomeata, ekmett, RyanGlScott, thomie Differential Revision: https://phabricator.haskell.org/D2079 GHC Trac Issues: #11790
* Change runtime linker to perform lazy loading of symbols/sectionsTamar Christina2016-04-113-34/+109
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The Runtime Linker is currently eagerly loading all object files on all platforms which do not use the system linker for `GHCi`. The problem with this approach is that it requires all symbols to be found. Even those of functions never used/called. This makes the number of libraries required to link things like `mingwex` quite high. To work around this the `rts` was relying on a trick. It itself was compiled with `MingW64-w`'s `GCC`. So it was already linked against `mingwex`. As such, it re-exported the symbols from itself. While this worked it made it impossible to link against `mingwex` in user libraries. And with this means no `C99` code could ever run in `GHCi` on Windows without having the required symbols re-exported from the rts. Consequently this rules out a large number of packages on Windows. SDL2, HMatrix etc. After talking with @rwbarton I have taken the approach of loading entire object files when a symbol is needed instead of doing the dependency tracking on a per symbol basis. This is a lot less fragile and a lot less complicated to implement. The changes come down to the following steps: 1) modify the linker to and introduce a new state for ObjectCode: `Needed`. A Needed object is one that is required for the linking to succeed. The initial set consists of all Object files passed as arguments to the link. 2) Change `ObjectCode`'s to be indexed but not initialized or resolved. This means we know where we would load the symbols, but haven't actually done so. 3) Mark any `ObjectCode` belonging to `.o` passed as argument as required: ObjectState `NEEDED`. 4) During `Resolve` object calls, mark all `ObjectCode` containing the required symbols as `NEEDED` 5) During `lookupSymbol` lookups, (which is called from `linkExpr` and `linkDecl` in `GHCI.hs`) is the symbol is in a not-yet-loaded `ObjectCode` then load the `ObjectCode` on demand and return the address of the symbol. Otherwise produce an unresolved symbols error as expected. 6) On `unloadObj` we then change the state of the object and remove it's symbols from the `reqSymHash` table so it can be reloaded. This change affects all platforms and OSes which use the runtime linker. It seems there are no real perf tests for `GHCi`, but performance shouldn't be impacted much. We gain a lot of time not loading all `obj` files, and we lose some time in `lookupSymbol` when we're finding sections that have to be loaded. The actual finding itself is O(1) (Assuming the hashtnl is perfect) It also consumes slighly more memory as instead of storing just the address of a symbol I also store some other information, like if the symbol is weak or not. This change will break any packages relying on renamed POSIX functions that were re-named and re-exported by the rts. Any packages following the proper naming for functions as found on MSDN will work fine. Test Plan: ./validate on all platforms which use the Runtime linker. Reviewers: thomie, rwbarton, simonmar, erikd, bgamari, austin, hvr Reviewed By: erikd Subscribers: kgardas, gridaphobe, RyanGlScott, simonmar, rwbarton, #ghc_windows_task_force Differential Revision: https://phabricator.haskell.org/D1805 GHC Trac Issues: #11223
* Typos in NoteJoachim Breitner2016-04-101-8/+5
|
* base: Fix "since" annotation on GHC.ExecutionStackBen Gamari2016-04-102-2/+2
| | | | I have no idea where "4.11" came from.
* Add doc to (<=<) comparing its type to (.)Chris Martin2016-04-101-1/+6
| | | | | | | | | | | | | | This is another documentation addition similar to D1989, this time comparing the type of the Kleisli composition operator (<=<) to that of plain function composition (.). Reviewers: hvr, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2100
* Provide an optimized replicateM_ implementation #11795Michael Snoyman2016-04-101-5/+38
| | | | | | | | | | | | | | | | | | In my testing, the worker/wrapper transformation applied here significantly decreases the number of allocations performed when using replicateM_. Additionally, this version of the function behaves correctly for negative numbers (namely, it will behave the same as replicateM_ 0, which is what previous versions of base have done). Reviewers: bgamari, simonpj, hvr, austin Reviewed By: bgamari, simonpj, austin Subscribers: nomeata, simonpj, mpickering, thomie Differential Revision: https://phabricator.haskell.org/D2086 GHC Trac Issues: #11795
* Remove obsolete comment about the implementation of foldlJoachim Breitner2016-04-081-4/+0
|
* GHC.Base: Use thenIO in instance Applicative IOJoachim Breitner2016-04-081-3/+3
| | | | | | | | Since recent changes to CSE, the previous definition were no longer CSEd with thenIO, which resulted in extra steps in the simplifier and hence slightly larger compile times. See ticket:11781#comment:7. Differential Revision: https://phabricator.haskell.org/D2092
* Don't infer CallStacksEric Seidel2016-04-042-11/+11
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | We originally wanted CallStacks to be opt-in, but dealing with let binders complicated things, forcing us to infer CallStacks. It turns out that the inference is actually unnecessary though, we can let the wanted CallStacks bubble up to the outer context by refusing to quantify over them. Eventually they'll be solved from a given CallStack or defaulted to the empty CallStack if they reach the top. So this patch prevents GHC from quantifying over CallStacks, getting us back to the original plan. There's a small ugliness to do with PartialTypeSignatures, if the partial theta contains a CallStack constraint, we *do* want to quantify over the CallStack; the user asked us to! Note that this means that foo :: _ => CallStack foo = getCallStack callStack will be an *empty* CallStack, since we won't infer a CallStack for the hole in the theta. I think this is the right move though, since we want CallStacks to be opt-in. One can always write foo :: (HasCallStack, _) => CallStack foo = getCallStack callStack to get the CallStack and still have GHC infer the rest of the theta. Test Plan: ./validate Reviewers: goldfire, simonpj, austin, hvr, bgamari Reviewed By: simonpj, bgamari Subscribers: bitemyapp, thomie Projects: #ghc Differential Revision: https://phabricator.haskell.org/D1912 GHC Trac Issues: #11573
* Kill the magic of AnyBen Gamari2016-03-301-0/+3
| | | | | | | | | | | | | | | | | | | | This turns `Any` into a standard wired-in type family defined in `GHC.Types`, instead its current incarnation as a magical creature provided by the `GHC.Prim`. Also kill `AnyK`. See #10886. Test Plan: Validate Reviewers: simonpj, goldfire, austin, hvr Reviewed By: simonpj Subscribers: goldfire, thomie Differential Revision: https://phabricator.haskell.org/D2049 GHC Trac Issues: #10886
* Defer inlining of Ord methodsBen Gamari2016-03-302-26/+174
| | | | | | This performs the same refactoring performed in D1980 for Eq on Ord, rewriting the class operations in terms of monomorphic helpers than can be reliably matched in rewrite rules.
* base: Fix haddock typoBen Gamari2016-03-291-1/+1
|
* base: Add comment noting import loopBen Gamari2016-03-291-0/+2
|
* Add Data.Functor.Classes instances for Proxy (trac issue #11756)Andrew Martin2016-03-292-0/+21
| | | | | | | | | | | | | | Test Plan: currently no test plan Reviewers: hvr, RyanGlScott, bgamari, austin Reviewed By: RyanGlScott, bgamari, austin Subscribers: thomie, RyanGlScott, andrewthad Differential Revision: https://phabricator.haskell.org/D2051 GHC Trac Issues: #11756
* base: Document caveats about Control.Concurrent.ChanErik de Castro Lopo2016-03-291-0/+5
| | | | | | | | | | | | | | | These are implemented using `MVars` which have known caveats. Suggest the use of `TChan` from the stm library instead. Test Plan: n/a Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2047
* Scrap IRIX supportHerbert Valerio Riedel2016-03-282-2/+2
| | | | | | | | | | | | | | | | Long time ago, IRIX was way ahead of its time in the last century with its SMP capabilities of scaling up to 1024 processors and other features such as XFS or OpenGL that originated in IRIX and live on to this day in other operating systems. However, IRIX's last software update was in 2006 and support ended around 2013 according to [1], so it's considered an extinct platform by now. So this commit message is effectively an obituary for GHC's IRIX support. R.I.P. IRIX [1]: https://en.wikipedia.org/wiki/IRIX
* base: Fix GHC.Word and GHC.Int on 32-bit platformsBen Gamari2016-03-252-4/+4
| | | | | | | Due to a cut-and-paste error D1980 (#11688) broke 32-bit platforms. This should fix it. See #11750.
* Defer inlining of Eq for primitive typesBen Gamari2016-03-244-25/+155
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: This is one solution to #11688, wherein (==) was inlined to soon defeating a rewrite rule provided by bytestring. Since the RHSs of Eq's methods are simple, there is little to be gained and much to be lost by inlining them early. For instance, the bytestring library provides, ```lang=haskell break :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) breakByte :: Word8 -> ByteString -> (ByteString, ByteString) ``` and a rule ``` forall x. break ((==) x) = breakByte x ``` since `breakByte` implments an optimized version of `break (== x)` for known `x :: Word8`. If we allow `(==)` to be inlined too early, we will prevent this rule from firing. This was the cause of #11688. This patch just defers the `Eq` methods, although it's likely worthwhile giving `Ord` this same treatment. This regresses compiler allocations for T9661 by about 8% due to the additional inlining that we now require the simplifier to perform. Updates the `bytestring` submodule to include updated rewrite rules which match on `eqWord8` instead of `(==)`. Test Plan: * Validate, examine performance impact Reviewers: simonpj, hvr, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1980 GHC Trac Issues: #11688
* base: Fix ClockGetTime on OS XBen Gamari2016-03-242-2/+2
| | | | | | | | | | | | | | | | | Apparently _POSIX_CPUTIME may be defined as -1 if CLOCK_PROCESS_CPUTIME_ID isn't defined. Test Plan: Validate Reviewers: austin, hvr, erikd, goldfire Reviewed By: erikd, goldfire Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2028 GHC Trac Issues: #11733
* base: Fix CPUTime on WindowsBen Gamari2016-03-201-14/+11
| | | | Arg, silly CPP.
* base: Rework System.CPUTimeBen Gamari2016-03-208-121/+276
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This started when I noticed that `getCPUTime` only provides 1 millisecond resolution on Linux. Unfortunately the previous implementation was quite unmaintainable, so this ended up being a bit more involved than I expected. Here we do several things, * Split up `System.CPUTime` * Add support for `clock_gettime`, allowing for significantly more precise timing information when available * Fix System.CPUTime resolution for Windows. While it's hard to get reliable numbers, the consensus is that Windows only provides 16 millisecond resolution in GetProcessTimes (see Python PEP 0418 [1]) * Eliminate terrible hack wherein we would cast between `CTime` and `Integer` through `Double` [1] https://www.python.org/dev/peps/pep-0418/#id59 Test Plan: Validate on various platforms Reviewers: austin, hvr, erikd Reviewed By: erikd Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2001
* Fix duplicate T11334 testBen Gamari2016-03-203-1/+1
|
* Mark GHC.Real.even and odd as INLINEABLEBen Gamari2016-03-201-4/+2
| | | | | | | | | | | | | | | | | | Previously they were merely specialised at Int and Integer. It seems to me that these are cheap enough to be worth inlining. See #11701 for motivation. Test Plan: Validate Reviewers: austin, hvr, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1997 GHC Trac Issues: #11701
* Add doc to (<$>) explaining its relationship to ($)Chris Martin2016-03-111-0/+9
| | | | | | | | | | Reviewers: bgamari, hvr, austin Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1989
* Make `catch` lazy in the actionBen Gamari2016-03-116-1/+52
| | | | | | | | | | | | | | | | | | | | | | Previously ```lang=haskell catch (error "uh oh") (\(_ :: SomeException) -> print "it failed") ``` would unexpectedly fail with "uh oh" instead of the handler being run due to the strictness of `catch` in its first argument. See #11555 for details. Test Plan: Validate Reviewers: austin, hvr, simonpj Reviewed By: simonpj Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D1973 GHC Trac Issues: #11555
* Use catchException in a few more placesBen Gamari2016-03-112-4/+4
| | | | | | | | | | | | | | These are cases in the standard library that may benefit from the strictness signature of catchException and where we know that the action won't bottom. Test Plan: Validate, carefully consider changed callsites Reviewers: austin, hvr Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1972
* Using unsafe foreign import for rtsSupportsBoundThreads (part of #9696)Marcin Mrotek2016-03-053-6/+6
| | | | | | | | | | | | | | | | | | A safe import is unnecessary considering rtsSupportsBoundThreads simply returns a constant. This commit doesn't fix the main issue of ticket #9696 that "readRawBufferPtr and writeRawBufferPtr allocate memory". Reviewers: bgamari, austin, hvr Reviewed By: hvr Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1964 GHC Trac Issues: #9696
* base: Mark Data.Type.Equality as TrustworthyBen Gamari2016-02-291-0/+1
| | | | | | | | | | | | Test Plan: Validate Reviewers: austin, ekmett, hvr Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1957 GHC Trac Issues: #11625
* Missing Proxy instances, make U1 instance more Proxy-likeRyanGlScott2016-02-296-12/+69
| | | | | | | | | | | | | | | | | | | | | | | | This accomplishes three things: * Adds missing `Alternative`, `MonadPlus`, and `MonadZip` instances for `Proxy` * Adds a missing `MonadPlus` instance for `U1` * Changes several existing `U1` instances to use lazy pattern-matching, exactly how `Proxy` does it (in case we ever replace `U1` with `Proxy`). This is technically a breaking change (albeit an extremely minor one). Test Plan: ./validate Reviewers: austin, ekmett, hvr, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1962 GHC Trac Issues: #11650
* GHC.Generics: Ensure some, many for U1 don't bottomBen Gamari2016-02-261-0/+3
| | | | | | | | | | | | Reviewers: austin, hvr, ekmett, RyanGlScott Reviewed By: RyanGlScott Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1952 GHC Trac Issues: #11650
* Typos in comments, etc.Gabor Greif2016-02-261-1/+1
|
* Testsuite: delete empty files [skip ci]Thomas Miedema2016-02-253-0/+0
|
* Handle multiline named haddock comments properlyThomas Miedema2016-02-251-1/+1
| | | | | | | | | | | | | Fixes #10398 in a different way, thereby also fixing #11579. I inverted the logic of the Bool argument to "worker", to hopefully make it more self-explanatory. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D1935
* Add more type class instances for GHC.GenericsRyanGlScott2016-02-258-26/+497
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | GHC.Generics provides several representation data types that have obvious instances of various type classes in base, along with various other types of meta-data (such as associativity and fixity). Specifically, instances have been added for the following type classes (where possible): - Applicative - Data - Functor - Monad - MonadFix - MonadPlus - MonadZip - Foldable - Traversable - Enum - Bounded - Ix - Generic1 Thanks to ocharles for starting this! Test Plan: Validate Reviewers: ekmett, austin, hvr, bgamari Reviewed By: bgamari Subscribers: RyanGlScott, thomie Differential Revision: https://phabricator.haskell.org/D1937 GHC Trac Issues: #9043
* base: A selection of fixes to the comments in GHC.StatsDavid Turner2016-02-251-17/+31
| | | | | | | | | | | | | | | | | Use `-- |` comments throughout. Note that numByteUsageSamples is also the number of major GCs Note that numGcs counts GCs for all generations Note that 'current' really means 'at the end of the last major GC' Reviewers: ezyang, hvr, simonmar, austin, bgamari Reviewed By: ezyang, simonmar, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1929 GHC Trac Issues: #11603
* Overload the static form to reduce verbosity.Facundo Domínguez2016-02-251-0/+8
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Static pointers are rarely used naked: most often they are defined at the base of a Closure, as defined in e.g. the distributed-closure and distributed-static packages. So a typical usage pattern is: distributeMap (closure (static (\x -> x * 2))) which is more verbose than it needs to be. Ideally we'd just have to write distributeMap (static (\x -> x * 2)) and let the static pointer be lifted to a Closure implicitly. i.e. what we want is to overload static literals, just like we already overload list literals and string literals. This is achieved by introducing the IsStatic type class and changing the typing rule for static forms slightly: static (e :: t) :: IsStatic p => p t Test Plan: ./validate Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: simonpj, mboes, thomie Differential Revision: https://phabricator.haskell.org/D1923 GHC Trac Issues: #11585