Re: [Haskell-cafe] Switching GHC Version

2012-02-06 Thread HASHIMOTO, Yusaku
Thanks for suggestions. Having /usr/bin scripts seems to work for me, Although 
virthualenv looks promising for package dependency management. But when run 
virthualenv with --ghc=tarball, it creates copy of GHC suite inside a project 
whose size is about 700MB.

On 2012/02/07, at 8:41, Brandon Allbery  wrote:

> On Mon, Feb 6, 2012 at 18:27, HASHIMOTO, Yusaku  wrote:
> Hi, I wrote a simple shell function for switching GHC version on the
> system. It works only under Mac OSX, and only switch GHCs installed
> via .pkg installers. It's useful to experiment newer features without
> worrying breaking environment.
> 
> FWIW I'd consider two alternatives:
> 
> (1) forgo links entirely and use something like 
> http://modules.sourceforge.net/ to manage $PATH;
> 
> (2) instead of using the bundled create-links, have the /usr/bin scripts 
> check a per-user symlink and fall back to a system one; running the select 
> script as root sets the system symlink, running as user sets the per-user 
> symlink.
> 
> -- 
> brandon s allbery  allber...@gmail.com
> wandering unix systems administrator (available) (412) 475-9364 vm/sms
> 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Switching GHC Version

2012-02-06 Thread HASHIMOTO, Yusaku
Hi, I wrote a simple shell function for switching GHC version on the
system. It works only under Mac OSX, and only switch GHCs installed
via .pkg installers. It's useful to experiment newer features without
worrying breaking environment.

GHC_BASE_DIR=/Library/Frameworks/GHC.framework/Versions/

ghcs () {
  VERSION=$1
  sudo $GHC_BASE_DIR/$VERSION/Tools/create-links . /Library/Frameworks /
}

Usage:
~/work/today 08:21 ghcs 7.4.0.20111219-x86_64
Password:
~/work/today 08:21 ghc --version
The Glorious Glasgow Haskell Compilation System, version 7.4.0.20111219
~/work/today 08:21 ghcs 7.4.1-x86_64
~/work/today 08:22 ghc --version
The Glorious Glasgow Haskell Compilation System, version 7.4.1

Now I'm curious of better way to achieve this. This have limitations
described above. Even it requires sudo because it modified symbolic
links under `/usr`.

Suggestions?
-nwn

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hierarchical tracing for debugging laziness

2012-01-24 Thread HASHIMOTO, Yusaku
Great, It illustrates why difference lists are awesome.

import HTrace

app :: [a] -> [a] -> [a]
app [] ys = htrace "app" ys
app (x:xs) ys = htrace "app" (x:app xs ys)

rev1 [] = htrace "[]" []
rev1 (x:xs) = htrace "rev1" (app (rev1 xs) [x])

rev2 []     ys = htrace "ys" ys
rev2 (x:xs) ys = htrace ":" (rev2 xs (x:ys))

*Main> rev1 [1..10]
rev1
rev1
rev1
rev1
rev1
rev1
rev1
rev1
rev1
rev1
[]
app
app
app
app
app
app
app
app
app
app
[10app
app
app
app
app
app
app
app
app
,9app
app
app
app
app
app
app
app
,8app
app
app
app
app
app
app
,7app
app
app
app
app
app
,6app
app
app
app
app
,5app
app
app
app
,4app
app
app
,3app
app
,2app
,1]
*Main> rev2 [1..10]

:4:1:
No instance for (Show ([a0] -> [a0]))
  arising from a use of `print'
Possible fix: add an instance declaration for (Show ([a0] -> [a0]))
In a stmt of an interactive GHCi command: print it
*Main> rev2 [1..10] []
:
:
:
:
:
:
:
:
:
:
ys
[10,9,8,7,6,5,4,3,2,1]

Thanks for sharing!

On 25 January 2012 01:47, Eugene Kirpichov  wrote:
> Hi cafe,
>
> Look how one can watch the evaluation tree of a computation, to debug
> laziness-related problems.
>
> {-# LANGUAGE BangPatterns #-}
> module HTrace where
>
> import Data.List (foldl')
> import Data.IORef
> import System.IO.Unsafe
>
> level = unsafePerformIO $ newIORef 0
>
> htrace str x = unsafePerformIO $ do
>   lvl <- readIORef level
>   putStrLn (replicate (4*lvl) ' ' ++ str)
>   writeIORef level (lvl+1)
>   let !vx = x
>   writeIORef level lvl
>   return vx
>
> xs = map (\x -> htrace (show x) x) [1..10]
>
> s = foldl (\a b -> htrace "+" (a+b)) 0 xs
> s2 = foldl' (\a b -> htrace "+" (a+b)) 0 xs
>
> b = htrace "b" 2
> c = htrace "c" 3
> a = htrace "a" $ b + c
> x = htrace "x" $ b + c
>
> *HTrace> a
> a
>     b
>     c
> 5
> *HTrace> x
> x
> 5
>
> *HTrace> s
> +
>     +
>         +
>             +
>                 +
>                     +
>                         +
>                             +
>                                 +
>                                     +
>                                         1
>                                     2
>                                 3
>                             4
>                         5
>                     6
>                 7
>             8
>         9
>     10
> 55
>
> (reload)
> *HTrace> s2
> +
>     1
> +
>     2
> +
>     3
> +
>     4
> +
>     5
> +
>     6
> +
>     7
> +
>     8
> +
>     9
> +
>     10
> 55
>
> --
> Eugene Kirpichov
> Principal Engineer, Mirantis Inc. http://www.mirantis.com/
> Editor, http://fprog.ru/
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: has-0.4 Entity based records

2010-05-22 Thread HASHIMOTO, Yusaku
>> There are many libraries to write function "takes an record has Foo
>> and Bar and returns something." But writing type of the function is
>> still difficult. I can't write such types using HList or records
>> without reading documents. I think, using has, There's few effort to
>> write such types.
>
> In which manner do you need to read less documentation to write:
>
> ] f :: Has Foo r => r -> ...
>
> Instead when using HList:
>
> ] f :: HasField Foo record fieldType => ...

HasField only gives projection function (hLookupByLabel), but Has
gives projection, injection and modification function.

If I want to write a generic function injecting a value into field Foo
in a record by HList, I should read documentation more.

>> I think `has' fits the needs of Haskellers who have the good habit of
>> writing a type of a function before its definition.
>
> What does this mean exactly in terms of the type inference possible?

Probably, yes. it's still fragile due to some reasons e.g. the
behavior of UndecidableInstances language extension.

> import Data.Has
> data Foo = Foo; type instance TypeOf Foo = Int
> data Bar = Bar; type instance TypeOf Bar = Int
> f r = (Foo ^. r) + (Bar ^. r)

*Main> :t f
f :: forall s.
 (Contains (Labelled Foo Int) s, Contains (Labelled Bar Int) s) =>
 s -> TypeOf Foo

-nwn
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: has-0.4 Entity based records

2010-05-13 Thread HASHIMOTO, Yusaku
Sorry for spamming, what I wanted to write is I think `has' has better
interface than other record packages in types.

There are many libraries to write function "takes an record has Foo
and Bar and returns something." But writing type of the function is
still difficult. I can't write such types using HList or records
without reading documents. I think, using has, There's few effort to
write such types.

I think `has' fits the needs of Haskellers who have the good habit of
writing a type of a function before its definition.

On 14 May 2010 07:58, HASHIMOTO, Yusaku  wrote:
> On 11 May 2010 03:25, adam vogt  wrote:
>> On Tue, May 4, 2010 at 12:18 PM, HASHIMOTO, Yusaku  
>> wrote:
>>> This library is inspired by HList[2], and interfaces are stealed from
>>> data-accessors[3]. And lenses[4], fclabels[5], and records[6] devote
>>> themselves to similar purposes.
>>>
>>> [2]: http://hackage.haskell.org/package/HList
>>> [3]: http://hackage.haskell.org/package/data-accessor
>>> [4]: http://hackage.haskell.org/package/lenses
>>> [5]: http://hackage.haskell.org/package/fclabels
>>> [6]: http://hackage.haskell.org/package/records
>>>
>>> Enjoy!
>>>
>>> -nwn
>>
>> Which niche does `has' fit between extensible (and more complicated)
>> records like HList and records vs the libraries that provide only
>> accessors?
>
> You may find `has' useful when you want to use a label name in more
> than one record structures. This is achieved by HList, records and
> wreckage, But I think has at its interface.
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: has-0.4 Entity based records

