[Haskell-cafe] Opaque types vs automated instance deriving

2011-06-20 Thread Alexey Karakulov
Hi all,
I encountered a problem when trying to

 derive makeBinary ''DiffTime

with help of *derive* package. The error was:

Not in scope: data constructor `MkDiffTime'

Which makes a sense, since it's not exported in Data.Time.Clock.
I bypassed the problem (yes, I'm too lazy to write instances by hands) with

 instance Binary UTCTime where
  put =
putGeneric
  get =
getGeneric

But it must be less efficient (and more verbose) than compile-time deriving.
If there was such a module like Data.Time.Clock.Internal, I could import it
to get hidden constructors (and maybe I'll have to fork the library for this
purpose).

OTOH, is it possible to change the derive TH function so it can bypass
module encapsulation mechanism and access un-exported things?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell question

2011-04-17 Thread Alexey Karakulov
I'm interested if it's possible to use functions from some module without
explicitly importing it. In ghci it's done on the fly, like this:

Prelude Data.Map.empty
Loading package array-0.3.0.2 ... linking ... done.
Loading package containers-0.4.0.0 ... linking ... done.
fromList []

But without gchi it seems impossible.

I have the file Test.hs:

 {-# LANGUAGE TemplateHaskell #-}
 module Test where
 import Language.Haskell.TH

 x :: ExpQ
 x = global $ mkName Data.Map.empty

When I load it in ghci, all works:

$ ghci -XTemplateHaskell Test.hs
*Test $x
Loading package pretty-1.0.1.2 ... linking ... done.
Loading package array-0.3.0.2 ... linking ... done.
Loading package containers-0.4.0.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
fromList []

But when I try to use it from other module, it fails. File Main.hs:

 {-# LANGUAGE TemplateHaskell #-}
 module Main where
 import Test

 main = do
   print $x

$ runhaskell Main.hs

Main.hs:5:9:
Not in scope: `Data.Map.empty'
In the result of the splice:
  $x
To see what the splice expanded to, use -ddump-splices
In the first argument of `print', namely `$x'
In the expression: print ($x)

--
All the best,
Alexey

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


[Haskell-cafe] IO-oriented cache library for interacting with GUI

2010-09-16 Thread Alexey Karakulov
Hi. I'm writing GUI (gtk) program which purpose is take some data as user
input, perform some evaluations, and produce some plots and coefficients.
Since some evaluations take significant time (about 10 seconds), I try to
cache results. The problem is that dependency structure is quite
complicated, something like this:

   a* - x, b*
   x - c
   x, b* - d

where
  α - β means that β depends on α
  values designated by *a*,*b*,*c*,*d* can be showed to user by request, and
*x* is internal value
  values designated by letters with asterisk (*a**,*b**) can be edited by
user

Consider *x*. I have two values:
xCache :: IORef X
xUpToDate :: IORef Bool

Initial state is:
xCache - newIORef undefined
xUpToDate - newIORef False

Since *x* is evaluated once, I do
xCache `writeIORef` x
xUpToDate `writeIORef` True

When user changes the value of *a *and saves it, all dependent on *a *values
cache is expired:
xUpToDate `writeIORef` False
(recursively do it with all cache depends on *x*)

When it comes to handling all *a,b,c,d,x *dependencies the code becomes a
mess. I now have something like

import Data.Functor
import Data.IORef
import Control.Monad

data Mutable a = Mutable { ref :: IORef a, onChange :: IO () }

change :: Mutable a - a - IO ()
change Mutable {..} a = ref `writeIORef` a  onChange

data Cache a b = Cache { fn :: a - b, arg :: IORef a, cached :: IORef
b, upToDate :: IORef Bool }

expire :: Cache a b - IO ()
expire Cache {..} = upToDate `writeIORef` False

update :: Cache a b - IO ()
update Cache {..} = do
   utd - readIORef upToDate
   unless utd $ writeIORef cached = fn $ readIORef arg

test = do
  aRef - newIORef undefined
  xRef - newIORef undefined
  xCache - Cache (^2) aRef xRef $ newIORef False
  let aMut = Mutable aRef (expire xCache)
  aMut `change` 1
  update xCache
  print = readIORef xRef -- 1
  aMut `change` 2
  print = readIORef xRef -- still 1
  update xCache
  print = readIORef xRef -- now 4

I'd like to know if there is some library that could help me.

(Sorry for my English)
--
All the best,
Alexey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Removing polymorphism from type classes (viz. Functor) (Again)

2010-08-15 Thread Alexey Karakulov
On Sun, Aug 15, 2010 at 10:50 AM, Ivan Lazar Miljenovic 
ivan.miljeno...@gmail.com wrote:

Yeah, I'm working on something like this at the moment, but I'm
 currently stuck on naming: if I want to have Functor for kind * - *,
 what's a good name for a type class for kind *?


I was thinking about EtaFunctor, which stands for η-expanded Functor. But
I'm not sure about η-expansion is correct term for removing polymorphism
from the type class.

Also, is there any type for which having a map a - a _doesn't_ make
 sense?  Bloomfilters maybe?


Not the answer, but there are cases where having a map (a - b) - f - g
could make some new sense:

data BitList = ...
fromBoolList :: [Bool] - BitList
type instance NewPt [a] b = [b]
type instance NewPt [a] Bool = BitList

