Adam,
class Foo a where
mkFoo :: a -> String
instance Foo String where
mkFoo x = x
In addition to making use of language extensions or wrapper types,
you could go with the following workaround in just plain Haskell 98:
import List
class MkFoo a where
mkFoo :: a -> Str
SevenThunders wrote:
>
> I am having some difficulty with creating a dynamic link library using
> GHC on windows XP.
>
>
I am having some problems with GHCs stdout when a Haskell program is called
from a windows program.
As I noted earlier I am calling some Haskell code from C as a bridge
Thank you Oleg! That explanation is very clear.
On 9/28/06, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote:
The typechecker commits to the instance
and adds to the current constraints
TypeCast x Int, Ord Bool, Eq Bool
The latter two are obviously satisfied and so discharged. The former
lea
On 29/09/2006, at 12:44 PM, Donald Bruce Stewart wrote:
Alternatively, use -fglasgow-exts :)
instance Foo String where
mkFoo = id
$ ghci -fglasgow-exts A.hs
*Main> mkFoo "foo"
"foo"
And just to follow up what Don said, this feature of GHC is described
here:
http://www.haskell
adam:
> I am trying to create an instance of a class for String types. I have
> the following:
>
> class Foo a where
> mkFoo :: a -> String
>
> instance Foo String where
> mkFoo x = x
>
> and receive the following error:
>
> test.hs:9:0:
> Illegal instance declaration for `Foo Stri
I am trying to create an instance of a class for String types. I have
the following:
class Foo a where
mkFoo :: a -> String
instance Foo String where
mkFoo x = x
and receive the following error:
test.hs:9:0:
Illegal instance declaration for `Foo String'
(The instance type m
david.curran:
> Where are compute languages going?
> I think multi core, distributed, fault tolerant.
> So you would end up with a computer of the sort envisioned by Hillis
> in the 80s with his data parallel programs. The only language that
> seems even close to this model is Erlang. What am I mis
Sorry if this comes across as the rant it is. If you are interested in
doing useful stuff rather then navel gazing please stop here.
Where are compute languages going?
I think multi core, distributed, fault tolerant.
So you would end up with a computer of the sort envisioned by Hillis
in the 80s
Brian Hulley wrote:
> Consider the scenario when you want to find a function that returns the
> i'th element of an array but all you know is that there is a module called
> Data.Array.IArray that will probably have such a function in it. So you
> start typing in your program:
>
> let
>
(.) :: a -> (a -> b) -> b
x.f == f x
Looks like a parallel of (>>=).
Sounds interesting and useful, but why hijack dot? Would work nicely with
record gettor functions (but not the settors).
Greg
Tim Newsham
http://www.thenewsh.com/~newsham/
___
H
On Wed, 27 Sep 2006, Brian Hulley wrote:
> Hi -
> Consider the scenario when you want to find a function that returns the i'th
> element of an array but all you know is that there is a module called
> Data.Array.IArray that will probably have such a function in it. So you start
> typing in your p
On 2006-09-28, Ashley Yakeley <[EMAIL PROTECTED]> wrote:
> Hey Ross, Conor, "Idiom" is a better name than "Applicative". Pretty
> much everyone thinks so.
I don't! Idiom doesn't tell me anything. Applicative at least tries
to.
--
Aaron Denney
-><-
___
On 28/09/06, Brian Hulley <[EMAIL PROTECTED]> wrote:
I think the H' proposal
http://hackage.haskell.org/trac/haskell-prime/wiki/CompositionAsDot is an
extremely bad idea.
Hear, hear. Besides the fact that it's a proposal I disagree with
anyway, it would break _every single Haskell program ever_
On 9/28/06, Brian Hulley <[EMAIL PROTECTED]> wrote:
On Thursday, September 28, 2006 1:33 AM, Greg Fitzgerald wrote:
> Since there's talk of removal of the composition operator in
> Haskell-prime,
> how about this:
>
> Instead of:
> foo = f . g
>
> you write:
> foo = .g.f
>
> A leading dot would
Hello Lyle,
Wednesday, September 27, 2006, 12:44:05 AM, you wrote:
> It's supposed to match movie titles from an imported database to a
> reference database.
> The import files each have 3,000 records, and the reference table has
> 137,986 records.
> Building the hash tables out of the files i
On Thu, Sep 28, 2006 at 03:22:25PM +0100, Simon Peyton-Jones wrote:
> | Does anything go wrong with irrefutable patterns for existential
> types?
>
> Try giving the translation into System F.
Hmm, that's not quite as satisfying as Conor's answer for GADTs.
___
> If I were to fix the language I would probably use something like ":" or
> "::" for selection and keep "." for composition.
I agree it's not worth changing. But I'd favor the use of a char such as
○ instead (which is incidentally how haskell-mode displays the "." char when
used infix).
| Does anything go wrong with irrefutable patterns for existential
types?
Try giving the translation into System F.
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On Tue, Sep 19, 2006 at 01:52:02PM +0100, Conor McBride wrote:
> [EMAIL PROTECTED] wrote:
> >Btw, why are there no irrefutable patterns for GADTs?
>
> Just imagine
>
> > data Eq a b where Refl :: Eq a a
>
> > coerce :: Eq a b -> a -> b
> > coerce ~Refl a = a
>
> coerce undefined True :: String
On 28.09 15:33, Bulat Ziganshin wrote:
> Hello Einar,
>
> Thursday, September 28, 2006, 1:25:55 PM, you wrote:
>
> > Historically HAppS has used ByteStrings in HTTP, while most other
> > libraries have used Strings.
>
> why not use StringLike class here? you can find implementation at
> darcs ge
Hello
I am needing a way to run initializers defined in various modules
in an eager fashion before main. I am doing this to load
deserialization functions for a Typeable function.
Basically I have code like:
$(inferDecoderAndRegisterItOnStartup ''MyType)
which defines a class instance, but add
Hello Einar,
Thursday, September 28, 2006, 1:25:55 PM, you wrote:
> Historically HAppS has used ByteStrings in HTTP, while most other
> libraries have used Strings.
why not use StringLike class here? you can find implementation at
darcs get --partial http://darcs.haskell.org/SoC/fps-soc/
--
B
Hello Bas,
Thursday, September 28, 2006, 2:39:13 AM, you wrote:
>> foo :: {MonadIO m} a -> m a
> Or move contexts to the end of a type and separate it with a | like Clean
> foo :: a -> m a | MonadIO m
i've proposed both these constructs here at list some time ago :
but we don't dec
Thoughts?
Without considering the subtleties of the different meanings of "." in
Haskell, I fail to see what people find so exciting about left to right
function composition. I find "not . null" much easier to read than "null
>>> not", let alone ".null.not".
IMO, the following are good reas
Hello SevenThunders,
Thursday, September 28, 2006, 12:28:45 AM, you wrote:
> Does cabal really work on windows?
i use it since ghc 6.4.2
> Although it's installed I notice that
> when I try to build my library using it, it dies on the first foreign import
> statement in the first .hs source it t
Hello Ch.,
Wednesday, September 27, 2006, 7:31:00 PM, you wrote:
> thus I think I will stay away from using it but argue with
> concrete abstraction features.
> Concerning the point someone made about the features of Haskell:
> * pattern matching: just case distinction
> * list comprehensions: s
On 26.09 10:01, Adam Langley wrote:
> >For the decoding part:
> >* Provide a monadic interface
>
> Are you suggesting a monad to pass in the input around, or that it
> returns mzero on error? The latter makes more sense to me.
Yes. Also make it possible for user supplied functions to fail
in bett
Jason Dagit wrote:
> I tried to create a type class for making instances of Show display a
> custom way. After using my class for a while I found that sometimes
> RealFloats would display as 'NaN' and this is unacceptable. So at
> this point I had something like:
>
> class Show a => StringValue
On 27.09 13:03, Pasqualino 'Titto' Assini wrote:
> There is also the HAppS application server and the HaskellNet library.
>
> Would not be possible to merge the protocol-handling parts of all these
> libraries into a generic Internet Haskell server that could then be expanded
> to support CGIs, tr
On Sep 28, 2006, at 00:38, Jeremy Gibbons wrote:
Perhaps the key is that there exist types P and Q s.t. there's an
isomorphism
F a <=> (P -> a,Q)
F is Naperian iff there's a P with F a = P -> a; but what's the Q for?
This seems to be intuitively Napierian:
ln (P -> a,Q) = (P,ln a) |
Chad Scherrer wrote:
>
> There must be a subtlety I'm missing, right?
What if the types are not instances of Eq?
Jason
Thanks, I figured it was something simple. Now I just to convince
myself there's no way around that. Is there a proof around somewhere?
Yes, there is a proof that
seq :
On 9/27/06, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote:
This message is intended as a long answer to Michael Shulman's
question (Re: variadic functions and typeCast) and Jason Dagit's
question (Re: Duplicate Instance problem). Incidentally, the short
answer to Jason Dagit's question is `constra
32 matches
Mail list logo