On Mon, Jul 13, 2009 at 10:33 PM, Ashley Yakeley wrote:
> On Mon, 2009-07-13 at 23:20 -0700, Jason Dagit wrote:
> > data EqualType a b where
> >MkEqualType :: EqualType t t
> >
> > Is there any reason to prefer this over:
> > data EqualType a b where
> > MkEqualType :: Equal
On Mon, 2009-07-13 at 23:20 -0700, Jason Dagit wrote:
> data EqualType a b where
>MkEqualType :: EqualType t t
>
> Is there any reason to prefer this over:
> data EqualType a b where
> MkEqualType :: EqualType a a
They're exactly the same. Yours just looks a bit "left-biase
+++ Kemps-Benedix Torsten [Jul 13 09 23:56 ]:
> Hello,
>
> is there a working example of how to use the format clause with
> HStringTemplate, e.g. for Data.Time.Day? I think, if there is a parameter
> $day$, a reasonable template might contain e.g.:
>
> $day;format="%d.%b.%Y"$
>
> But I only g
On Mon, Jul 13, 2009 at 10:52 PM, Ashley Yakeley wrote:
> Ryan Ingram wrote:
>
> data Type a where
>>> TInt :: Type Int
>>> TBool :: Type Bool
>>> TChar :: Type Char
>>> TList :: Type a -> Type [a]
>>> TFun :: Type a -> Type b -> Type (a -> b)
>>>
>>
> "Type" here is what I call a simpl
Ryan Ingram wrote:
data Type a where
TInt :: Type Int
TBool :: Type Bool
TChar :: Type Char
TList :: Type a -> Type [a]
TFun :: Type a -> Type b -> Type (a -> b)
"Type" here is what I call a simple type witness. Simple type witnesses
are useful because they can be compared by v
Hi,
I have a data structure, which shows like this: AttrBgColor {bgColor
= Color 0 0 0}
And the following is my Read code. But it failed parsing
31 instance Read Attribute where
32 readsPrec _ str = [ (mkAttr attr_ color, rest) | (attr_, rest1) <- lex str
33
It does seem that having quantified contexts would make this *much* easier...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Hello,
is there a working example of how to use the format clause with
HStringTemplate, e.g. for Data.Time.Day? I think, if there is a parameter
$day$, a reasonable template might contain e.g.:
$day;format="%d.%b.%Y"$
But I only get "toModifiedJulianDay: [54960]" as the result which correspond
Malcolm Wallace wrote:
> > {-# LANGUAGE CPP #-}
>> main = putStrLn (__FILE__ ++ ":" ++ show __LINE__)
>>
>> This outputs:
>> test.hs:2
>
>> if I had a module Foo.Bar.Car.MyModule, I would like to be able to
>> output something like this on error:
>> Foo.Bar.Car.MyModule:2
>
> It works for me. If
George Pollard schrieb:
> Ok, so I have a small idea I'm trying to work on; call it a
> Prelude-rewrite if you want. For this I want to be able to have the
> hierarchy Functor → Applicative → Monad.
>
> For Functor, I would like to be able to implement it for a wider
> variety of types, as there a
On Mon, Jul 13, 2009 at 6:09 AM, Chris Eidhof wrote:
> Hey Kev,
>
> The types are "thrown away" during compile time. Therefore, if you have a
> constructor "VWrapper :: a -> Value" nothing is known about that "a" when
> you scrutinize it.
>
> What you could do, however, is something like this:
>
{-# LANGUAGE CPP #-}
main = putStrLn (__FILE__ ++ ":" ++ show __LINE__)
This outputs:
test.hs:2
if I had a module Foo.Bar.Car.MyModule, I would like to be able to
output something like this on error:
Foo.Bar.Car.MyModule:2
It works for me. If you place that text in Try/Me.hs and call
Matthew Elder wrote:
> {-# LANGUAGE CPP #-}
> main = putStrLn (__FILE__ ++ ":" ++ show __LINE__)
>
> This outputs:
> test.hs:2
>
> Unfortunately, if your file is in a hierarchy of folders, this flat file
> name doesn't give much context. Is there a macro to find out the current
> module? IE if I
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
On Mon, Jul 13, 2009 at 9:18 AM, Kev Mahoney wrote:
> That said, I think I may defer this until I understand the ins and
> outs of Haskell's type system a little better. I think a parametrized
> type will be the only way to do it. The only reason I thought GADTs
> may be able to do this is because
Thanks, I hadn't noticed Data.Dynamic. It never even occurred to me
that something like this would be in the standard libraries. It looks
like it's precisely what I was looking for, after a brief scan of the
documentation.
I will report back if I bump into any problems with it
2009/7/13 Chaddaï F
Hello Cafe,
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
On Mon, Jul 13, 2009 at 12:41 PM, Kev
Mahoney wrote:
> So far, I've learnt you can do this:
>
> data Value where
> VInt :: Integer -> Value
> ...
> VWrapper :: a -> Value
>
> which can let you encode arbitrary 'dynamic' types into Value. I was
> hoping to be able to pattern match to get the value o
Oops, wrong mail account for my last email. Apologies.
What I'm trying to accomplish is being able to write haskell libraries
for the interpreter that don't use the interpreter's predefined Value
types, without having to edit the Value type itself and add a new
constructor (i.e. it's abstracted aw
> It’s tempting to say, we should
> use the original English, which is British English.
Some suggest the original English remained in Britain when the North
American colonies were founded; others claim it was brought to the
Americas by the British settlers, leaving a pale imitation back in
Britain
Then you could add a specific constructor for String. The main point
is: the case construct only works for values, not for types. There is
no typecase construct. If you want to have certain restrictions on the
'a', such as the Show class, you could also do something like this:
> data Value
>> Nice idea. Perhaps use a merge sort, because that is actually useful,
>> because it does not degenerate for large lists.
>
> Great idea if we want to keep Haskell community compact :)))
Or stay with quicksort --- which is treesort. :o)
___
Haskell-Ca
Hello Matthias,
Monday, July 13, 2009, 6:05:06 PM, you wrote:
>> I like the quicksort example at
> Nice idea. Perhaps use a merge sort, because that is actually useful,
> because it does not degenerate for large lists.
Great idea if we want to keep Haskell community compact :)))
--
Best reg
> I like the quicksort example at
> http://www.haskell.org/haskellwiki/Introduction very much; it shows how much
> time you can save when you use Haskell.
Nice idea. Perhaps use a merge sort, because that is actually useful,
because it does not degenerate for large lists.
Matthias.
_
On Mon, 13 Jul 2009 12:43:07 +0200, Matthias Görgens
wrote:
code snippet: no hello world please. That's not a way to judge a
language! But: a random haskell one line snippet with explanation would
be cool.
Perhaps a solution to a problem like the ones you can find on Project
Euler (http://p
Hey Kev,
The types are "thrown away" during compile time. Therefore, if you
have a constructor "VWrapper :: a -> Value" nothing is known about
that "a" when you scrutinize it.
What you could do, however, is something like this:
data Value a where
VInt :: Integer -> Value Integer
...
Dan Doel wrote:
Hope that helps.
It does, thanks!
Jeremy
--
The University of Edinburgh is a charitable body, registered in
Scotland, with registration number SC005336.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/m
> code snippet: no hello world please. That's not a way to judge a
> language! But: a random haskell one line snippet with explanation would
> be cool.
Perhaps a solution to a problem like the ones you can find on Project
Euler (http://projecteuler.net/index.php?section=problems). Of course
you c
Hi there,
I'm currently writing an interpreter that I would like to be able to
use with other haskell programs. I would like to be able to pass along
arbitrary types though the interpreter. I've seen hints that GADTs can
do this, but I am having trouble understanding them.
So far, I've learnt you
Brent Yorgey wrote:
> Raynor Vliegendhart wrote:
>
>> One of the examples I tried was:
>>
>>hylo (unfoldr (\a -> Just (a,a))) head $ 42
>>
>> This expression fails to determinate.
>>
>> Here are two examples copumpkin tried on IRC:
>>
>> > let hylo f g = g . fmap (hylo f g) . f in hylo (flip
Hum I must lost my mind
Thank you.
On Mon, Jul 13, 2009 at 3:33 PM, Ketil Malde wrote:
> Magicloud Magiclouds writes:
>
>> 43 instance Read Attribute where
>> 44 readsPrec _ str = [ (mkAttr attr_ color, rest) | (attr_, rest1) <- lex
>> str
>> 45
Magicloud Magiclouds writes:
> 43 instance Read Attribute where
> 44 readsPrec _ str = [ (mkAttr attr_ color, rest) | (attr_, rest1) <- lex
> str
> 45 , (color, rest) <- case
> reads rest1 of
> 46
32 matches
Mail list logo