Hello,
> Thanks. This sort of works, but shifts the problem to another context.
Now it
> seems that I can't hide the extra type information in the existential
> types, which is what I want to do.
>
I think that you can't abstract over a type context, i.e. you can't expect
type inference to inst
Hello,
> data LSet t where
> Nil :: LSet Nil
> Ins :: (Member a t b
> , If b t (a ::: t) r)
> => L a -> LSet t -> LSet r
>
Try replacing both original occurrences of r, i.e. (untested)
Ins :: (Member a t b, If b t (a ::: t) (LSet r)) => L a -> LSet t ->
LSet r
Hello,
> > > data LSet t where
> > > Nil :: LSet Nil
> > > --either add the new element or do nothing
> > > Ins :: (Member a t b
> > > , If b (LSet t) (LSet (a ::: t)) r)
> > > => L a -> LSet t -> r
> > >
> > The constructor Ins needs to return an LSet. Maybe try re
Hello,
> data LSet t where
> Nil :: LSet Nil
> --either add the new element or do nothing
> Ins :: (Member a t b
> , If b (LSet t) (LSet (a ::: t)) r)
> => L a -> LSet t -> r
>
The constructor Ins needs to return an LSet. Maybe try replacing
occurrences of r with
Hello,
There will be a talk on Fortress ( a new OO/Functional language from Sun)
on Wednesday June 25 at 6:30pm in Manhattan.
Abstract:
The Java Programming Language revolutionized programming with two simple
concepts: "Write once run anywhere", and Garbage Collection. This led
to a big s
Hello,
> I would like to be able to run a shell command like curl and process the
> output in my Haskell program, but I couldn't find anything helpful about
it.
>
Try looking in System.Process. runInteractiveProcess should work for you.
-Jeff
---
This e-mail may contain confidential and/o
Hello,
> > $ pointfree "\xs -> foldl' (+) 0 xs / fromIntegral (length xs)"
> > ap ((/) . foldl' (+) 0) (fromIntegral . length)
>
This will have the same space usage as the pointed version. You can see
this by looking at the monad instance for ((->) r):
instance Monad ((->) r) where
Hello,
> For example, the natural and naive way to write Andrew's "mean" function
> doesn't involve tuples at all: simply tail recurse with two accumulator
> parameters, and compute the mean at the end. GHC's strictness analyser
> does the right thing with this, so there's no need for seq, $!, or
Hello,
> I offer up the following example:
>
This is an instructive example.
> mean xs = sum xs / length xs
>
In order to type-check, I actually need to write something like:
mean xs = sum xs / fromIntegral (length xs)
There are other ways of get the numeric types to match correctly, bu
Hello,
One frequent criticism of Haskell (and by extension GHC) is that it has
unpredictable performance and memory consumption. I personally do not find
this to be the case. I suspect that most programmer confusion is rooted in
shaky knowledge of lazy evaluation; and I have been able to fix, w
Hello,
> The function (++) :: [x] -> [x] -> [x] has O(n) complexity.
>
> If somebody were to invent some type that looks like [x] but actually
> uses some sort of tree rather than a linked list, you should be able to
> get O(1) concatenation. Has anybody ever implemented such a thing?
>
You ca
Hello,
> >Prelude Data.Typeable> typeOf (\a -> (Just (a:"")))
> >(\a -> (Just (a:""))) :: Char -> Maybe [Char]
> >
> >Prelude Data.Typeable> getDomain $ typeOf (\a -> (Just (a:"")))
> >[Char]
> >
> >Prelude Data.Typeable>getCodomain $ typeOf (\a -> (Just (a:"")))
> >(May
Hello,
> Thanks a lot, this helps a bit, but access to function bodies is exactly
> what I need. Or being more precise, I need the functionality of ghci's
> command ':t'. So functions that behave as follows, where everything is
> of course meta-represented in some way as ADT:
>
>Prelude Data.
Hello,
> I wondered, why not take an n-tuple of arguments s.t.
>
>multApply' :: (a1->a2->...->an->o) -> (a1,(a2,(...(an,o)...))) -> o
>
I'm not sure what you're trying to do here. Why is there an o in the
argument? Also, do you really mean the number of arguments expected to
match the numb
Hello,
I use HDBC for ODBC database access, and HAppS as a web server. I am
fairly happy with both. Here are some further thoughts...
> Finally some practical questions:
> ·regarding Haskell and databases, the page http://haskell.
> org/haskellwiki/Libraries_and_tools/Database_interfaces
Hello,
You can also just use reads which returns a list of (partial) parses.
-Jeff
[EMAIL PROTECTED] wrote on 12/19/2007 03:17:39 PM:
> Hi
>
> > > Well, how do I compile a Haskell program in such a way, that I
> > > get a useful error message from read? I mean, like the
> > > filename/linen
Hello,
Does the following code work for you?
-Jeff
---
{-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances
-fallow-overlapping-instances #-}
data Nil = Nil
data x ::: xs = x ::: xs
infixr 5 :::
data HTrue = HTrue deriving Show
data HFalse = HFalse deriving S
Hello,
You should be able to use fundeps to do exactly what you describe below.
Can you make a relatively small self-contained example which exemplifies
the ugliness you see?
-Jeff
[EMAIL PROTECTED] wrote on 12/07/2007 11:24:35 AM:
>
> I have some type-level sets using fundeps workin
Hello,
Have you tried using -fglasgow-exts? That should enable all ghc
extensions.
-Jeff
[EMAIL PROTECTED] wrote on 11/06/2007 02:02:11 PM:
> On Nov 6, 2007 12:15 PM, David Benbennick <[EMAIL PROTECTED]> wrote:
> > In ghc 6.8.1, the error messages are more helpful:
> >
> > foo.hs:5:0:
> >
Hello,
> > I think you mean
> >
> > !U -o U
> >
> > is a theorem. The converse is not provable.
> >
> Oops... I should read more carefully before hitting send.
>
> This is of course completely wrong.
>
This is embarrassing... I was right the first time.
!U -o U
is a theorem in
Hello,
> I think you mean
>
> !U -o U
>
> is a theorem. The converse is not provable.
>
Oops... I should read more carefully before hitting send.
This is of course completely wrong.
Sorry for the noise,
Jeff
---
This e-mail may contain confidential and/or privileged information. I
Hello,
> Just to continue the academic nitpicking.. :-)
>
> > Linear logic/typing does not quite capture uniqueness types since a
term
> > with a unique type can always be copied to become non-unique, but a
linear
> > type cannot become unrestricted.
>
> Actually, that isn't quite accurate.
Hello,
> > Just a bit of minor academic nitpicking...
> >
> > > Yeah. After all, the "uniqueness constraint" has a theory with an
> > > excellent pedigree (IIUC linear logic, whose proof theory Clean uses
> > > here, goes back at least to the 60s, and Wadler proposed linear
> > types
> > > for
Hello,
Just a bit of minor academic nitpicking...
> Yeah. After all, the "uniqueness constraint" has a theory with an
> excellent pedigree (IIUC linear logic, whose proof theory Clean uses
> here, goes back at least to the 60s, and Wadler proposed linear types
> for IO before anybody had heard
I forgot to send this reponse to haskell-cafe earlier...
Hello,
> You mean for the IO monad, right?
>
Sorry. I meant divergence is unavoidable for any strict Monad, such as IO.
However, sequence will always compute over the entire list; if the
resulting computation itself is lazy then the re
Hello,
> > countIO :: String -> String -> Int -> [a] -> IO [a]
> > countIO msg post step xs = sequence $ map unsafeInterleaveIO
> ((blank >> outmsg (0::Int) >> c):cs)
> >where (c:cs) = ct 0 xs
> > output = hPutStr stderr
> > blank= output ('\r':take 70 (repeat ' '))
>
Hello,
Agda is essentially an implementation of a type checker for Martin-Lof
type theory (i.e. dependent types).
It is designed to be used as a proof assistant. Roughly speaking
propositions are represented as types and a proof of a proposition is a
well-typed, total and terminating func
Hello,
> There are 4 variants of tail:
>
> tail :: [a] -> [a] -- normal
> tailDef :: [a] -> [a] -> [a] -- returns the first argument on []
> tailMay :: [a] -> Maybe [a] -- returns a Nothing
> tailNote :: String -> [a] -> [a] -- crashes, but with a helpful message
> tailSafe :: [a] -> [a] -- retu
Hello,
> {-# OPTIONS_GHC -fglasgow-exts #-}
>
> data Foo a
>
> foo :: Foo a -> a -> Bool
> foo = undefined
>
> newtype A = A (forall a. a->a)
>
> ok = foo f (A id)
> where f = undefined :: Foo A
>
> type B = forall a. a->a
>
> boom = foo f (id :: B)
> where f = undefined :: Foo B
>
Hello,
> Hence the need to perform a "run" operation like runIdentity,
> evalState or runParser (for Parsec) to get something useful to
> happen. Except for lists we don't seem to do this. I suppose lists
> are so simple that the operators :, ++ and the [] constructor do all
> we ever need wit
Hello,
> On 14/08/07, Jeff Polakow <[EMAIL PROTECTED]> wrote:
> Of course, the type [Int] denotes a value which is a list of Ints;
> additionally [Int] can be viewed as a value representing the
> nondeterministic computation of a single Int. Generally, the type
> Monad m =
Hello,
> On 8/14/07, Jeff Polakow <[EMAIL PROTECTED]> wrote:
> > One general intuition about monads is that they represent computations
> > rather than simple (already computed) values:
>
> > x :: Int -- x is an Int
> > x :: Monad m =>
Hello,
> Look! You are doing it again! :) Does that paragraph even
> contain the word "Monad"? :)
>
Sorry. Your first paragraph led me to believe you were writing about
monads.
> I'm aware a monad is an abstraction and as such it doesn't *do*
> anything. My point was along the lines that
Hello,
There is clearly a problem with the Haskell/monad tutorials out there...
> The tutorials seriously need to step back and start with
> something like, "To enforce order of evaluation we evaluate
> closures* returning a defined type. The first closure will feed
> its result to the second
Hello,
> :r is also *much* faster in general; :l reloads all modules from
> scratch, while :r only reloads the modules that have changed.
>
:r also doesn't seem check the import declarations for changes. For
example, if I add a new import statement to my file, without adding code
which uses the
Hello,
> 'Monad' is a type class.
>
> So what's 'IO'? Is the correct terminology 'instance' as in 'IO is an
> instance of Monad'. I consider 'IO' to be 'a monad' as that fits with
> mathematical terminology.
>
I agree with this.
>But what about an actual object of type 'IO
> Int', say?
>
I usu
Hello,
> On 8/1/07, Andrew Wagner <[EMAIL PROTECTED]> wrote:
> > For me, I think the key to monads is to really
> > understand 2 things about them:
> > ...
> > 2.) Monads are about sequencing
>
> Now I disagree on 2.
>
> Monads are no more about sequencing than binary operators are about
> seque
Hello,
> But here I am only entitled to discharge (A /\ B) in the preceding
> proof and not A and B on their own.
> What proof which would allow me to discharge my assumptions A and B?
>
> I can see in my head how it makes perfect sense, but can't jiggle a
> way to do it using only the given deri
Hello,
> Hello all,
>
> Given an HList (http://homepages.cwi.nl/~ralf/HList/) would it be
> possible to do the following:
>
> Create a class/function/magicks that would essentially do what
> hOccursMany does, except it would not return a list of elements, but a
> new HList. For example, would th
Hello,
> I'm trying to learn haskell, so here's is my first newbie question.
> I hope this list is appropriate for such help requests.
>
Yes.
> I'm trying to write a function with the signature [IO Int] -> IO [Int]
>
As other people have mentioned, the library function sequence has this
type (
Hello,
> In John Hughes's "Programming With Arrows"
> (http://www.cs.chalmers.se/~rjmh/afp-arrows.pdf), he discusses a
> "stream function" type
> newtype SF a b = SF {runSF :: [a] -> [b]}
> and gives
> instance Arrow SF where
> He gives some examples using this, and everything seems to go jus
Hello,
Partial evaluation in this context (programming languages research)
usually refers to "compile time" optimization techniques such as
statically evaluating as much of a function as possible (e.g. going into
the function body and evaluating as much as possible that doesn't depend
on the f
Hello,
On my system, GHC 6.6 running on windows xp, System.Time.toClockTime
fails on calendar times later than (by days, I didn't check hours,
minutes, etc.) January 18, 2038. Is this a bug?
thanks,
Jeff
---
This e-mail may contain confidential and/or privileged information. If you
Hello,
> dbCreateIndices con dtn dof = do
>let dummy = newDbItem
>let query = "SELECT id FROM " ++ (dtn dummy) ++ " ORDER BY " ++ (dof
dummy)
>ids <- liftM (map fromSql . concat ) $! quickQuery con query []
>return $ IntMap.fromList $ zip ids [0..]
>
> quickQuery returns a lazy l
Hello,
You might want to look at the scrap your boilerplate papers and/or their
implementation in GHC in Data.Generics.
-Jeff
[EMAIL PROTECTED] wrote on 03/19/2007 01:11:19 PM:
> Hey,
>
> I have a structure containing Xs in various places, like so
>
> data X
> data Structure = Structure ..
Jefferson Heard <[EMAIL PROTECTED]> wrote on 03/06/2007 03:18:40 PM:
> Nope, I'm asking why
>
> um . IntMap.elems . IntMap.IntersectionWith (\x y -> x*y) queryVector
> rationalProjection
>
> won't work.
>
We have (simplifying away some typeclass details):
sum . elems :: IntMap a -> a
a
[EMAIL PROTECTED] wrote on 03/06/2007 02:43:03 PM:
> Usually, I can do this, but today, my brain is weak, and I'm just trying
to
> get this piece of code out the door. My code looks like this:
>
> weight = sum (IntMap.elems (IntMap.intersectionWith
>(\x y -> x*y) queryVector ratio
Hello,
I am trying to install hsffig and I get the following error:
bash$ make
:
:
Linking cabal-setup.exe ...
Distribution/Simple/Configure.o:fake:(.text+0x74fd): undefined
reference to [EMAIL PROTECTED]'
collect2: ld returned 1 exit status
Hello,
> PS: Talking about smart programs: Is there a library anywhere that
> could be used to implement expert systems in Haskell or to
> evaluate Horn clauses in Prolog style?
>
Here is one possible starting point is the backtracking monad transformer
by Oleg et al:
http://okmij.or
Hello,
I'm trying to understand what happens when a typeclass constraint with an
uninstantiated type variable gets duplicated.
Does the type checker treat the separate copies of the constraint as two
constraints (with the same type variable) which are checked separately?
Or does the type checke
Have you looked at OOHaskell (http://homepages.cwi.nl/~ralf/OOHaskell/)?
-Jeff
[EMAIL PROTECTED] wrote on 12/07/2006 07:07:46 AM:
> Hi,
>
> I've got an object model that I have a difficult time
> conceptualising how it might look like in Haskell:
>
> class Element { }
>
> class Inline : Elem
Hello,
I think my problem is a faulty
ghc installation and not HDBC.
sorry for the noise,
Jeff
[EMAIL PROTECTED] wrote on 10/31/2006
02:31:27 PM:
>
> Hello,
>
> When trying to compile a standalone program using hdbc in cygwin,
I
> get many linker errors.
> I have no problems using
Hello,
When trying to compile a standalone
program using hdbc in cygwin, I get many linker errors.
I have no problems using my code interactively
with ghci.
I am using the command line:
ghc --make -package HDBC
-package HDBC-odbc -O -o testExecute testExecute.hs
Am I missing something?
Hello,
When I compile my program without
profiling:
bash-3.1$ ghc --make -auto-all
-prof -O -o analysis analysis.hs
Chasing modules from:
analysis.hs
Compiling Main
( analysis.hs, analysis.o )
Linking ...
everything works fine.
However when I compile with profilin
Hello,
Why would ghci run out of heap
space (and crash) the second time I run a computation?
More specifically, I have a ghci session
which goes something like this:
*Analysis>run
[ ... print out of a very
long list ...]
*Analysis>run
[ ... partial print out
GHC's he
> honest, the documentation for Arrows blows my
mind. I think a few
> examples would go a long way.
>
John Hughes' original paper on arrows is full of examples.
Additionally, Hughes wrote a tutorial on programming with arrows, for the
2004 AFP summer school in Tartu, which is very accessible. B
Hello,
I have installed ghc-6.4.2 on
a windows XP machine. However, the machine refuses to execute ghc-pkg (thus
preventing me from using Cabal) and complains that "C:\ghc\ghc-6.4.2\bin\ghc-pkg.exe
is not a valid Win32 application." Is there something obvious
I might have overlooked while inst
57 matches
Mail list logo