[Haskell-cafe] Transforming AST parametrized with type

2013-09-10 Thread Sergey Mironov
Hi. Pat asked a question [1] about AST parametrized with types. People
suggest to use Functor machinery if possible. Have anything changed
since them? Do we have a way to safely transform the tree like

data Expr a = Id { id :: Id a } | Op { op :: Char, expra :: (Expr a) ,
exprb :: (Expr a) }

data Id a = Id { name :: a }

from Expr String to, say, Expr Int where Int names may represent some
keys in the hash map?

Regards,
Sergey

[1] -  
http://stackoverflow.com/questions/5434889/is-it-possible-to-use-syb-to-transform-the-type

PS sclv suggested to use synthesize from SYB to solve the problem.
Could anyone provide me with example of this method?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Looking for GUI examples

2013-09-10 Thread Sergey Mironov
Wow. Thanks! Looks impressive.

Regards,
Sergey

2013/9/10 Ivan Perez :
> You may want to check one of Keera Studios' apps. All four of these do what
> you want:
>
> https://github.com/ivanperez-keera/haskellifi-trayicon
> https://github.com/ivanperez-keera/keera-diamondcard-sms-trayicon
> https://github.com/ivanperez-keera/keera-three-balance-checker
> https://github.com/keera-studios/keera-posture
>
> The code is well organised, each module tries to implement only one feature.
> The part that adds the tray icon, menus and modifies the image is in the
> Controller; usually you'd be looking for files with the names Icon*,
> Status*, Tray* or *Menu*
>
> One example:
> https://github.com/ivanperez-keera/haskellifi-trayicon/blob/master/src/Controller/Conditions/WifiListMenu.hs
> https://github.com/ivanperez-keera/haskellifi-trayicon/blob/master/src/Controller/Conditions/Icon.hs
>
> Note that the first module adds the menu to the icon, and the second one
> changes the icon.
>
> There are more complex examples in the other programs.
>
> Let me know if you have any questions.
>
> Cheers
>
> Ivan
>
>
> On 9 September 2013 15:23, Henk-Jan van Tuyl  wrote:
>>
>> On Mon, 09 Sep 2013 11:48:42 +0200, Sergey Mironov 
>> wrote:
>>
>>> Hi, Cafe. I'd like to write simple GUI utility containing tray icon
>>> and the menu. Could you please suggest Haskell example to make my
>>> start easier?
>>
>>
>> There is a simple wxHaskell program for this:
>>
>> https://github.com/wxHaskell/wxHaskell/blob/master/samples/wx/TestTaskBarIcon.hs
>>
>> There is however a problem with this (maybe just on Windows), see the bug
>> report I just entered:
>> http://sourceforge.net/p/wxhaskell/bugs/71/
>>
>> Regards,
>> Henk-Jan van Tuyl
>>
>>
>> --
>> Folding@home
>> What if you could share your unused computer power to help find a cure? In
>> just 5 minutes you can join the world's biggest networked computer and get
>> us closer sooner. Watch the video.
>> http://folding.stanford.edu/
>>
>>
>> http://Van.Tuyl.eu/
>> http://members.chello.nl/hjgtuyl/tourdemonad.html
>> Haskell programming
>> --
>>
>>
>> ___
>> 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


[Haskell-cafe] Looking for GUI examples

2013-09-09 Thread Sergey Mironov
Hi, Cafe. I'd like to write simple GUI utility containing tray icon
and the menu. Could you please suggest Haskell example to make my
start easier?

Regards,
Sergey

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


[Haskell-cafe] [ANN] thirdake-0.1 the Makefile-like DSL

2013-07-29 Thread Sergey Mironov
Hi, cafe.

Neil Mitchell mentioned more than ten build systems written in Haskell in his
paper [1]. The list includes shake (of cause) Abba, Coadjuke, hake, hmk, and
even two cakes.

I'm glad to announce the thirdcake - a DSL for make language. Thirdcake allows
user to produce clean and safe (I hope) Makefiles for the good old GNU make.

The package is in it's early stages and is not on Hackage yet. Consider visiting

  https://github.com/grwlf/cake3

or just

  git clone https://github.com/grwlf/cake3

./Example/Foo contains working toy-project demonstrating the approach.

Regards,
Sergey

[1] - 
http://community.haskell.org/~ndm/downloads/paper-shake_before_building-10_sep_2012.pdf


PS
My English is still buggy, feel free to patch the grammar as well as the rest

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


Re: [Haskell-cafe] [Haskell] [ANN] Initial release of the threepenny-gui library, version 0.1.0.0

2013-07-21 Thread Sergey Mironov
Hi, I have a Path problem when installing threepenny-gui from Hackage.
Probably somtething trivial.

Sergey


src/BarTab.hs:9:8:
Could not find module `Paths'
Use -v to see a list of the files searched for.
Failed to install threepenny-gui-0.1.0.0
cabal: Error: some packages failed to install:
threepenny-gui-0.1.0.0 failed during the building phase. The exception was:
ExitFailure 1



2013/7/21 Heinrich Apfelmus :
> Dear Haskellers,
>
> And the shark, he has teeth,
> And he wears them in (his) face.
> And Macheath, he has a knife,
> (But) yes the knife, no-one sees.
>
> After an obligatory cryptical quotation from a famous writer, I am pleased
> to announce the first public release of *threepenny-gui*, a cheap and simple
> library to satisfy your immediate GUI needs in Haskell.
>
> Want to write a small GUI thing but forgot to sacrifice to the giant rubber
> duck in the sky before trying to install wxHaskell or Gtk2Hs? Then this
> library is for you!
>
> Threepenny-gui is easy to install (!!) because it uses the web browser as a
> display. Internally, we implement a small web server that communicates with
> the browser to display GUI elements. Consequently, you can use HTML and CSS
> to design the user interface. You can freely manipulate the HTML DOM and
> handle browser events by writing Haskell code.
>
>   hackage  - http://hackage.haskell.org/package/threepenny-gui
>   examples - https://github.com/HeinrichApfelmus/threepenny-gui#examples
>   source   - https://github.com/HeinrichApfelmus/threepenny-gui
>
> Many thanks to Daniel Austin for collaborating with me on this project and
> to Chris Done for implementing the Ji library which is the basis for this
> effort.
>
>
> On that note, the threepenny API for creating and manipulating GUI elements
> departs from earlier traditions. Do you like the new look and feel of the
> API? What do you think could be improved? Try it out and send us your
> feedback!
>
>
> Best regards,
> Heinrich Apfelmus
>
> --
> http://apfelmus.nfshost.com
>
>
> ___
> Haskell mailing list
> hask...@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell

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


[Haskell-cafe] Announce: vsim the VHDL-subset simulator (unmaintained)

2013-05-21 Thread Sergey Mironov
Hi. I'd like to announce the vsim - the simulator for (small subset
of) VHDL language. Currently
the project contains pretty large Java part and is not maintained.
That's why I don't want to
publish it on Hackage. Still, as far as I now have a permission to
share the code, I would like to do it.

https://github.com/grrwlf/vsim

VSim is a VHDL simulator project aimed develop a methods of compiling VHDL code
into a high-level language (Haskell). Currently it is able to compile simple
VHDL programs, containing plain integer types, 1-dimentional arrays, records. It
supports processes, procedures, functions (partly). Breakpoints and wait
statements should work.

Simulator compile VHDL into Haskell in several steps.

Firstly, VHDL is translated into VIR-file by a translator written in Java (see
tr/ folder and runtr function in ./simenv shell script). VIR file is lisp-like
file, describing vhdl entities in a less complex manner. For example, it
contains all the port maps expanded.

Secondly, VSim tool is used to translate VIR into Haskell (see src/ folder and
runsim functino in ./simenv). VSim is a small program which translates VIR
line-by-line into Haskell program. haskell-src-exts is used to build the AST
and print it to stdout.

Finaly, Haskell program should be compiled into binary with ghc having runtime
library included (refer to src\_r/ folder and runsim function in ./simenv).
The runtime is the heart of the simulator and it's largest part.

Java part is a main headache, because it is big, unsupported and has bugs
lurking here and there. Haskell part is smaller and cleaner, but VHDL-standard
coverage is still poor. For example, signal assignments are working as if they
are declared with transport delay mechanism. Another problem is missing enum
support except of some pre-defined.

Sergey

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


[Haskell-cafe] ANN haskdogs-0.3.2

2013-05-13 Thread Sergey Mironov
Hi. I'm pleased to announce haskdogs-0.3.2, a source navigation helper.

Haskdogs is a small HSH-based tool which calls hasktags to create tag file for
entire haskell project. It takes into account first-level dependencies by
recursively scanning imports and adding matching packages to the final tag list.

As a result, programmer can use her text editor supporting tags (vim, for
example) to jump directly to definition of any function she uses.

Note that haskdogs call Unix shell commands like 'test' or 'mkdir' so this tool
will likely fail to work on pure Windows platforms. In return, haskdogs is
pretty small - only 125 lines long.

Changes:

* Generate extended tag file by default (hasktags -c -x)
* Add -d command line option which allows user to specify additional source
  directories
* Fix no-sources bug

Github: https://github.com/ierton/haskdogs
See also Vim-hint at https://github.com/ierton/haskdogs#vim-hint

Install:

cabal install hasktags haskdogs

Usage:

haskdogs [-d (FILE|'-')] [FLAGS]
FLAGS will be passed to hasktags as-is followed by
a list of files. Defaults to -c -x.


Basically, just run haskdogs in your Haskell project directory

Thanks to yihuang for the contributions!

Sergey

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


Re: [Haskell-cafe] JSON querying

2013-02-17 Thread Sergey Mironov
2013/2/17 Oliver Charles :
> On 02/17/2013 03:01 PM, Sergey Mironov wrote:
>>
>> Hi folks. Hackage contains several JSON packages but as far as I see,
>> they all provide 'static' conversion from JSON format to Haskell data
>> type. Is there a method of converting object containing optional filed
>> 'a' to for example Maybe a.
>
> Assuming you have some sort of 'path' to the key in question, aeson-lens
> might be exactly what you want:
> http://hackage.haskell.org/package/aeson-lens
>
> I use aeson-lens to turn a list of strings of the form ["foo", "bar", "baz"]
> into a query into first the 'foo' object, then the 'bar' object, then the
> 'baz' object, using the following:
>
> pathToLens :: Functor f
>=> [T.Text]
>-> (Maybe Value -> f (Maybe Value))
>-> Maybe Value
>-> f (Maybe Value)
> pathToLens [p] = key p
> pathToLens ps = let ps' = filter (not . T.null) ps
> in key (head ps') . (foldl (.) id . map pathElem $ tail ps')
>   where
> pathElem p = maybe (key p) nth (readMay $ T.unpack p)
>
> So as you can see - I turn any arbitrary path into a query into JSON, with a
> chance of failure.
>
> Hope this helps!
> - Ollie
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

Good news, thanks a lot!

Sergey

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


[Haskell-cafe] JSON querying

2013-02-17 Thread Sergey Mironov
Hi folks. Hackage contains several JSON packages but as far as I see,
they all provide 'static' conversion from JSON format to Haskell data
type. Is there a method of converting object containing optional filed
'a' to for example Maybe a.

Thanks, Sergey

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


Re: [Haskell-cafe] Moscow Haskell Users Group (MskHUG) December meeting.

2012-12-03 Thread Sergey Mironov
Hi. Great idea, I'm in.

Sergey


2012/12/3 Serguey Zefirov :
> I would like to announce MskHUG December meeting and invite everyone 
> interested.
>
> The meeting will take place December 13th, 20:00 to 23:30 in the nice
> conference center in centre of Moscow: http://www.nf-conference.ru/
>
> The meeting's agenda is to start more intense discussions. Most
> probably, there will be a couple of short presentations - I can tell
> about creating fast Haskell programs to handle large data to start the
> discussion.
>
> I will bring white paper and pencils for everyone to write and draw,
> there will be projector and screen and also tea, cofee and snacks.
>
> If you want to participate, please, email me.
>
> ___
> 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] Copying a syntax tree

2012-10-02 Thread Sergey Mironov
Yes, thats good solution. Let me complicate things a bit. Lets define
last data, D, in a different way:

> data A a = A Int Int (B a)
> data B a = B String String (C a)
> data C a = C Int Int (D a)
>
> data D a = D Int (F a)

where F is a type function

> type family F t
> data Stage1
> data Stage2
> type instance F Stage1 = Int
> type instance F Stage2 = String

This time D is not a functor, because 'a' can accept only either
Stage1 or Stage2. And what I need is to quickly define copy :: A
Stage1 -> A Stage2

is it possible without writing boilerplate?

2012/10/2 Erik Hesselink :
> You could add {-# LANGUAGE DeriveFunctor #-}, and then add 'deriving
> Functor' to all your data types (or you could of course manually
> define your functor instances). Then what you want is just 'fmap
> show'.
>
> Erik
>
> On Tue, Oct 2, 2012 at 9:55 AM, Sergey Mironov  wrote:
>> Hi! I have a syntax tree defined like this:
>>
>>>
>>> data A a = A Int Int (B a)
>>>
>>> data B a = B String String (C a)
>>>
>>> data C a = C Int Int (D a)
>>>
>>
>> and so on, all the data are parametrized with a type variable. This variable
>> is actually used as a field in the very end of a hierarchy:
>>
>>>
>>> data D a = D Int a
>>>
>>
>> Now I have to write a function which would copy (A Int) to (A String). Is it
>> possible to do so using TH/syb without writing
>>
>> copyA (A i1 i2 b) = A i1 i2 (copyB b)
>> copyB = ...
>> copyC = ...
>> ..
>> copyD (D i a) = D i (show a)
>> ?
>>
>> Could you provide me with a hint?
>>
>> Thanks,
>> Sergey
>>
>> ___
>> 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


[Haskell-cafe] Copying a syntax tree

2012-10-02 Thread Sergey Mironov
Hi! I have a syntax tree defined like this:

>
> data A a = A Int Int (B a)
>
> data B a = B String String (C a)
>
> data C a = C Int Int (D a)
>

and so on, all the data are parametrized with a type variable. This variable
is actually used as a field in the very end of a hierarchy:

>
> data D a = D Int a
>

Now I have to write a function which would copy (A Int) to (A String). Is it
possible to do so using TH/syb without writing

copyA (A i1 i2 b) = A i1 i2 (copyB b)
copyB = ...
copyC = ...
..
copyD (D i a) = D i (show a)
?

Could you provide me with a hint?

Thanks,
Sergey

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


[Haskell-cafe] IO vs MonadIO

2012-09-12 Thread Sergey Mironov
Hi. Just a brief question. System.IO functions are defined in IO monad
and have signatures like Foo -> IO Bar.
Would it be better to have all of them defined as (MonadIO m) => Foo
-> m Bar? What are the problems that would arise?

Sergey

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


[Haskell-cafe] ANNOUNCE vkhs-0.0.3

2012-09-08 Thread Sergey Mironov
I'm happy to announce a new package called VKHS:

http://hackage.haskell.org/package/VKHS
https://github.com/ierton/vkhs

VKHS provides access to Vkontakte [1] (popular Russian social network)
API methods.
Library can be used to login into the network as a standalone application
(OAuth implicit flow as they call it). Interaction with user is not required.
For now, vkhs offers limited error detection and no captcha support. Here is an
example code:

import Web.VKHS.Login
import Web.VKHS.Api

main = do
let client_id = "11" -- application id, register first
let user_of_interest = "22"
let e = env client_id "u...@example.com" "password"
[Photos,Audio,Groups]
(Right at) <- login e
(Right ans) <- api e at "users.get" [
  ("uids",user_of_interest)
, ("fields","first_name,last_name,nickname,screen_name")
, ("name_case","nom")
]
putStrLn ans

Internally, library uses small curl-based HTTP automata and tagsoup for jumping
over relocations and submitting various 'Yes I agree' forms.

Sergey.

[1] - http://vk.com

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


[Haskell-cafe] package categories

2012-09-08 Thread Sergey Mironov
Hello list. Do we have a guideline for selecting correct category for
a package being developed? I'd like to choose between Web.MyLib and
Network.MyLib. Or probably just MyLib if I feel ambitious?
Sergey.

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


Re: [Haskell-cafe] map over Bijections

2012-08-27 Thread Sergey Mironov
Yes, you are right, I don't really need the second argument. I am not
skilled enough to join the discussion, but I do understand your
solution. Thanks!

Sergey

2012/8/27 Tillmann Rendel :
> Hi,
>
>
> Sergey Mironov wrote:
>>
>> I need map equivalent for Bijection type which is defined in fclabels:
>>
>> data Bijection (~>) a b = Bij { fw :: a ~> b, bw :: b ~> a }
>>
>> instance Category (~>) => Category (Bijection (~>)) where ...
>>
>> I can define this function as follows:
>> mapBij :: Bijection (->) a c -> Bijection (->) [a] [b] -> Bijection (->)
>> [a] [c]
>> mapBij b1 b = (map (fw b1)) `Bij` (map (bw b1))
>
>
> Two observations.
>
> First observation: The second argument seems unnecessary, so we have the
> following instead:
>
>> mapBij :: Bijection (->) a c -> Bijection (->) [a] [c]
>> mapBij b = (map (fw b)) `Bij` (map (bw b))
>
>
> Second observation: I guess this works for arbitrary functors, not just
> lists, so we get the following:
>
>> fmapBij :: Functor f => Bijection (->) a c -> Bijection (->) (f a) (f c)
>> fmapBij b = (fmap (fw b)) `Bij` (fmap (bw b))
>
>
> Lets check that fmapBij returns a bijection:
>>
>>   fw (fmapBij b) . bw (fmapBij b)
>>   {- unfolding -}
>> = fmap (fw b) . fmap (bw b)
>>   {- functor -}
>> = fmap (fw b . bw b)
>>   {- bijection -}
>> = fmap id
>>   {- functor -}
>> = id
>
>
> Looks good.
>
>
> I guess we can generalize this to get: If f is a functor on a category c, it
> is also a functor on the category (Bijection c). But I am not sure how to
> express this with Haskell typeclasses. Maybe along the lines of:
>
>> import Control.Categorical.Functor -- package categories
>>
>> instance Endofunctor f cat => Endofunctor f (Bijection cat) where
>>   fmap b = (fmap (fw b)) `Bij` (fmap (bw b))
>
>
> So Bijection is a functor in the category of categories?
>
>   Tillmann
>
>
>
>

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


[Haskell-cafe] map over Bijections

2012-08-27 Thread Sergey Mironov
Hi. I need map equivalent for Bijection type which is defined in fclabels:

data Bijection (~>) a b = Bij { fw :: a ~> b, bw :: b ~> a }

instance Category (~>) => Category (Bijection (~>)) where ...

I can define this function as follows:
mapBij :: Bijection (->) a c -> Bijection (->) [a] [b] -> Bijection (->) [a] [c]
mapBij b1 b = (map (fw b1)) `Bij` (map (bw b1))

but do I really need to do it explicitly? Can I obtain same result
using some Category combinators or other common stuff?

Sergey

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


Re: [Haskell-cafe] Compiling Haskell targetting different OS/arch

2012-08-27 Thread Sergey Mironov
ARM guys use native ghc to build arm binaries

2012/8/24 Taylor Hedberg :
> Thiago Negri, Fri 2012-08-24 @ 13:27:32-0300:
>> Is it possible to compile Haskell code targetting a OS/arch that
>> differs from the one where the compiler (GHC) is running?
>
> No, GHC doesn't currently support cross-compilation.
>
> ___
> 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] fclabels > 0.5

2012-08-21 Thread Sergey Mironov
just what I was looking for, thanks!

2012/8/20 Erik Hesselink :
> Untested, but this should be about right:
>
> osi (Bij f b) = iso (Bij b f)
>
> Erik
>
> On Mon, Aug 20, 2012 at 2:35 PM, Sergey Mironov  wrote:
>> Hi. I'm porting old code, which uses fclabels <0.5. Old fclabels
>> define Iso typeclass as follows:
>>
>> class Iso f where
>>   iso :: a :<->: b -> f a -> f b
>>   iso (Lens a b) = osi (b <-> a)
>>   osi :: a :<->: b -> f b -> f a
>>   osi (Lens a b) = iso (b <-> a)
>>
>> Newer one defines iso:
>>
>> class Iso (~>) f where
>>   iso :: Bijection (~>) a b -> f a ~> f b
>>
>> instance Arrow (~>) => Iso (~>) (Lens (~>) f) where
>>   iso bi = arr ((\a -> lens (fw bi . _get a) (_set a . first (bw bi))) . 
>> unLens)
>>
>> instance Arrow (~>) => Iso (~>) (Bijection (~>) a) where
>>   iso = arr . (.)
>>
>> but no osi. I'm not a guru in categories, can you help me define osi?
>>
>> Thanks
>> Sergey.
>>
>> ___
>> 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


[Haskell-cafe] salvia

2012-08-21 Thread Sergey Mironov
Hi. Does anybody know anything about Sebastiaan Visser, the maintainer
of Salvia-* packages (web server) ? Looks like his email is dead.
Sergey

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


[Haskell-cafe] fclabels > 0.5

2012-08-20 Thread Sergey Mironov
Hi. I'm porting old code, which uses fclabels <0.5. Old fclabels
define Iso typeclass as follows:

class Iso f where
  iso :: a :<->: b -> f a -> f b
  iso (Lens a b) = osi (b <-> a)
  osi :: a :<->: b -> f b -> f a
  osi (Lens a b) = iso (b <-> a)

Newer one defines iso:

class Iso (~>) f where
  iso :: Bijection (~>) a b -> f a ~> f b

instance Arrow (~>) => Iso (~>) (Lens (~>) f) where
  iso bi = arr ((\a -> lens (fw bi . _get a) (_set a . first (bw bi))) . unLens)

instance Arrow (~>) => Iso (~>) (Bijection (~>) a) where
  iso = arr . (.)

but no osi. I'm not a guru in categories, can you help me define osi?

Thanks
Sergey.

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


Re: [Haskell-cafe] RoseTree + Data.Typeable.Zipper

2012-01-08 Thread Sergey Mironov
2012/1/8 Sergey Mironov 

> Hi list!
> Could you please give me a quick example of navigating throw
> Data.Typeable.Zipper built on top of a Rose Tree?
> eg. (See ??? in the last line - is my question)
>
> {-#LANGUAGE TemplateHaskell, DeriveDataTypeable, TypeOperators #-}
>
> import Data.Typeable.Zipper
>
> data Tree k a = Tree {
> _rules :: [(k,Tree k a)]
> } deriving(Show, Typeable)
>
> $(mkLabelsNoTypes [''Tree])
>
> atree = Tree [(1, Tree []), (2, Tree []), (3, Tree [(11, Tree [])])]
>
> moveToLeftmostChild :: (Typeable k, Typeable a) =>
> Zipper1 (Tree k a) -> Zipper1 (Tree k a)
> moveToLeftmostChild z = moveTo ??? z
>
> Thanks,
> Sergey
>

Heh, look like I've found the solution by myself! Here is the missing part:

get_child n t = ((_rules t) !! n) -- fast'n'diry
set_child n c t = t{ _rules = (hs ++ (c:ts)) } where
(hs,ts) = splitAt n (_rules t)

focus_child :: Int -> Tree k a :-> (k, Tree k a)
focus_child n = lens (get_child n) (set_child n)

moveToLeftmostChild :: (Ord k, Typeable k, Typeable a)
=> Zipper (Tree k a) (Tree k a) -> Zipper (Tree k a) (k, Tree k a)
moveToLeftmostChild z = moveTo (focus_child 0) z

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


[Haskell-cafe] RoseTree + Data.Typeable.Zipper

2012-01-08 Thread Sergey Mironov
Hi list!
Could you please give me a quick example of navigating throw
Data.Typeable.Zipper built on top of a Rose Tree?
eg. (See ??? in the last line - is my question)

{-#LANGUAGE TemplateHaskell, DeriveDataTypeable, TypeOperators #-}

import Data.Typeable.Zipper

data Tree k a = Tree {
_rules :: [(k,Tree k a)]
} deriving(Show, Typeable)

$(mkLabelsNoTypes [''Tree])

atree = Tree [(1, Tree []), (2, Tree []), (3, Tree [(11, Tree [])])]

moveToLeftmostChild :: (Typeable k, Typeable a) =>
Zipper1 (Tree k a) -> Zipper1 (Tree k a)
moveToLeftmostChild z = moveTo ??? z

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


Re: [Haskell-cafe] [ANNOUNCEMENT] xmobar 0.14

2011-12-11 Thread Sergey Mironov
2011/12/10 Jose A. Ortega Ruiz 

>
> I'm happy to announce the release of xmobar 0.14.
>
> Xmobar is a text-based, minimalistic status bar for linuxy systems,
> written in Haskell.  See http://projects.haskell.org/xmobar for
> details.
>
> Many, many thanks to the many, many contributors, and apologies for
> taking so long to put their code and fixes under a new release.
>
> In this episode:
>
> _New features_
>
>  - New brightness monitor, courtesy of Martin Perner.
>  - New DateZone plugin, for configurable timezone and localized
>datetimes, also by Martin.
>  - New keyboard layout monitor (Kbd).  Yes, by Martin.
>  - Rewrite of the event handling ([issue 53], [issue 57]), you
>guessed it.
>  - Cpu monitor now also reports `iowait` field ([issue 55]).
>  - Battery monitor: the full charge file is now settable in the
>monitor arguments (olpc systems use `charge_full_design`; see
>[issue 62]).
>
> _Bug fixes_
>
>  - [issue 45]: Fix for crashes with AC status changes in battery monitor.
>  - [issue 48]: The  field of Wireless behaves like a percentage.
>  - [issue 50]/[issue 61]: `MPD` monitor now works with libmpd 0.6.
>  - [issue 60]: Fixes for crashes on power resume for battery monitor.
>  - Template sections without fields are now correctly displayed.
>  - Catch errors when reading battery status (Ben Boeckel).
>  - Compilation issues with ghc 7.x (Sergei Trofimovich).
>  - Fixes for CoreTemp monitor in new kernels (Norbert Zeh).
>  - Fix for pulseaudio problems in volume monitor (Martin Perner).
>  - Fix for parsing errors when a `Run` entry ended in an array
>(Martin).
>  - Fixed compilation in OpenBSD (Ivo van der Sangen).
>
> [issue 45]: http://code.google.com/p/xmobar/issues/detail?id=45
> [issue 48]: http://code.google.com/p/xmobar/issues/detail?id=48
> [issue 50]: http://code.google.com/p/xmobar/issues/detail?id=50
> [issue 53]: http://code.google.com/p/xmobar/issues/detail?id=53
> [issue 55]: http://code.google.com/p/xmobar/issues/detail?id=55
> [issue 57]: http://code.google.com/p/xmobar/issues/detail?id=57
> [issue 60]: http://code.google.com/p/xmobar/issues/detail?id=60
> [issue 61]: http://code.google.com/p/xmobar/issues/detail?id=61
> [issue 62]: http://code.google.com/p/xmobar/issues/detail?id=62
>
> Cheers,
> jao
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


Hi. I am Awesome WM user thinking about swithcing to the xmonad. Could I
take an opportunity and ask about mouse support in xmonad/xmobar ?
Actually, I assume that xmobar does nothing with mouse, but what is a
common way of showing something like main menu to the user? Is there an
option of switching windows with mouse by pressing on some window's icon,
just like common DE does?

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


Re: [Haskell-cafe] Programming with arrows, exercises

2011-09-30 Thread Sergey Mironov
2011/9/30 John Lask :
> On 30/09/2011 7:15 AM, Sergey Mironov wrote:
>>
>> Hello. I am reading "Programming with Arrows" by John Hughes (very
>> helpful and interesting!), the book has an exercises requiring a
>> module called Circuits for checking the answer. There should be things
>> like class ArrowCircuit and various functions related to digital logic
>> circuits simulation.  Does anybody know where can I find one?
>>
>> Thanks,
>> Sergey
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>
> This was in the old arrows library I have attached a copy, it will probably
> need modification to compile.
>
> You should be able to use the examples with the current arrows library with
> a few mods.
>

Yes, looks quite old. Unfotinately, it doesn't match the book.. I
found that  module I was looking for is in Appendix! Should I be more
attentive.. Anyway, thank you!

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


[Haskell-cafe] Programming with arrows, exercises

2011-09-29 Thread Sergey Mironov
Hello. I am reading "Programming with Arrows" by John Hughes (very
helpful and interesting!), the book has an exercises requiring a
module called Circuits for checking the answer. There should be things
like class ArrowCircuit and various functions related to digital logic
circuits simulation.  Does anybody know where can I find one?

Thanks,
Sergey

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


Re: [Haskell-cafe] [Haskell] [ANNOUNCE] Haskdogs-0.1

2011-09-17 Thread Sergey Mironov
2011/9/16 Mathijs Kwik :
> Do I need any special .el file to use these?
> Or commandline arguments to use etags format?
>
> Emacs tells me 'visit-tags-table-buffer: File
> /home/mathijs/packages/snap/tags is not a valid tags table'
>

Please try haskdogs-0.3.
  haskdogs -e
should generate TAGS file. I didn't check, but probably it is what
emacs supports.

Sergey

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


Re: [Haskell-cafe] [Haskell] [ANNOUNCE] Haskdogs-0.1

2011-09-15 Thread Sergey Mironov
2011/9/14 Ivan Lazar Miljenovic :
> On 14 September 2011 19:18, Sergey Mironov  wrote:
>>
>> Yes, I forgot to mention PATH. I expect somthing like
>>
>> export PATH="$HOME/.cabal/bin:$PATH"
>>
>> in .bash_profile or similar.
>>
>> Also, I probably should remove hasktags from the build-tools. Better
>> check it's presense in tuntime.
>
> You also seemed to have some hard-coded paths to have it in
> ~/.cabal/var; this assumes that people use cabal-install to install
> your package rather than a system package manager or the like.  Is it
> possible to change that?

Shure. But I still need some directory to store unpacked sources. If
not ~/.cabal/var, then it should be something like ~/.haskdogs/. Exact
path doesn't metter actually. I'll add automatic creation of this dir
and maybe it is good idea to move it to .. heh, one-line long config
file instead of hardcode :)

Thanks,
Sergey.

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


Re: [Haskell-cafe] [Haskell] [ANNOUNCE] Haskdogs-0.1

2011-09-14 Thread Sergey Mironov
2011/9/14 Ivan Lazar Miljenovic :
> Re-cc'ing -cafe:
>
> On 14 September 2011 14:29, yi huang  wrote:
>> On Wed, Sep 14, 2011 at 11:32 AM, Ivan Lazar Miljenovic
>>  wrote:
>>>
>>> On 14 September 2011 13:27, yi huang  wrote:
>>> > On Wed, Sep 14, 2011 at 10:18 AM, Ivan Lazar Miljenovic
>>> >  wrote:
>>> >>
>>> >> On 14 September 2011 11:24, yi huang  wrote:
>>> >> > Cabal compains about "Unknown build tool hasktags".
>>> >> > It seems not necessary to set "Build-tools: hasktags" in cabal file?
>>> >>
>>> >> cabal-install isn't capable of automatically building and installing
>>> >> build-tools for you.  So to install haskdogs, you need to do "cabal
>>> >> install hasktags && cabal install haskdogs".
>>> >
>>> > I have installed hasktags, and .cabal/bin is in my PATH, i can run
>>> > hasktags
>>> > directly from shell.
>>> > What else did i miss?
>>>
>>> How did you specify your PATH?  You can't use ~/.cabal/bin, you need
>>> either $HOME/.cabal/bin or the fully expanded path.
>>
>> It is $HOME/.cabal/bin , and `which hasktags' can find it without problem.
>> Cabal 1.10.2, ghc 7.0.4, i'm trying to look into cabal source to find the
>> problem.
>
> Actually... looks like you're right.  I can't build it either, he
> appears to have hard-coded some paths in and it appears that you need
> some kind of magic to register a program as a build tool (that's what
> the error is from: hasktags isn't a registered build-tool).
>
> --
> Ivan Lazar Miljenovic
> ivan.miljeno...@gmail.com
> IvanMiljenovic.wordpress.com
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

Yes, I forgot to mention PATH. I expect somthing like

export PATH="$HOME/.cabal/bin:$PATH"

in .bash_profile or similar.

Also, I probably should remove hasktags from the build-tools. Better
check it's presense in tuntime.

Thanks a lot,
Sergey

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


[Haskell-cafe] [Haskell] [ANNOUNCE] Haskdogs-0.1

2011-09-13 Thread Sergey Mironov
Hi! I am pleased to announce haskdogs - project-level ctag file generator.

haskdogs is a small shellscript-like tool which creates tag file for
entire haskell project directory. It takes into account first-level
dependencies by recursively scanning imports and adding matching
packages to the final tag list. As a result, programmer can use
his/her text editor supporting tags (vim, for example) to jump
directly to definition of any standard or foreign function he/she
uses. Note, that haskdogs calls some Unix shell commands like test or
mkdir so this tool will likely fail to work on pure Windows platforms.

To use it, do

0) cabal install hasktags haskdogs && mkdir -p ~/.cabal/var/haskdogs
1) cabal unpack TrickyProject-4.2 && cd TrickyProject-4.2
2) haskdogs
3) enjoy the tagfile with references to every function

http://hackage.haskell.org/package/haskdogs-0.1

Sergey

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


[Haskell-cafe] ghc on arm status

2011-07-20 Thread Sergey Mironov
Hi. I was searching for info about building ghc on ARM arch. I already
know about [1] approach, and also saw debian binaries [2], but I am
afraid I have to compile ghc by myself this time, since our system
uses incompatible libc, so my question is addressed to gentoo users
and sympathetic :) Did anybody see any working (currently or in the
past) dev-lang/ghc arm ebuild?

Thanks,
Sergey

[1] - http://hackage.haskell.org/trac/ghc/wiki/ArmLinuxGhc
[2] - http://packages.debian.org/sid/ghc6

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


Re: [Haskell-cafe] [iteratee] empty chunk as special case of input

2011-07-14 Thread Sergey Mironov
2011/7/14 John Lato :
> Sorry for the followup, but I forgot about one other important reason
> (probably the real reason) for the nullC case in bindIteratee.  Note
> what happens in the regular case: the iteratee is run, and if it's in
> a completed state, the result is passed to the bound function (in the
> "m_done" line), which is then also run.  Examine what happens if the
> inner iteratee is also complete:
>
>> const . flip onDone stream
>
> which would be more clearly written as
>
>> \b _str -> onDone b stream
>
> so in this case the leftover stream result from the first iteratee
> (stream) is used as the result of the second iteratee, and the
> leftover stream from the second iteratee (_str) is discarded.

> This doesn't seem right; what should happen is that the two streams
> should be appended somehow.

Yes I see. From this point ov view, the way of ignoring second
iteratee's leftover stream is neither worse or better comparing to
other possible ways, like ignoring stream of first iteratee or
appending them together somehow. I thought about it, and now it seems
that all this problem exists because of iteratee's possibility to jump
into done state without processing any data.

I came to iteratees from IncrementalGet library (binary-strict
package), and thought that they are using similar concepts, but now I
see big difference - IncrementalGet's approach doesn't allow such
state change. That is how they define /Get/ (iteratee-like structure).

newtype Get r a = Get { unGet :: S -> (a -> S -> IResult r) -> IResult r }

data IResult a = IFailed S String
   | IFinished S a
   | IPartial (B.ByteString -> IResult a)

data S = S ...  -- contains data chunk (bytestring) and some other state holders

unGet has similar design in onDone branch, but onCont is hidden inside
IResult. So, user can't obtain the result without providing a stream
as input. Well, there is also black magic there..  but I think It
makes impossible to have two conflicting iteratees like bindIteratee
may discover.

I would like to compare  those approaches and decide what is "better"
(it depends on task of course, but how?).. binary-strict's code is
easier to understand, but iteratees are more general and offer more
features, including very powerfull stream transformations. Is it good
idea to merge somehow those approaces? For example, if I'll replace
IncrementalGet's hardcoded stream type with type variable like
iterarees do, will I be able to implement convStream on top of Get,
how do you think? What about enumeratees?

By the way, Iteratee package contains itertut.lhs - very good
tutorial, thanks! It says that CPS was used to eliminate constructors.
How do yo think, may I hope that one day compiler will be able to
transform constructor-based approach, introduced there, into CPS
automatically?

Thanks,
Sergey

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


[Haskell-cafe] [iteratee] empty chunk as special case of input

2011-07-13 Thread Sergey Mironov
Hi community, hi John. I find myself reading bindIteratee[1] function
for a several days.. there is something that keeps me away from
completely understanding of the concept. The most noticeble thing is
\nullC\ guard in the definition. To demonstate the consequences of
this solution, let me define an iterator like

myI = Iteratee $ \onDone _ -> onDone 'a' (Chunk "xyz")

It is a bit unusial, since myI substitutes real stream with a fake one
(xyz). Now lets define two actions producing different results in
unusual manner:

printI i = enumPure1Chunk ['a'..'g'] i >>= run >>= print

i1 = (return 'b' >> myI >> I.head)  -- myI substitutes the stream,
last /I.head/ produces 'x', OK
i2 = (I.head >> myI >> I.head) -- produces 'b'!  I expected another
'x' here but myI's stream was ignored by >>=

Well, I understand that this is probably an expected behaviour, but
what is it for? Why we can't handle null input like non-null? Iterator
may just stay in it's current state in that case.

Thanks in advance
Sergey

--
[1] - bindIteratee (basically, >>=) code from Data.Iteratee.Base.hs

bindIteratee :: (Monad m, Nullable s)
=> Iteratee s m a
-> (a -> Iteratee s m b)
-> Iteratee s m b
bindIteratee = self
where
self m f = Iteratee $ \onDone onCont ->
 let m_done a (Chunk s)
   | nullC s  = runIter (f a) onDone onCont
 m_done a stream = runIter (f a) (const . flip onDone
stream) f_cont
   where f_cont k Nothing = runIter (k stream) onDone onCont
 f_cont k e   = onCont k e
 in runIter m m_done (onCont . (flip self f .))

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


[Haskell-cafe] Fwd: [iteratee] how to do nothing .. properly

2011-06-15 Thread Sergey Mironov
Forgot reply to all

-- Forwarded message --
From: Sergey Mironov 
Date: 2011/6/16
Subject: Re: [Haskell-cafe] [iteratee] how to do nothing .. properly
To: John Lato 


Thanks for explanations! /ErrorT String (Iteratee s m) a/ definitely
does the work. But wrapping Enumeratee is harder since /ErrorT String
(Enumeratee s s' m) a/ doesn't compiles. Maybe most users actually
don't need to wrap Enumeratee, will check it. Heh, throwRecoverableErr
name tells me "use me, I am all you need":) Well, one just need to
grok the interface.. Anyway, iteratees are much deeper and powerful
than I expected when switched to it from Data.Binary. I'll better open
new threads for asking more questions.

Again thanks,
Sergey

PS
sorry for delayed answer, had vacation without email access

2011/6/5 John Lato :
> Yes, this is expected.  'throwErr' is only meant to be used when the error
> should be non-recoverable, and the stream would often be invalid then, so
> throwErr doesn't take any steps to preserve it.  You could retain the rest
> of the stream with getChunk and use throwRecoverableErr though.
>
> Wrapping an iteratee with ErrorT is fine, and I use this approach often.  I
> typically would use an explicit Either rather than ErrorT, but the two
> approaches are exactly the same.
>
> Note that wrapping the other way, Iteratee s (ErrorT e m), can sometimes
> cause problems, and is best avoided unless you really know what you're
> doing.  This may change in a future release.
>
> John
>
> On Thu, Jun 2, 2011 at 4:27 PM, Sergey Mironov  wrote:
>>
>> I am glad to help! Looks like upgrading to 0.8.5.0 also fixes initial
>> problem that involved me into testing!
>>
>> I'll take the opportunity and ask another thing about iteratee: Is it
>> expected behavior that throwErr consumes all data in current chunk? I
>> wish it to stop in place and let after-checkErr code to continue the
>> parsing. Well, I already found solution (or workaround?) - I wrap
>> Iteratee with ErrorT monad and use ErrorT's raiseError instead of
>> throwErr. Is it correct?
>>
>> Here is example code
>>
>> instance Exception Int
>>
>> iter4 = do
>>    I.dropWhile (/= 3)
>>    h<-I.head
>>    throwErr $ toException $ (-4::Int)  -- doesn't meter what exactly to
>> throw
>>    return h
>>
>> -- catch the error with checkErr
>> iter5 = do
>>    (_,b)<-countBytes $ I.checkErr $ iter4
>>    s <- I.stream2list
>>    return (b,s)
>>
>> print5 = enumPure1Chunk [1..10] (iter5) >>= run >>= print
>>
>>
>> Thanks a lot!
>> Sergey
>>
>> 2011/6/2 John Lato :
>> > Hi Sergey,
>> >
>> > I've got an explanation; quite surprisingly it's a bug in
>> > enumPure1Chunk.
>> > Even though it is an odd case, I'm surprised that it hasn't come up
>> > before
>> > now since enumPure1Chunk appears frequently.
>> >
>> > I've just uploaded 0.8.5.0 which has the fix.  There's now an additional
>> > Monoid constraint on enumPure1Chunk, unfortunately.
>> >
>> > Thanks very much for reporting this.
>> >
>> > John L
>> >
>> > On Thu, Jun 2, 2011 at 10:02 AM, Sergey Mironov 
>> > wrote:
>> >>
>> >> Ok. I've checked iteratee-0.8.3.0 and 0.8.4.0. Results are same.
>> >>
>> >> Sergey
>> >>
>> >> 2011/6/2 John Lato :
>> >> > Hi Sergey,
>> >> > I can't explain this; maybe it's a bug in enumWith?  I'll look into
>> >> > it.
>> >> > Thanks,
>> >> > John
>> >> >
>> >> >>
>> >> >> Message: 20
>> >> >>
>> >> >> Date: Thu, 2 Jun 2011 02:46:32 +0400
>> >> >> From: Sergey Mironov 
>> >> >> Subject: [Haskell-cafe] [iteratee] how to do nothing .. properly
>> >> >> To: haskell-cafe@haskell.org
>> >> >> Message-ID: 
>> >> >> Content-Type: text/plain; charset=ISO-8859-1
>> >> >>
>> >> >> Hi. Would anybody explain a situation with iter6 and iter7 below?
>> >> >> Strange thing - first one consumes no intput, while second consumes
>> >> >> it
>> >> >> all, while all the difference is peek  which should do no processing
>> >> >> (just copy next item in stream and return to user).
>> >> >> What I am trying to do - is to write

Re: [Haskell-cafe] [iteratee] how to do nothing .. properly

2011-06-02 Thread Sergey Mironov
I am glad to help! Looks like upgrading to 0.8.5.0 also fixes initial
problem that involved me into testing!

I'll take the opportunity and ask another thing about iteratee: Is it
expected behavior that throwErr consumes all data in current chunk? I
wish it to stop in place and let after-checkErr code to continue the
parsing. Well, I already found solution (or workaround?) - I wrap
Iteratee with ErrorT monad and use ErrorT's raiseError instead of
throwErr. Is it correct?

Here is example code

instance Exception Int

iter4 = do
I.dropWhile (/= 3)
h<-I.head
throwErr $ toException $ (-4::Int)  -- doesn't meter what exactly to throw
return h

-- catch the error with checkErr
iter5 = do
(_,b)<-countBytes $ I.checkErr $ iter4
s <- I.stream2list
return (b,s)

print5 = enumPure1Chunk [1..10] (iter5) >>= run >>= print


Thanks a lot!
Sergey

2011/6/2 John Lato :
> Hi Sergey,
>
> I've got an explanation; quite surprisingly it's a bug in enumPure1Chunk.
> Even though it is an odd case, I'm surprised that it hasn't come up before
> now since enumPure1Chunk appears frequently.
>
> I've just uploaded 0.8.5.0 which has the fix.  There's now an additional
> Monoid constraint on enumPure1Chunk, unfortunately.
>
> Thanks very much for reporting this.
>
> John L
>
> On Thu, Jun 2, 2011 at 10:02 AM, Sergey Mironov  wrote:
>>
>> Ok. I've checked iteratee-0.8.3.0 and 0.8.4.0. Results are same.
>>
>> Sergey
>>
>> 2011/6/2 John Lato :
>> > Hi Sergey,
>> > I can't explain this; maybe it's a bug in enumWith?  I'll look into it.
>> > Thanks,
>> > John
>> >
>> >>
>> >> Message: 20
>> >>
>> >> Date: Thu, 2 Jun 2011 02:46:32 +0400
>> >> From: Sergey Mironov 
>> >> Subject: [Haskell-cafe] [iteratee] how to do nothing .. properly
>> >> To: haskell-cafe@haskell.org
>> >> Message-ID: 
>> >> Content-Type: text/plain; charset=ISO-8859-1
>> >>
>> >> Hi. Would anybody explain a situation with iter6 and iter7 below?
>> >> Strange thing - first one consumes no intput, while second consumes it
>> >> all, while all the difference is peek  which should do no processing
>> >> (just copy next item in stream and return to user).
>> >> What I am trying to do - is to write an iteratee consuing no input,
>> >> but returning a constant I give to it. I thought (return a) should do
>> >> it, but it seems I was wrong as return actually consumes all unparsed
>> >> stream. iter6 experience tells me that (peek>>return a) is what I
>> >> need, but it's completely confusing and not what I expected.
>> >>
>> >> Thanks,
>> >> Sergey
>> >>
>> >>  import Data.Iteratee as I
>> >>  import Data.Iteratee.IO
>> >>  import Control.Monad
>> >>  import Control.Exception
>> >>  import Data.ByteString
>> >>  import Data.Char
>> >>  import Data.String
>> >>
>> >>  -- countBytes :: (..., Num b) => Iteratee s m a -> Iteratee s m (a, b)
>> >>  countBytes i = enumWith i I.length
>> >>
>> >>  iter6 = do
>> >>     h <- countBytes $ (peek >> return 0)
>> >>     s <- I.stream2list
>> >>     return (h,s)
>> >>
>> >>  iter7 = do
>> >>     h <- countBytes $ (return 0)
>> >>     s <- I.stream2list
>> >>     return (h,s)
>> >>
>> >>  print6 = enumPure1Chunk [1..10] (iter6) >>= run >>= print
>> >>  print7 = enumPure1Chunk [1..10] (iter7) >>= run >>= print
>> >>
>> >>
>> >> Here is example ghci session
>> >>
>> >> *Main> print6
>> >> ((0,0),[1,2,3,4,5,6,7,8,9,10])
>> >> -- read 0 items, returns 0
>> >> *Main> print7
>> >> ((0,10),[])
>> >> -- read 10 items (???) returns 0
>> >> *Main>
>> >>
>> >>
>> >>
>> >> --
>> >>
>> >> ___
>> >> Haskell-Cafe mailing list
>> >> Haskell-Cafe@haskell.org
>> >> http://www.haskell.org/mailman/listinfo/haskell-cafe
>> >>
>> >>
>> >> End of Haskell-Cafe Digest, Vol 94, Issue 3
>> >> ***
>> >
>> >
>
>

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


Re: [Haskell-cafe] [iteratee] how to do nothing .. properly

2011-06-02 Thread Sergey Mironov
Ok. I've checked iteratee-0.8.3.0 and 0.8.4.0. Results are same.

Sergey

2011/6/2 John Lato :
> Hi Sergey,
> I can't explain this; maybe it's a bug in enumWith?  I'll look into it.
> Thanks,
> John
>
>>
>> Message: 20
>>
>> Date: Thu, 2 Jun 2011 02:46:32 +0400
>> From: Sergey Mironov 
>> Subject: [Haskell-cafe] [iteratee] how to do nothing .. properly
>> To: haskell-cafe@haskell.org
>> Message-ID: 
>> Content-Type: text/plain; charset=ISO-8859-1
>>
>> Hi. Would anybody explain a situation with iter6 and iter7 below?
>> Strange thing - first one consumes no intput, while second consumes it
>> all, while all the difference is peek  which should do no processing
>> (just copy next item in stream and return to user).
>> What I am trying to do - is to write an iteratee consuing no input,
>> but returning a constant I give to it. I thought (return a) should do
>> it, but it seems I was wrong as return actually consumes all unparsed
>> stream. iter6 experience tells me that (peek>>return a) is what I
>> need, but it's completely confusing and not what I expected.
>>
>> Thanks,
>> Sergey
>>
>>  import Data.Iteratee as I
>>  import Data.Iteratee.IO
>>  import Control.Monad
>>  import Control.Exception
>>  import Data.ByteString
>>  import Data.Char
>>  import Data.String
>>
>>  -- countBytes :: (..., Num b) => Iteratee s m a -> Iteratee s m (a, b)
>>  countBytes i = enumWith i I.length
>>
>>  iter6 = do
>>     h <- countBytes $ (peek >> return 0)
>>     s <- I.stream2list
>>     return (h,s)
>>
>>  iter7 = do
>>     h <- countBytes $ (return 0)
>>     s <- I.stream2list
>>     return (h,s)
>>
>>  print6 = enumPure1Chunk [1..10] (iter6) >>= run >>= print
>>  print7 = enumPure1Chunk [1..10] (iter7) >>= run >>= print
>>
>>
>> Here is example ghci session
>>
>> *Main> print6
>> ((0,0),[1,2,3,4,5,6,7,8,9,10])
>> -- read 0 items, returns 0
>> *Main> print7
>> ((0,10),[])
>> -- read 10 items (???) returns 0
>> *Main>
>>
>>
>>
>> --
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>> End of Haskell-Cafe Digest, Vol 94, Issue 3
>> ***
>
>

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


[Haskell-cafe] [iteratee] how to do nothing .. properly

2011-06-01 Thread Sergey Mironov
Hi. Would anybody explain a situation with iter6 and iter7 below?
Strange thing - first one consumes no intput, while second consumes it
all, while all the difference is peek  which should do no processing
(just copy next item in stream and return to user).
What I am trying to do - is to write an iteratee consuing no input,
but returning a constant I give to it. I thought (return a) should do
it, but it seems I was wrong as return actually consumes all unparsed
stream. iter6 experience tells me that (peek>>return a) is what I
need, but it's completely confusing and not what I expected.

Thanks,
Sergey

 import Data.Iteratee as I
 import Data.Iteratee.IO
 import Control.Monad
 import Control.Exception
 import Data.ByteString
 import Data.Char
 import Data.String

 -- countBytes :: (..., Num b) => Iteratee s m a -> Iteratee s m (a, b)
 countBytes i = enumWith i I.length

 iter6 = do
 h <- countBytes $ (peek >> return 0)
 s <- I.stream2list
 return (h,s)

 iter7 = do
 h <- countBytes $ (return 0)
 s <- I.stream2list
 return (h,s)

 print6 = enumPure1Chunk [1..10] (iter6) >>= run >>= print
 print7 = enumPure1Chunk [1..10] (iter7) >>= run >>= print


Here is example ghci session

*Main> print6
((0,0),[1,2,3,4,5,6,7,8,9,10])
-- read 0 items, returns 0
*Main> print7
((0,10),[])
-- read 10 items (???) returns 0
*Main>

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


Re: [Haskell-cafe] generic putback

2011-05-17 Thread Sergey Mironov
Thanks for your answers! I looked further and found that 'Oleg alredy
did it'. Really, looks like iteratees will suit my needs :) I'm sorry
for bothering.

Sergey

2011/5/15 Daniel Gorín :
> I think you need to change the type of putback slightly:
>
> import Data.IORef
>
> putback :: a -> IO a -> IO (IO a)
> putback a action =
>   do next <- newIORef a
>      return (do r <- readIORef next; writeIORef next =<< action; return r)
>
> main =
>   do getChar' <- putback 'a' getChar
>      str <- sequence $ take 10 $ repeat getChar'
>      putStrLn str
>
> Thanks,
> Daniel
>
> On May 15, 2011, at 4:33 PM, Sergey Mironov wrote:
>
>> Hi Cafe. I wonder if it is possible to write a IO putback function
>> with following interface
>>
>> putback :: a -> IO a -> IO a
>> putback x io = ???
>>
>>
>> where io is some action like reading from file or socket.
>> I want putback to build new action which will return x on first call,
>> and continue executing io after that.
>>
>> Thanks in advance!
>> Sergey.
>>
>> ___
>> 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


[Haskell-cafe] generic putback

2011-05-15 Thread Sergey Mironov
Hi Cafe. I wonder if it is possible to write a IO putback function
with following interface

putback :: a -> IO a -> IO a
putback x io = ???


where io is some action like reading from file or socket.
I want putback to build new action which will return x on first call,
and continue executing io after that.

Thanks in advance!
Sergey.

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


[Haskell-cafe] Data.Binary.IncrementalGet remake

2011-04-20 Thread Sergey Mironov
Hello cafe.

Haskell wiki told me about continuation-based parser
Data.Binary.IncrementalGet [1] from binary-strict package. I found the
idea very useful and tried to use it. Original library by Lennart
Kolmodin raises some questions. The lib's main data structures are:

data IResult a = IFailed S String
   | IFinished S a
   | IPartial (B.ByteString -> IResult a)

newtype Get r a = Get { unGet :: S -> (a -> S -> IResult r) -> IResult r }

instance Monad (Get r) where
  return a = Get (\s -> \k -> k a s)
  m >>= k = Get (\s -> \cont -> unGet m s (\a -> \s' -> unGet (k a) s' cont))
  fail err = Get (\s -> const $ IFailed s err)

Here, "S" is parser's state. It works well, but currently doesn't
support lookAhead. I tried to add such function and gave up to do it
having current implementation, but write simpler one instead. Please
see IncrementalGet2.hs (link [2] below). Remake is briefly tested, has
no ghc-specific optimizations, but allows user to peek data from
stream.

What bothering me is the fact that I could actually miss idea (or part
of idea) of the original. If it is so, please let me know :) For
example, what is the point of using separate result type r in original
Get r a?

[1] - Original IncrementalGet lib.
http://www.haskell.org/haskellwiki/DealingWithBinaryData#Incremental_parsing
[2] - Main file of remake

https://github.com/ierton/binary-incremental-get2/blob/a9f9afaa0cbc0435a8acea338a31aafaef53fb6e/src/Data/Binary/IncrementalGet2.hs
[3] - whole github project
https://github.com/ierton/binary-incremental-get2
--
Sergey

sorry for weak English

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


Re: [Haskell-cafe] ADT patch/update

2010-08-12 Thread Sergey Mironov
2010/8/8 Stephen Tetley :
> Maybe this paper is close?
>
> Type-safe diff for families of datatypes
> Eelco Lempsink Sean Leather Andres Löh
>

Thanks a lot! Just what I need.. and more trickier than I thought.
They represent any ADT as a tree and use diff algorithm for trees to
build 'EditScripts' - list of operations to transform src data to dest
one.

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


[Haskell-cafe] ADT patch/update

2010-08-07 Thread Sergey Mironov
Hi Cafe. I am searching for materials on one data type-related problem.
Suppose we have version control system storing values of user-defined algebraic
data type. 'User' (actually, programmer) wants to store his/her data and later
update it by applying patches.

By patch I mean value of some (another) type representing one simplest update
of stored value.

Say, for tree type

> data Tree a = Node (Tree a) (Tree a) | Leaf a

one may write

> {-# LANGUAGE TypeFamilies #-}
> {-# LANGUAGE UndecidableInstances #-}
>
> class Storable a where
> type Patch a :: *
> update :: Patch a -> a -> a
>
> data TreeStep = Left | Right -- Like in zippers ?
> type family Location a :: *
> type instance Location (Tree a) = [TreeStep]
>
> instance (Storable a) => Storable (Tree a) where
> type Patch (Tree a) = (Location (Tree a), Patch a)
> update = ... -- Move to specific location and call node's update

Patch here is coded explicitly but I guess there may be some generic way of it
to calculate. Whether any similar work has been carried out?
Will be glad to read comments!

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


Re: [Haskell-cafe] trees and pointers

2010-07-15 Thread Sergey Mironov
15 июля 2010 г. 2:01 пользователь Victor Gorokhov  написал:
> You can implement pure pointers on top of Data.Map with O(log n) time:
>
> {-# LANGUAGE ExistentialQuantification #-}
> import Data.Map ( Map )
> import qualified Data.Map as Map
> import Data.Typeable
> import Control.Monad.State
> import Data.Maybe
>
> type PointerSpace = Map Int PackedValue
> newtype Pointer a = Pointer Int
> data PackedValue = forall a. Typeable a => PackedValue a
>
> readPointer :: Pointer a -> State PointerSpace a
> readPointer ( Pointer key ) =  do
>  space <- get
>  return $ fromJust $ cast $ Map.find key space
>
> writePointer :: a -> Pointer a -> State PointerSpace ()
> writePointer a ( Pointer key ) = do
>  space <- get
>  put $ Map.insert key ( PackedValue a ) space
>
> newPointer :: a -> State PointerSpace ( Pointer a )
> newPointer a = do
>  space <- get
>  let key = findEmptyKey space -- implement it yourself
>     p = Pointer key
>  writePointer a p
>  return p

Thanks for an example! Probably, one can think about using Arrays
instead of Map or IntMap in order to achieve 'true' O(1) in pure. But
I suppose that there are some trouble with array expanding. Or
somebody would already make it.

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


Re: [Haskell-cafe] trees and pointers

2010-07-15 Thread Sergey Mironov
2010/7/15 Serguey Zefirov :
> 2010/7/14 Sergey Mironov :
>> Hi cafe! I have a question of C-to-Haskell type:)
>>
>> Imagine web application wich allows users to browse some shared
>> filesystem located at the server.
>> Application stores every users's position within that filesystem
>> (current directory or file).
>>
>> In C this can be implemented with the help of following data types:
>>
>> Any ideas?
>
> Use IORef. ;)
>
> PS
> MVar is better, actually.
>

Somehow I forgot about them:) Code will turn into something like

data TreeNodeData = File | Dir (IORef TreeNode)
data TreeNode = TreeNode {
next :: Maybe (IORef TreeNode),
prev :: Maybe (IORef TreeNode),
up :: Maybe (IORef TreeNode), -- missed it in original C example
payload :: TreeNodeData
}

data User = User {
position :: IORef TreeNode,
-- ...
}

It really should work! (we don't take multithreading issues into
account for now)
Slightly annoying thing is that 1-to-1 mapping from C to Haskell also
forces programmer to perform C-like low-level pointer linking.

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


[Haskell-cafe] trees and pointers

2010-07-14 Thread Sergey Mironov
Hi cafe! I have a question of C-to-Haskell type:)

Imagine web application wich allows users to browse some shared
filesystem located at the server.
Application stores every users's position within that filesystem
(current directory or file).

In C this can be implemented with the help of following data types:

struct tree_node {
union item {
// some file data
struct file *file;

// struct dir has link to another list of tree_node
struct dir *dir;
};
int type;

// List of tree_nodes
struct tree_node *next;
struct tree_node *prev;
};

struct user {
struct tree_node *position;

// List of users
struct user *next;
struct user *prev;
};

This implementation will give us
1) O(1) time to insert to shared tree
2) O(1) time to access user's current position

Is it possible to reach this requirements in haskell?

For example, managing distinct tree type like

data TreeNode = File | Dir [TreeNode]

will lead to failure of req. 2 (have to traverse this
tree to find each user's position).

Also one could manage several zipper types (one for every user):

data TreeNodeCtx = Top | TreeNodeCtx {
left :: [TreeNode],
right :: [TreeNode],
up :: TreeNodeCtx
}

data TreeNodeZ = TreeNodeZ {
ctx :: [TreeNodeCtx]
pos :: TreeNode
}

It works for one user but not for many because of req. 1 (have to
insert new item into
several zippers).

Any ideas?

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


Re: [Haskell-cafe] Re: Finding zipper for custom tree

2010-07-13 Thread Sergey Mironov
2010/7/2 Heinrich Apfelmus :
> Sergey Mironov wrote:
>>
>> Hello list!
>> I am trying to understand zipper concept using papers like [1] and [2].
>> Though main idea looks clear, I still have a problem in applying it for
>> custom data types.
>>
>> Please help me with deriving Zipper-type from
>>
>>> data DTree a = P | D [(a, DTree)]
>>
>> Looking in [1] ('Zippers via Differentiation' chapter) I tried to do
>> the following:
>>
>> 1. Find a DTreeF type which is a pattern functor ([2], chapter 2.1) of my
>> DTree
>> 2. Write DTreeF in 'algebraic' form (using '+' and '*')
>> 3. Find DTreeF' - "derivative" of DTreeF
>> 4. Define my zipper type using list of DTreeF'
>
> These are the right steps.
>
>> Step 1 likely ends with
>>
>>> data DTreeF a x = P | D [(a,x)]
>>
>> [2] says that using this pattern functor one could build a fixed-point
>> version of DTree:
>>
>>> data Fix f = In {out :: (f (Fix f))}
>>> data DTreeFP = Fix DTreeF
>>
>> but seems that I have nothing to do with it right now.
>
> The fixed point is just another way to write  DTree .
>
>    DTreeFP a = DTree a
>
>> Step 2 is my main question:
>>
>> In [1] authors did it for binary tree:
>>
>> data Tree a = Leaf a | Bin (Tree a) (Tree a)
>>
>> data TreeF a x = Leaf a | Bin x x
>>
>> and thus
>>
>> TreeF = a + x * x
>>
>> TreeF' = x + x
>>
>> My DTree has inner list of tuples. How should I rewrite it in terms of
>> '+' and '*' ?
>
> Ah, you can't write it in terms of only '+' and '*' because you also have
> the list type in there:
>
>    DTreeF = 1 + List (a * x)
>                 ^^ List involves a fixed point
>
> So, to find the derivate, you have to calculate the derivative of  List
>  first:
>
>    List' x = List x * List x
>
> and then you can use the chain rule to find  DTreeF .
>
>
> Regards,
> Heinrich Apfelmus
>
> --
> http://apfelmus.nfshost.com
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

Sorry for late answer. Luke, Heinrich - thank you very much for explanations.
I feel that I need more reading to get familiar with differentiation
of functors and chain rule. Could you suggest some books or papers?

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


[Haskell-cafe] Finding zipper for custom tree

2010-07-01 Thread Sergey Mironov
Hello list!
I am trying to understand zipper concept using papers like [1] and [2].
Though main idea looks clear, I still have a problem in applying it for
custom data types.

Please help me with deriving Zipper-type from

> data DTree a = P | D [(a, DTree)]

Looking in [1] ('Zippers via Differentiation' chapter) I tried to do
the following:

1. Find a DTreeF type which is a pattern functor ([2], chapter 2.1) of my DTree
2. Write DTreeF in 'algebraic' form (using '+' and '*')
3. Find DTreeF' - "derivative" of DTreeF
4. Define my zipper type using list of DTreeF'

Step 1 likely ends with

> data DTreeF a x = P | D [(a,x)]

[2] says that using this pattern functor one could build a fixed-point
version of DTree:

> data Fix f = In {out :: (f (Fix f))}
> data DTreeFP = Fix DTreeF

but seems that I have nothing to do with it right now.

Step 2 is my main question:

In [1] authors did it for binary tree:

data Tree a = Leaf a | Bin (Tree a) (Tree a)

data TreeF a x = Leaf a | Bin x x

and thus

TreeF = a + x * x

TreeF' = x + x

My DTree has inner list of tuples. How should I rewrite it in terms of
'+' and '*' ?

Any comments are welcome!

[1] - http://en.wikibooks.org/wiki/Haskell/Zippers
[2] - http://people.cs.uu.nl/andres/Rec/MutualRec.pdf

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