But this kind of overlapping type instance is not allowed in ghc (yet?)

-- 
All the best,
Alexey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Removing polymorphism from type classes (viz. Functor) (Again)

2010-08-14 Thread Alexey Karakulov
I was inspired by George Pollard's
posthttp://www.haskell.org/pipermail/haskell-cafe/2009-July/063981.htmlat
haskell-cafe and tried to implement the non-polymorphic Functor class
( I
named it Functor' ). I changed some names and added reasonable constraints.

type family NewPt f a
class Functor' f where
type Point f
map ∷ (a ~ Point f, b ~ Point g, g ~ NewPt f b, Functor' g) ⇒ (a →
b) → f → g

I would like to be able to write:

type OldPt f = NewPt f (Point f)
class (f ~ OldPt f) ⇒ Functor' f ...

but ghc says it's not implemented yet (version 6.12.1). However, it's not
the main problem.

Now I can write some instances:

type instance NewPt [a] b = [b]
instance Functor' [a] where
  type Point [a] = a
  map = fmap

type instance NewPt ByteString a = ByteString
instance Functor' ByteString where
  type Point ByteString = Word8
  map = BS.map

But I can't write instance for Set:

type instance NewPt (Set a) b = Set b
instance Ord a ⇒ Functor' (Set a) where
  type Point (Set a) = a
  map = Set.map

ghci  complains: Could not deduce (Ord a1) from the context (g ~ NewPt (Set
a) a1, a1 ~ Point g, Functor' g)
  arising from a use of `Set.map' at ...

The type of Set.map is

Set.map :: (Ord a, Ord b) = (a - b) - Set a - Set b

(Ord a) is in the instance context, and what about b? Type of map for Set
instance would be:

original:
map ∷ (a ~ Point f, b ~ Point g, g ~ NewPt f b, Functor' g) ⇒ (a → b) →
f → g

substitute: f → Set a, g → Set b
map :: Functor' (Set b) ⇒ (a →b) →Set a →Set b

(Ord b) must be deduced from (Functor (Set b)) but it doesn't. I don't know
whether it's my mistake somewhere or ghc problem.

(Sorry for my English, it's not perfect).
-- 
All the best,
Alexey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Removing polymorphism from type classes (viz. Functor) (Again)

2010-08-14 Thread Alexey Karakulov
On Sat, Aug 14, 2010 at 2:27 PM, Ivan Lazar Miljenovic 
ivan.miljeno...@gmail.com wrote:

 Alexey Karakulov ankaraku...@gmail.com writes:


  (Ord b) must be deduced from (Functor (Set b)) but it doesn't. I don't
 know
  whether it's my mistake somewhere or ghc problem.

 I've come across this problem as well; the best solution I've seen so
 far is the one taken by Ganesh in his rmonad library:
 http://hackage.haskell.org/package/rmonad

 --
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 IvanMiljenovic.wordpress.com


Thanks for the link, but RFunctor typeclass is still (more or less)
polymorphic, so I couldn't write ByteString instance for it. (Really I don't
care about ByteString, but it's good example). However, I could try to use
Suitable+Constraints concept for non-polymorphic functors.

-- 
All the best,
Alexey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] How to do this with associated types?

2010-07-25 Thread Alexey Karakulov
Suppose I have one piece of code like this:

 class Result r e | r - e where
    failure :: e - r a
    success :: a - r a

 at :: Result r String = [a] - Int - r a
 at xs i = if i = 0  i  length xs
     then success (xs !! i)
     else failure Wrong index

Either instance of Result is quite straightforward:

 instance Result (Either e) e where
     failure e = Left e
     success x = Right x

Maybe instance is discarding failure information:

 instance Result Maybe e where
     failure _ = Nothing
     success x = Just x

Some tests it in ghci:

ghci let xs = [0,1,2]
ghci at xs 2 :: Either String Integer
Right 2
ghci at xs 3 :: Either String Integer
Left Wrong index
ghci at xs 2 :: Maybe Integer
Just 2
ghci at xs 3 :: Maybe Integer
Nothing

I'd like to replace functional dependencies with type families
(associated types in my case):

 class Result r where
   type Failure
   failure :: Failure r - r a
   success :: a - r a

Either instance is ok:

 instance Result (Either e) where
   type Failure (Either e) = e
   failure e = Left e
   success x = Right x

But what to do with Maybe?

 instance Result Maybe where
   type Failure Maybe = forall e. e -- can't do this
   failure _ = Nothing
   success x = Just x
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] point-free ADT pattern matching ?

2010-07-15 Thread Alexey Karakulov
I wonder if pattern matching could be less verbose. Maybe this sounds weird,
but here is example of what I mean:

 type A = (Int, String)

 f :: String - A - A
 f s (i,s') = (i, s ++ s')

 data B = B Int String deriving Show

g :: String - B - B
g s (B i s') = B i $ s ++ s'

Types A/B and functions f/g are quite similar: (x :: A) or (x :: B) means
that x contains some integer and string values, and f/g functions take some
string and prepend it to the string part of x. The code for f and g has the
same level of verbosity, but -- ta-dah! -- we can use arrows and define f in
a highly laconic manner:

 import Control.Arrow
 f' :: String - A - A
 f' = second . (++)

So my queastion is how I could define (g' :: String - B - B) in the same
way.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe