I've looked around with no success… this surprises me actually. Has
anyone embedded SpiderMonkey, V8, or any other relatively decent
JavaScript interpreters in GHC (using the FFI)?
I just started something [1].
Cheers,
Simon
[1] https://github.com/sol/v8
Out of curiosity: wouldn't it make mo
Have we become a bit complacent about RT?
We're not complacent, we just know things without having to
check references. Just kidding, of course, functional programmers
tend to enjoy improving their understanding!-)
The Strachey reference is worth reading - great that it is online
these days, bu
I have the opportunity to make a presentation to folks (developers and
managers) in my organization about Haskell - and why it's important - and
why it's the only way forward.
Haskell is important, but not the only way forward. Also, there have been
other great languages, with limited impact - i
Look how one can watch the evaluation tree of a computation, to debug
laziness-related problems.
You might like the old Hood/GHood:
http://hackage.haskell.org/package/hood
http://hackage.haskell.org/package/GHood
Background info/papers:
http://www.ittc.ku.edu/csdl/fpg/Tools/Hood
http://www.it
* syb: toJSON and fromJSON from the Data.Aeson.Generic module. Uses
the Data type class.
..
As can be seen, in most cases the GHC Generics implementation is much
faster than SYB and just as fast as TH. I'm impressed by how well GHC
optimizes the code!
Not that it matters much if you're going wit
I am planning to give a workshop on FP using Haskell.
The audience will be programmers with quite a bit of
experience with conventional languages like Java and
.net . I want to give them some feeling about FP. And
hopefully, they will become interested so they want more...
My recommendations:
The world needs programmers to accept and take seriously Greg
Wilson's extensible programming, and stop laughing it off as "lolwut
wysiwyg msword for programming", and start implementing it.
http://third-bit.com/blog/archives/4302.html
Who is "the world"? For starters, I don't think it is Greg
suggests using :etags in GHCI or hasktags, or gasbag. Of the three,
hasktags comes closest to "working" but it has (for me) a major
inconvenience, namely it finds both function definitions and type
signatures, resulting in two TAGS entries such as:
Some customization required? Tweaking the outp
It is a common situation when one has two implementations of
the same function, one being straightforward but slow, and the
other being fast but complex. It would be nice to be able to check
if these two versions are equal to catch bugs in the more complex
implementation.
This common situatio
I am very curious about the readiness of trading and banking
industries to adopt FPLs like Haskell:
.. Why are are trading/banking diving into FPLs?
Some possible reasons have been given, but to keep things
in perspective, you might want to consider that it isn't just
FPLs. Smalltalk, for in
Lately I've been trying to go the other direction: make a large
section of formerly strict code lazy.
There used to be a couple of tools trying to make suggestions
when a function could be made less strict (Olaf Chitil's StrictCheck
and another that escapes memory at the moment). Often, it
c
I've recently had the opportunity to explain in prose what denotational
semantics are to a person unfamiliar with it. I was trying to get across
the concept of distilling the essence out of some problem domain. I
wasn't able to get the idea across so I'm looking for some simple ways
to explain it.
Earlier today I was trying to set up a Windows build bot for the
'network' package. That turned out to be quite difficult. Too much
playing with PATHs, different gcc versions, etc. Does anyone have a
repeatable, step-by-step process to install GHC and get a build
environment (where I could build n
Perhaps ghc should also ignore all group-writable *.hs, *.lhs, *.c, *.o,
*.hi files.
dot-ghci files are *run* if you just start ghci (or ghc -e) in that
directory
(even if you don't intend to compile, load, or run any Haskell code).
Claus
___
Has
ghci> :set -XOverloadedStrings
ghci> "$name ate a banana." % [("name", "Johan")]
"Johan ate a banana."
class Context a where
lookup :: a -> T.Text -> T.Text
instance Context [(T.Text, T.Text)] where
lookup xs k = fromMaybe (error $ "KeyError: " ++ show k) (P.lookup
This is obviously a personal preference issue, but I try to avoid the
Cabal macros since they don't let my code run outside the context of
Cabal. I often times like to have a test suite that I can just use
with runhaskell, and (unless you can tell me otherwise) I can't run it
anymore.
Also, I thi
but if improved records are never going to happen
Just to inject the usual comment: improved records have
been here for quite some time now. In Hugs, there is TREX;
in GHC, you can define your own. No need to wait for them.
Using one particular random variation of extensible records
and labels
> instance (EmbedAsChild m c, m1 ~ m) => EmbedAsChild m (XMLGenT m1 c)
That looked to me like a long-winded way of saying:
> instance (EmbedAsChild m c) => EmbedAsChild m (XMLGenT m c)
Unless I'm missing something?
These two instances are not equivalent:
- the first matches even if m and
I opted to host them there rather than uploading them to Hackage,
because
they're part of a wider project.
Note that this means they won't be cabal installable or searchable. Was
that your intention?
I am curious about this: wasn't cabal designed with the
option of having several package rep
I haven't the faintest idea what SML is doing with the third
version, but clearly it shouldn't.
Those numbers are worrying, not just because of the third
version - should doubling the tree size have such a large effect?
I find your report that GHC doesn't do as well with the third
version as
remote-repo: myhackage:http://myhackage/packages
However, when I try to unpack my package with cabal:
$ cabal unpack MyPackage
Downloading MyPackage-0.0.1...
cabal: Failed to download
http://myhackage/packages/package/MyPackage-0.0.1.tar.gz : ErrorMisc
"Unsucessful HTTP code: 404"
Why is cabal ev
The bottom line is that
- in logic programming languages, building a list by working on
a pair of arguments representing a segment of the list is the
NORMAL way to build a list; it's as fast as it gets, and the
list is inspectable during construction.
modulo usage patterns: e.g., mostly l
The characteristics of the "logical" variable are as follows.
An "incomplete" data structure (ie. containing free variables)
may be returned as a procedure's output. The free variables
can later be filled in by other procedures, giving the effect
of implicit assignments to a data structu
I often find myself writing example code that I'd like
to distribute via cabal, but without further burdening
hackage with not generally useful packages.
1. The simplest approach would be if cabal could expose
its internal 'unpackPackage' as a command, so that
author: cabal sdist
user: cab
Interesting discussion. I still think it is the same idea,
namely to represent not-yet-known list tails by variables,
embedded into two different kinds of languages.
\rest->start++rest
[start|rest]\rest-- '\' is an infix constructor
Savvy Prolog programmers wouldn't *DREAM* of
using
Stack Overflow and Reddit are at least improvements over the traditional
web forums, starting to acquire some of the features Usenet had twenty
years ago. Much like Planet-style meta-blogs and RSS syndication makes
it liveable to follow blogs.
Very much this. I mourn Usenet's potential as muc
To simplify, the difference in persistence between the two
representations is enough to consider them very different
as it makes a dramatic difference in interface.
Interesting discussion. I still think it is the same idea,
namely to represent not-yet-known list tails by variables,
embedded into
2) If there is a problem, here's what you could do about it,
in descending order of attractiveness:
y) specify the requirements (a sample application
of what needs to be supported would be a start)
z) review the existing options wrt to those requirements
(which ones are you aware about, w
I'm occasionally working on making a friendly yet performant library that
simultaneously builds parsers and generators, but it's non-trivial. If you
I'm probably missing something in the "friendly yet performant"
requirements, but I never quite understood the difficulty:
A typical translation o
Some questions about Haddock usage:
1. Haddock executable and library are a single hackage package,
but GHC seems to include only the former (haddock does not
even appear as a hidden package anymore). Is that intended?
2. Naively, I'd expect Haddock processing to involve three stages:
1
After it catches this error, the function returns (line 376):
return (fail (show e))
The "fail" is running in the Either monad (The Result type = Either).
This calls the default Monad implementation of fail, which is just a
call to plain old error. This basically causes the entire program to
cra
On the topic of cabal odisseys:
I think it would help to document (prominently) what Cabal
fundamentally doesn't (try to) do, to avoid optimistic
expectations (and hence the surprises when Cabal doesn't
meet those expectations), and to point out the design choices
behind many bug tickets (even
That sort of code (stripped out):
In Game.hs:
data Game = Game { ...
activeRules :: [Rule]}
applyTo :: Rule -> Game -> Game
applyTo r gs = ...
Often, it helps to parameterize the types/functions (instead
of using recursive modules to hardcode the parameters).
Would somethi
For another programs (that compile fine with ghc --make), I didn't
bother making the package. But I had to find out the package
dependencies by building, checking where it fails, and trying to add a
package to the dependency list. Maybe there's a better way, didn't
find it.
We do plan to fix thi
One of the problems is that the anchors that Haddock
currently generate aren't always legal in HTML, XHTML,
or XML. I'd like to fix the anchor generation so that they
are. If I do, then links between old and new generated
Haddock pages will land on the right page, but won't
always get to the r
I am making use of the Data.Array.Repa module to achieve data-parallelism.
On running my program I get the error:
"thread blocked indefinitely on an MVar operation"
Haven't seen any responses yet, so here are some suggestions:
Two questions:
1. What could be some of the potential causes for
Most languages today provide a certain "glue" to bring everything
together.
Most languages today provide several kinds of glue and, while some
of those kinds are not recommended, Haskell unfortunately doesn't
provide all useful kinds of glue. Especially the module system is a
weak point: in SML,
Prelude> :t id :: Eq b => b -> b
id :: Eq b => b -> b :: (Eq b) => b -> b
Prelude> id :: Eq b => b -> b
:1:0:
No instance for (Show (b -> b))
arising from a use of `print' at :1:0-19
Possible fix: add an instance declaration for (Show (b -> b))
In a stmt of a 'do' expres
f :: forall a b. C a b => T a -> Bool
f T1 = True
f T2 = (op :: a -> b) 3
as that results in the counter-intuitive
Couldn't match expected type `Bool' against inferred type `b'
`b' is a rigid type variable bound by
the type signature for `f'
at C:\Users\claus\Desktop\
class C a b | a->b where
op :: a -> b
instance C Int Bool where
op n = n>0
data T a where
T1 :: T a
T2 :: T Int
-- Does this typecheck?
f :: C a b => T a -> Bool
f T1 = True
f T2 = op 3
The function f "should" typecheck because inside the T2 branch we know
Claus -- cafe5 is pretty much where it's at. You're right, the proggy
was used as the bug finder, actually at cafe3, still using ByteString.
It would be useful to have a really tiny data source - no more than
100 entries per Map should be sufficient to confirm or reject hunches
about potentia
I'll work with Simon to investigate the runtime, but would welcome any
ideas on further speeding up cafe4.
An update on this: with the help of Alex I tracked down the problem (an
integer overflow bug in GHC's memory allocator), and his program now
runs to completion.
So this was about keepin
This seems like an example of list-chauvinism -- what Chris Okasaki
calls a communal blind spot of the FP community in Breadth-First
Numbering: Lessons from a Small Exercise in Algorithm Design --
http://www.eecs.usma.edu/webs/people/okasaki/icfp00.ps
Thanks for sharing; this was an interesting
I'm interested in situations where you think fundeps work
and type families don't. Reason: no one knows how to make
fundeps work cleanly with local type constraints (such as GADTs).
If you think you have such as case, do send me a test case.
Do you have a wiki page somewhere collecting th
I have below duplicate code, but i don't know how to use TH instance code.
--> duplicate code start
<--
instance Variable PageType where
toVariant = toVariant . show
fromVariant x = fmap (\v -> read v :: PageType) $ fromVariant x
If
If you go this route, I will shamelessly promote hothasktags instead
of ghci. It generates proper tags for qualified imports.
What do you mean by "proper" here?
I think Luke means that if you use qualified names then hothasktags can
give you better location information than current ghci ctags
If you want to use cool languages, you may have to get a cool job. I
know: it's easy to say and harder to accomplish.
Most functional languages (e.g. Lisp, Haskell, ...) have a challenging
time in industry since they require some savvy with multiple levels of
higher abstractions and some sa
I'll work with Simon to investigate the runtime, but would welcome any
ideas on further speeding up cafe4.
Just a wild guess, but those foldWithKeys make me nervous.
The result is strict, the step function tries to be strict, but if
you look at the code for Data.IntMap.foldr, it doesn't really
..ghci is able to generate the tagsfiles for you. This allows you to
jump to definitions of identifiers.
If you go this route, I will shamelessly promote hothasktags instead
of ghci. It generates proper tags for qualified imports.
What do you mean by "proper" here? GHCi has the information
As others have pointed out, you can't go from operation to
representation,
but you can pair operations and expressions with their representations.
This idea is also implemented in my little 'repr' package:
http://hackage.haskell.org/package/repr
And probably more completely/comfortably!-) Th
ms that, for some people at least, the latest version of
the Haskell tools won't work when launched from Cygwin Bash.
Chris
-Original Message-
From: haskell-cafe-boun...@haskell.org
[mailto:haskell-cafe-boun...@haskell.org] On Behalf Of Claus Reinke
Sent: 08 June 2010 09:02
To: haskel
Thanks Stephen--that was related to my original question, about using HP
with Cygwin. The answer seems to be No!--you must use MSYS (for real
work).
The short version:
- Cygwin provides commandline tools, compilers and libraries
- MSYS provides commandline tools for the MinGW compilers and lib
> If I have a problem where I have to select from a set of operations,
> how
> would I print the result?
>
> Example: If I can chose from (x+y), (x*y), (x^2+y)...
> and I feed them all into my problem solver
> and it finds that "(x*y) is right", how can I print that string?
As others have point
The approach is so simple and trivial that it must have occurred to
people a hundred times over. Yet I do not find any other examples of
this. Whenever I google for church encoding the examples don't go beyond
church numerals.
Am I googling for the wrong keywords?
You might find "Typing Reco
All my code, whether neat or not so neat is still way too concrete, too
direct.
I think the correct answer is one should try to find abstractions and
not code straight down to the point. Which to me is still a really tough
one, I have to admit.
Taking this cue, since you've raised it before, a
I am trying to improve the error reporting in my sendfile library, and I
know I can find out the current file name and line number with something
like this:
{-# LANGUAGE CPP #-}
main = putStrLn (__FILE__ ++ ":" ++ show __LINE__)
This outputs:
test.hs:2
Unfortunately, if your file is in a hierar
JVM 7 has tail calls,
Source, please? JSR-292 seems the most likely candidate so far,
and its draft doesn't seem to mention tail calls yet. As of March
this year, the people working on tail calls for mlvm [1], which
seems to be the experimentation ground for this, did not seem to
expect any fas
For example, Clojure lacks proper tail recrusion optimization due to
some missing functionality in the JVM. But does anybody know the
details?
|Basically, the JVM lacks a native ability to do tail calls. It does
|not have an instruction to remove/replace a stack frame without
|executing an
It's too bad that indexes are `Int` instead of `Word` under
the hood. Why is `Int` used in so many places where it is
semantically wrong? Not just here but also in list indexing...
Indices/offsets can only be positive and I can't see any good
reason to waste half the address space -- yet we e
I've heard that many Haskellers know HaRe only as a rumour. It has
been many years since the original project finished, and HaRe hasn't
been maintained for quite some time, so just pointing to the sources
isn't quite the right answer.
The sources are still available, and build with GHC 6.8.3 (
I (too) often find myself writing code such as this:
if something
then putStrLn "howdy there!"
else if somethingElse
then putStrLn "howdy ho!"
else ...
1. recognize something odd. done.
2. look for improvements. good.
3. define suitable abstractions for your special case
4.
It is not possible to write a modifyIORef that *doesn't* leak memory!
Why? Or can one read about it somewhere?
Possibly, Don meant that 'modifyIORef' is defined in a way that
does not allow to enforce evaluation of the result of the modification
function (a typical problem with fmap-style
who needs this kind of documentation?
http://hackage.haskell.org/packages/archive/tfp/0.2/doc/html/Types-Data-Num-Decimal-Literals.html
The code below is shown under 'Source' links
in that documentation. I don't understand it,
but it seems everything is generated automatically.
What should the
I was recently trying to figure out if there was a way, at runtime, to do
better strictness analysis for polymorphic HOFs, for which the strictness of
some arguments might depend on the strictness of the strictness of function
types that are passed as arguments [1]. As an example, consider foldl.
A much better idea than making sum strict, would simply be to add a
sum'.
Even better to abstract over strictness, to keep a lid on code duplication?
{-# LANGUAGE TypeOperators #-}
sum = foldlS ($) (+) 0
sum' = foldlS ($!) (+) 0
-- identity on constructors of t (from a), modulo
I am learning to use cabal for my code.
Just when I start, I met a question, is there an easy way to find
out what packages my code depends?
If you've managed to get your code to compile,
ghc --show-iface Main.hi
is perhaps the easiest way (ghc --make and ghci will also report
package de
I've written a multi-threaded Haskell program that I'm trying to
debug. Basically what's happening is the program runs for a while, and
then at some point one of the threads goes crazy and spins the CPU
while allocating memory; this proceeds until the system runs out of
available memory. I can't f
| bar :: (C T) => T
| *Main> :t bar
|
| :1:0:
| No instance for (C T)
| arising from a use of `bar' at :1:0-2
| Possible fix: add an instance declaration for (C T)
| In the expression: bar
I'm not sure where that comes from, but it does seem to be an
artifact of GHC's type in
>From what I understand, the current best practices are to build your
package dependencies like so:
ParsecMyMonadT
MyMonadT_Parsec -- orphan instances go here
ProjectPackage
This does mean splitting up your project into three packages, but
decouples the orphan instance into its own package
I once thought, that error messages must be configurable by libraries,
too. This would be perfect for EDSLs that shall be used by non-Haskellers.
Yes, that is a problem.
But I have no idea how to design that.
There was some work in that direction in the context of the Helium
project. See th
It's too wordy, but it's a start. This is also prime ground for wanting
to have configurable levels of error reports, since some users will find
it helpful to see both types but others will find it confusing.
Indeed. For this simple example, I find Hugs' message nearly optimal,
but as one could
Do you argue that overloading logical operations like this in Haskell
sacrifices type safety? Could programs "go wrong" [1] that use such
abstractions?
If I understand your point correctly, you are suggesting that such programs
are still type safe. I agree with the claim that such features are
--
type F a = Int
class A a where
foo :: A b => a (F b)
--
GHC - OK
Hugs - Illegal type "F b" in constructor application
This time, I'd say Hugs is wrong (though eliminating that initial
complaint leads back to an
head[[]{}]
GHCi: []
Hugs: ERROR - Empty field list in update
What is the correct behavior?
Seems as if GHC interprets []{} as labelled construction instead
of labelled update - 3 Expressions (the grammar productions):
| qcon { fbind1 , ... , fbindn } (labeled construction, n>=0)
| aexp
--
type F a = Int
class A a where
foo :: A b => a (F b)
--
GHC - OK
Hugs - Illegal type "F b" in constructor application
This time, I'd say Hugs is wrong (though eliminating that initial
complaint leads back to an
--
class A a where
foo :: A (b d) => a (c b)
--
GHC compiles it successfully, but Hugs rejects it:
Ambiguous type signature in class declaration
*** ambiguous type : (A a, A (b c)) => a (d b)
*** assigned to: foo
'd'
---
class A a where
foo :: a b
class B a
class (A a, B a) => C a
---
GHC compiles it without errors, but Hugs rejects it: "Illegal type in
class constraint".
The error message is horribly uninformative.
I find this slightly more complicated case quite confusing with the
current wording:
Prelude> :t (\x -> x) :: (a -> b) -> (a -> a)
:1:7:
Couldn't match expected type `a' against inferred type `b'
`a' is a rigid type variable bound by
an expression type signature at
Of course once you've got ifthenelse you find yourself wanting explicit
desugaring of pattern matching (could view patterns help here?),
Could you be more specific about what you want there, perhaps
with a small example? I recognize the other problems from my own
forays into EDSLs, but I'm not s
One user's view of error message history, perhaps helpful to reformers:-)
Once upon a time, Hugs tended to have "better" error messages than GHC.
They still weren't perfect, mostly when begginners where confronted with
messages referring to advanced concepts - eg, Simon Thompson had a list
of t
I wonder if I am completely off here, but I am surprised that there is
no progress on the scoped labels front. The Haskell wiki mentioned
that the status quo is due to a missing optimum in the design space,
but the same can be said about generic programming in Haskell and yet,
GHC ships with Scrap
I understand from your later post that is was in fact specialized, but
how do I make sure it _is_ specialized?
-ddump-tc seems to give the generalized type, so it seems you'd need
to look at the -ddump-simpl output if you want to know whether a
local function is specialized.
http://www.haskell
As I said, I don't get the fusion if I just add the function above to the
original Dist.hs, export it and compile the module with '-c -O2
-ddump-simpl':
I can't reproduce this.
Interesting. I'm using ghc 6.11.20090320 (windows), uvector-0.1.0.3.
I attach the modified Dist.hs and its simpl ou
Once I actually add a 'dist_fast_inline_caller', that indirection
disappears in the inlined code, just as it does for dist_fast itself.
dist_fast_inlined_caller :: UArr Double -> UArr Double -> Bool
dist_fast_inlined_caller p1 p2 = dist_fast_inlined p1 p2 > 2
However, in the simpl output
I've got one of those algorithms which "threatens to march off the right edge" (in the words of
Goerzen et al). I need something like a State or Maybe monad, but this is inside the IO monad.
So I presume I need StateT or MaybeT. However, I'm still (sdlowly) learning about monads from
first princ
dist_fast :: UArr Double -> UArr Double -> Double
dist_fast p1 p2 = sumDs `seq` sqrt sumDs
where
sumDs = sumU ds
ds= zipWithU euclidean p1 p2
euclidean x y = d*d
where
My current best try uses the uvector package, has two 'vectors' of type
(UArr Double) as input, and relies on the sumU and zipWithU functions
which use streaming to compute the result:
dist_fast :: UArr Double -> UArr Double -> Double
dist_fast p1 p2 = sumDs `seq` sqrt sumDs
where
I've got one of those algorithms which "threatens to march off the right edge" (in the words of
Goerzen et al). I need something like a State or Maybe monad, but this is inside the IO monad. So
I presume I need StateT or MaybeT. However, I'm still (slowly) learning about monads from first
princi
I miss lots of stuff from when I was a kid. I used to write
elem x (_ ++ x : _) = True
elem _ _ = False
and think that was cool. How dumb was I?
Yeah, the Kiel Reduction Language had similarly expressive
and fun pattern matching, with subsequence matching and
backtracking if
oops, sorry, keyboard accident
>I assume you want to write FRP in a Haskell-embedded DSL and generate
FRP'd JavaScript. If you wish to use Flapjax as a supporting library
I'd be glad to help.
I'm curious: how difficult is it nowadays for in-page JavaScript to
control the evolution of its sur
I assume you want to write FRP in a Haskell-embedded DSL and generate
FRP'd JavaScript. If you wish to use Flapjax as a supporting library
I'd be glad to help.
I'm curious: how difficult is it nowadays for in-page JavaScript to
control the evolution of its surrouding page, FRP-style? I used to
With these functions visualized, one could make a kind of "drag and
drop" interface for Haskell programming, although that isn't really my
intention. I admit this is a little convoluted even for the purpose of
visualization, but at least it's a starting place. Does anyone know of
another syst
seq something like size map that will force a traversal of the entire
tree, and ensure that the result is actually demanded, ..
(Not tested)
and not recommended, either, I'm afraid!-)
|> Actually, I'm unsure how to fix this. For an expression like this:
|>
|>Data.Map.delete key map
|>
|>
mplus' :: MonadPlus m => Maybe a -> m a -> m a
mplus' m l = maybeToMonad m `mplus` l
maybeToMonad :: Monad m => Maybe a -> m a
maybeToMonad = maybe (fail "Nothing") return
In general, however, this operation can't be done. For example,
how would you write:
mplus' :: IO a -> [a] -> [a]
P
So I wonder of existing projects of such type, both Molecular dynamics and Monte Carlo methods.
The fastest Haskell Monte Carlo code I've seen in action is
Simon's port of a Monte Carlo Go engine:
http://www.haskell.org/pipermail/haskell-cafe/2009-March/057982.html
http://www.haskell.org/pipe
If someone wants to use a unix shell on an unknown platform, they
should at least check that one exists there or -even better- provide
one, not just assume that there'll always be one (and then be surprised
about getting complaints from "those windows users"). Same for
autoconf, make & co.
Yo
http://socghop.appspot.com/student_project/show/google/gsoc2009/haskell/t124022468245
There's less than a month left before I'm supposed to jump into coding,
and I'd love to hear about any little idea you think would make this
project even better! I created a project page with a rough draft of wh
The thing is, it doesn't really matter if autoconf macros work fine for
every Unix ever invented. The Windows users simply cannot use packages
with configure scripts. They complain about it a lot. We can call them
foolish for not installing cygwin/mingw, but they will not do it and
instead will si
z :: client -> Label client
z client = undefined
ok :: (B.Label client ~ A.Label client) =>
client -> [A.Label client].
ok client = [ A.z client, B.z client]
This technique relies on the explicit management of the identities of
modules both at compile-time (type annotatio
Standard ML's answer to that kind of issue is type sharing.
Does type sharing help with making modules retroactively compatible?
It would be as if one could write modules parameterised by types,
instead of declaring them locally, and being able to share a type
parameter over several imports:
1 - 100 of 572 matches
Mail list logo