2010-05-13 Thread HASHIMOTO, Yusaku
On 11 May 2010 03:25, adam vogt  wrote:
> On Tue, May 4, 2010 at 12:18 PM, HASHIMOTO, Yusaku  wrote:
>> This library is inspired by HList[2], and interfaces are stealed from
>> data-accessors[3]. And lenses[4], fclabels[5], and records[6] devote
>> themselves to similar purposes.
>>
>> [2]: http://hackage.haskell.org/package/HList
>> [3]: http://hackage.haskell.org/package/data-accessor
>> [4]: http://hackage.haskell.org/package/lenses
>> [5]: http://hackage.haskell.org/package/fclabels
>> [6]: http://hackage.haskell.org/package/records
>>
>> Enjoy!
>>
>> -nwn
>
> Which niche does `has' fit between extensible (and more complicated)
> records like HList and records vs the libraries that provide only
> accessors?

You may find `has' useful when you want to use a label name in more
than one record structures. This is achieved by HList, records and
wreckage, But I think has at its interface.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: has-0.4 Entity based records

2010-05-04 Thread HASHIMOTO, Yusaku
I think I missed your point in my last post, and there are more
necessary extensions need to be enabled than I wrote before.

TypeFamilies, TypeOperator and FlexibleContexts extensions are
necessary. So you need to write this at top of the code if you don't
choose OPTIONS_GHC pragma.

> {-# LANGUAGE TypeFamilies,TypeOperators,FlexibleContexts #-}

Sorry for incorrect information.

-nwn

On 5 May 2010 02:33, HASHIMOTO, Yusaku  wrote:
> I uploaded new version (0.4.0.1) of this package with proper pragmas.
>
> On 5 May 2010 02:00, HASHIMOTO, Yusaku  wrote:
>> Hello
>>
>>>> I'm pleased to announce the release of my new library, named "has",
>>>> written to aim to ease pain at inconvinience of Haskell's build-in
>>>> records.
>>>
>>> Hmm, nice work, looks interesting.
>>
>> Thanks!
>>
>>>> You can use the has in three steps (without counting installation).
>>>>
>>>> 1. Write {-# OPTIONS_GHC -fglasgow-exts #-} top of your code,
>>>
>>> This is going out of style.  It would be nice to know specifically
>>> what LANGUAGE extensions are necessary.
>>
>> Ah, yes. {-# LANGUAGE TypeFamilies #-} is enough for that literate
>> haskell file, But the has depends GHC's language extensions such as
>> UndecidableInstances, OverlappingInstances and TypeFamilies. But I'll
>> remove OPTIONS_GHC pragma from library codes. Thank you for your
>> suggestion.
>>
>> -nwn
>>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: has-0.4 Entity based records

2010-05-04 Thread HASHIMOTO, Yusaku
I uploaded new version (0.4.0.1) of this package with proper pragmas.

On 5 May 2010 02:00, HASHIMOTO, Yusaku  wrote:
> Hello
>
>>> I'm pleased to announce the release of my new library, named "has",
>>> written to aim to ease pain at inconvinience of Haskell's build-in
>>> records.
>>
>> Hmm, nice work, looks interesting.
>
> Thanks!
>
>>> You can use the has in three steps (without counting installation).
>>>
>>> 1. Write {-# OPTIONS_GHC -fglasgow-exts #-} top of your code,
>>
>> This is going out of style.  It would be nice to know specifically
>> what LANGUAGE extensions are necessary.
>
> Ah, yes. {-# LANGUAGE TypeFamilies #-} is enough for that literate
> haskell file, But the has depends GHC's language extensions such as
> UndecidableInstances, OverlappingInstances and TypeFamilies. But I'll
> remove OPTIONS_GHC pragma from library codes. Thank you for your
> suggestion.
>
> -nwn
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: has-0.4 Entity based records

2010-05-04 Thread HASHIMOTO, Yusaku
Hello

>> I'm pleased to announce the release of my new library, named "has",
>> written to aim to ease pain at inconvinience of Haskell's build-in
>> records.
>
> Hmm, nice work, looks interesting.

Thanks!

>> You can use the has in three steps (without counting installation).
>>
>> 1. Write {-# OPTIONS_GHC -fglasgow-exts #-} top of your code,
>
> This is going out of style.  It would be nice to know specifically
> what LANGUAGE extensions are necessary.

Ah, yes. {-# LANGUAGE TypeFamilies #-} is enough for that literate
haskell file, But the has depends GHC's language extensions such as
UndecidableInstances, OverlappingInstances and TypeFamilies. But I'll
remove OPTIONS_GHC pragma from library codes. Thank you for your
suggestion.

-nwn
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: has-0.4 Entity based records

2010-05-04 Thread HASHIMOTO, Yusaku
Hello,

I'm pleased to announce the release of my new library, named "has",
written to aim to ease pain at inconvinience of Haskell's build-in
records.

With the has, You can reuse accessors over records to write generic
function, combine records with another.

Repository is at GitHub: http://github.com/nonowarn/has
Uploaded on Hackage: http://hackage.haskell.org/package/has

So you can install this by "cabal install has"

You can use the has in three steps (without counting installation).

1. Write {-# OPTIONS_GHC -fglasgow-exts #-} top of your code,
   import Data.Has module.

> {-# OPTIONS_GHC -fglasgow-exts #-}
> import Data.Has

2. Define entities. "Entity" is data to index field in records.
   You can define an entity in one line.

> data Foo = Foo; type instance TypeOf Foo = Int

   (I lied) Before semicolon, declares entity. After semicolon,
   specifies the type to which the entity points.

   Define some entities for later examples.

> data Bar = Bar; type instance TypeOf Bar = Double
> data Baz = Baz; type instance TypeOf Baz = String
> data Quux = Quux; type instance TypeOf Quux = Bool

3. Define Records by concatinating fields of entities.

> type MyRecord = FieldOf Foo :&: FieldOf Bar :&: FieldOf Baz

   This is almost same as writing

< data MyRecord = MyRecord { foo :: Int
<  , bar :: Double
<  , baz :: String
<  }

   To construct a value of record, remove colons and replace entities
   in record with values, and uncapitalize some words.

> aRecord :: MyRecord
> aRecord = fieldOf 42 & fieldOf 3.14 & fieldOf "string"

   And you can play with it.

To read/write/modify a value of field in records, you can use
functions with names stealed from data-accessor. But uses value-level
entities instead of accessors.

< Foo ^. aRecord   -- Reading
< Foo ^= 4649 $ aRecord-- Writing
< Foo ^: (*2) $ aRecord-- Modifying

If we have another record type contains Foo field, You can still
access the field in the same way.

> type AnotherRecord = FieldOf Bar :&: FieldOf Foo
> anotherRecord :: AnotherRecord
> anotherRecord = fieldOf 2.71 & fieldOf 31

< Foo ^. anotherRecord -- And this also works

Using these functions and Has constraint, You can write generic
functions over records.

> fooIsGreaterThan :: (Has Foo r) => r -> Int -> Bool
> fooIsGreaterThan r x = (Foo ^. r) > x

< aRecord `fooIsGreaterThan` 40   -- evaluated to True
< anotherRecord `fooIsGreaterThan` 40 -- evaluated To False

Even if you defined another record by combining records by (:&:), you
can still access the field, and apply to generic functions.

> type MoreRecord = FieldOf Baz :&: FieldOf Quux
> type CombinedRecord = AnotherRecord :&: MoreRecord
> combinedRecord :: CombinedRecord
> combinedRecord = (fieldOf 1.618 & fieldOf 39) & (fieldOf "sowaka" & fieldOf 
> True)
>-- We can omit parentheses
>-- (even place parens anyware in record)

< combinedRecord `fooIsGreaterThan` 40 -- This yet works

The Has constraint provides not only genericity but also safety. If
the record doesn't satisfy the constraint, the type checker rejects
it.

> predicateOnRecords :: (Has Foo r, Has Quux r) => r -> Bool
> predicateOnRecords r = fooIsGreaterThan r 30 && (Quux ^. r)

< predicateOnRecords combinedRecord -- This is OK
< predicateOnRecords aRecord-- This yields compile error

More examples included in package[1]

[1]: http://github.com/nonowarn/has/tree/master/examples/

This library is inspired by HList[2], and interfaces are stealed from
data-accessors[3]. And lenses[4], fclabels[5], and records[6] devote
themselves to similar purposes.

[2]: http://hackage.haskell.org/package/HList
[3]: http://hackage.haskell.org/package/data-accessor
[4]: http://hackage.haskell.org/package/lenses
[5]: http://hackage.haskell.org/package/fclabels
[6]: http://hackage.haskell.org/package/records

Enjoy!

-nwn
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe