Re: [Haskell-cafe] Problems with libgmp on Amazon Linux

2012-01-06 Thread Yucheng Zhang
On Sat, Jan 7, 2012 at 1:04 PM, Yucheng Zhang  wrote:
> ldconfig -n /usr/bin

Sorry, it should be:

ldconfig -n /usr/lib

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


Re: [Haskell-cafe] Problems with libgmp on Amazon Linux

2012-01-06 Thread Yucheng Zhang
On Sat, Jan 7, 2012 at 8:08 AM, Nicu Ionita  wrote:
> It seemed to work pretty well, with some problems when configuring HP,
> because although libgmp was already installed, it was not recognized. I
> installed the newer version 5.0.2 (from sources) [4], did some tricks (cp
> /usr/lib/lib/libgmp* /usr/lib), then configure worked and HP was built and
> installed.

I think you should get the installed libgmp recognized, but not doing tricks
like this. It is no problem as a temporary solution, but you should always
try to make use of a package manager.

> Loading package integer-gmp ... : can't load .so/.DLL for: gmp
> (libgmp.so: cannot open shared object file: No such file or directory)

I have no experience with AWS, but it seems that you need to run a ldconfig
to rebuild the cache, since you installed libgmp just by copying into /usr/lib.

ldconfig -n /usr/bin

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


Re: [Haskell-cafe] Solved but strange error in type inference

2012-01-04 Thread Yucheng Zhang
On Wed, Jan 4, 2012 at 9:41 PM, Yves Parès  wrote:
> Would you try:
>
> f :: a -> a
> f x = undefined :: a
>
> And tell me if it works? IMO it doesn't.

It works.

As I understand, in this situation we are specializing the 'undefined
:: forall a. a'
to a more specific dependent type.

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


Re: [Haskell-cafe] Solved but strange error in type inference

2012-01-04 Thread Yucheng Zhang
On Wed, Jan 4, 2012 at 8:15 PM, Yucheng Zhang  wrote:
> I expected the type of 'x' to be universally quantified, and thus can be 
> unified
> with 'forall a. a' with no problem.

I've never been thinking in a detailed level, and the 'x' appears to be able to
take any type, and thus the wrong expectation.

Thanks for all the input from all.

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


Re: [Haskell-cafe] Solved but strange error in type inference

2012-01-04 Thread Yucheng Zhang
On Wed, Jan 4, 2012 at 7:58 PM, Yves Parès  wrote:
> f :: forall a. a -> a
> f x = x :: forall a. a
>
> Which is obviously wrong: when you have entered f, x has been instatiated to
> a specific type 'a', and then you want it to x to be of any type? That
> doesn't make sense.

I did not expect the type variables to be scoped.

I expected the type of 'x' to be universally quantified, and thus can be unified
with 'forall a. a' with no problem.

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


Re: [Haskell-cafe] Solved but strange error in type inference

2012-01-04 Thread Yucheng Zhang
On Wed, Jan 4, 2012 at 3:46 AM, Yves Parès  wrote:
> Because without ScopedTypeVariable, both types got expanded to :
>
> legSome :: forall nt t s. LegGram nt t s -> nt -> Either String ([t], s)
>
> subsome :: forall nt t s. [RRule nt t s] ->  Either String ([t], s)
>
> So you see subsome declare new variables, which do not match the rigid ones
> declared by legSome signature, hence the incompatibility.
>

It's not obvious to see the incompatibility. I looked into the Haskell
2010 Language
Report, and found my question answered in Section 4.4.1, along with a minimal
reproducing example:

f :: a -> a
f x = x :: a  -- invalid

The confusing point to me is that the 'a' from 'f' type signature on
its own is not
universally quantified as I expected, and it is dependent on the type of 'f'.

This dependence is not obvious for a beginner like me.

ScopedTypeVariables will help to express the dependence exactly. And moving
'subsome' to top-level will prevent from bringing in the dependent type.

> Now, concerning the error I asked you to deliberately provoke, that's the
> quickest way I found to know what is the output of the type inferer, and
> maybe the only simple one.

I find this one of the most interesting tricks I've seen.

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


Re: [Haskell-cafe] Solved but strange error in type inference

2012-01-03 Thread Yucheng Zhang
On Wed, Jan 4, 2012 at 2:48 AM, Bardur Arantsson  wrote:
> 'subsome' to a different type than the one you intended -- and indeed one
> which can't be unified with the inferred type. (Unless you use
> ScopedTypeVariables.)

Thanks for the reply.

Actually, my question is why the different type can't be unified with
the inferred type? Could you point me some related resources?

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


Re: [Haskell-cafe] Solved but strange error in type inference

2012-01-03 Thread Yucheng Zhang
On Wed, Jan 4, 2012 at 1:07 AM, Yves Parès  wrote:
>> I wonder why the redeclared type variables cannot match those of legSome?
> Try to put a totally wrong type to subsome, like
> subsome :: Int
> and tell us from the error what type is actually inferred.
>

The actually inferred type is

Couldn't match expected type `Int'
with actual type `[([Symbols nt t], [s] -> t0)]
  -> Either [Char] ([t], t0)'
In the expression: subsome :: Int

I still don't understand why the original mismatch happens.

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


Re: [Haskell-cafe] Solved but strange error in type inference

2012-01-03 Thread Yucheng Zhang
On Wed, Jan 4, 2012 at 1:38 AM, Yucheng Zhang  wrote:
> On Wed, Jan 4, 2012 at 1:07 AM, Yves Parès  wrote:
>> Try to put a totally wrong type to subsome, like
>> subsome :: Int
>> and tell us from the error what type is actually inferred.
>

Sorry, I found I misunderstood the suggestion. I will try.

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


Re: [Haskell-cafe] Solved but strange error in type inference

2012-01-03 Thread Yucheng Zhang
On Wed, Jan 4, 2012 at 1:07 AM, Yves Parès  wrote:
> Try to put a totally wrong type to subsome, like
> subsome :: Int
> and tell us from the error what type is actually inferred.

The error is like

>Couldn't match type `nt' with `Int'
>  `nt' is a rigid type variable bound by
>   the type signature for
> legSome :: LegGram nt t s -> nt -> Either String ([t], s)
>   at xx.hs:35:1
>Expected type: [RRule Int t s]
>  Actual type: [RRule nt t s]
>In the first argument of `subsome', namely `l'
>In the expression: subsome l

However, this error cannot be resolved by a use of ScopedTypeVariable,
while the original error can be resolved.

I still don't see where the mismatch happens in the original error. Any help
is appreciated.

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


Re: [Haskell-cafe] Solved but strange error in type inference

2012-01-03 Thread Yucheng Zhang
On Wed, Jan 4, 2012 at 12:44 AM, Yves Parès  wrote:
> Remove subsome type signature. You are redeclaring type variables which
> obviously cannot match those of legSome.
> This cannot work without scoped type variables (and ad-hoc foralls to bring
> them to scope, of course).

That subsome type signature is from the original code.

I wonder why the redeclared type variables cannot match those of legSome?




p.s. I just realized that my changed code missed the line:

> import qualified Data.Map as M

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


Re: [Haskell-cafe] Solved but strange error in type inference

2012-01-03 Thread Yucheng Zhang
As I investigated the code more carefully, I found that the type unification
failure may not be related to the suspected class constraint on data
constructor.

I have made minor changes to the original code to remove the Ord constraint,
including introducing a FakedMap with no requirement on Ord. The type
unification
failure continues:

>Couldn't match type `nt1' with `nt'
>  `nt1' is a rigid type variable bound by
>the type signature for
>  subsome :: [RRule nt1 t1 s1] -> Either String ([t1], s1)
>at xx.hs:34:19
>  `nt' is a rigid type variable bound by
>   the type signature for
> legSome :: LegGram nt t s -> nt -> Either String ([t], s)
>   at xx.hs:29:1
>Expected type: [Symbols nt1 t1]
>  Actual type: [Symbols nt t]
>In the first argument of `makeWord', namely `r'
>In the expression: makeWord r

The complete changed code follows:


data Symbols nt t = NT nt -- ^ non terminal
  | T t  -- ^ terminal
 deriving (Eq, Ord)

type Sem s = [s]->s

data Rule nt t s = Rule { refined :: nt
   , expression :: [Symbols nt t]
   , emit :: Sem s
   }

type RRule nt t s = ([Symbols nt t], Sem s)



data FakedMap a b = FakedMap

delete :: k -> FakedMap k a -> FakedMap k a
delete a b = b

lookup :: k -> FakedMap k a -> Maybe a
lookup a b = Nothing



data LegGram nt t s = LegGram (FakedMap nt [RRule nt t s])

legSome :: LegGram nt t s -> nt -> Either String ([t], s)
legSome (LegGram g) ntV =
  case Main.lookup ntV g of
Nothing -> Left "No word accepted!"
Just l -> let sg = legSome (LegGram (Main.delete ntV g))
  subsome :: [RRule nt t s] -> Either String ([t], s)
  subsome [] = Left "No word accepted!"
  subsome ((r,sem):l) =
let makeWord [] = Right ([],[])
makeWord ((NT nnt):ll) =
  do (m, ss) <- sg nnt
 (mm, sss) <- makeWord ll
 return (m++mm, ss:sss)
makeWord ((T tt):ll) =
  do (mm, sss) <- makeWord ll
 return (tt:mm, sss)
 in
   case makeWord r of
 Right (ll, mm) -> Right (ll, sem mm)
 Left err -> subsome l
  in subsome l

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


Re: [Haskell-cafe] Solved but strange error in type inference

2012-01-03 Thread Yucheng Zhang
On Tue, Jan 3, 2012 at 7:49 PM, Yucheng Zhang  wrote:
> I found some descriptions of ScopedTypeVariables here:
>
> http://hackage.haskell.org/trac/haskell-prime/wiki/ScopedTypeVariables

Sorry, I found just now a more up-to-date description in the GHC documentation:

http://www.haskell.org/ghc/docs/latest/html/users_guide/other-type-extensions.html#scoped-type-variables

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


Re: [Haskell-cafe] Solved but strange error in type inference

2012-01-03 Thread Yucheng Zhang
On Tue, Jan 3, 2012 at 7:46 PM, Brandon Allbery  wrote:
> Right, but I think this is conflating two aspects of ScopedTypeVariables and
> may not bring them into scope "fully".  Although, that's a question for
> someone who understands ghc's type system far better than I do.
>

I found some descriptions of ScopedTypeVariables here:

http://hackage.haskell.org/trac/haskell-prime/wiki/ScopedTypeVariables

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


Re: [Haskell-cafe] Solved but strange error in type inference

2012-01-03 Thread Yucheng Zhang
As I understand it, both ways work.

> legSome ((LegGram g)::LegGram nt t s) ntV

If you compile this without ScopedTypeVariables extension, GHC will
remind you of it:

>Illegal signature in pattern: LegGram nt t s
>Use -XScopedTypeVariables to permit it

So another solution is to avoid the ugly redundancy is:

> legSome :: forall nt t s . LegGram nt t s -> nt -> Either String ([t], s)

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


Re: [Haskell-cafe] Solved but strange error in type inference

2012-01-03 Thread Yucheng Zhang
On Tue, Jan 3, 2012 at 6:44 PM, Brandon Allbery  wrote:
> On Tue, Jan 3, 2012 at 05:17, Yucheng Zhang  wrote:
>>
>> subsome :: [RRule nt t s] -> Either String ([t], s)
>>
>> It seems to me that the compiler is not sure the two 'nt' are equal.
>> The ScopedTypeVariables can make the compiler believe they are equal.
>
>
> But ScopedTypeVariables is enabled already.
>

Sorry, I meant actually using ScopedTypeVariables as in the first function,
which compiles well:

legSome :: LegGram nt t s -> nt -> Either String ([t], s)
-- ^^
--isn't this redundant?
--vv
legSome ((LegGram g)::LegGram nt t s) ntV =
  case M.lookup ntV g of
Nothing -> Left "No word accepted!"
Just l -> let sg = legSome (LegGram (M.delete ntV g))
  subsome :: [RRule nt t s] -> Either String ([t], s)
  subsome [] = Left "No word accepted!"
  subsome ((r,sem):l) =
let makeWord [] = Right ([],[])
makeWord ((NT nnt):ll) =
  do (m, ss) <- sg nnt
 (mm, sss) <- makeWord ll
 return (m++mm, ss:sss)
makeWord ((T tt):ll) =
  do (mm, sss) <- makeWord ll
 return (tt:mm, sss)
 in
   case makeWord r of
 Right (ll, mm) -> Right (ll, sem mm)
 Left err -> subsome l
  in subsome l

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


Re: [Haskell-cafe] Solved but strange error in type inference

2012-01-03 Thread Yucheng Zhang
On Tue, Jan 3, 2012 at 5:43 PM, AUGER Cédric  wrote:
> legSomeb :: LegGram nt t s -> nt -> Either String ([t], s)
> -- but without it I have an error reported
> legSomeb (LegGram g) ntV =
>   case M.lookup ntV g of
>     Nothing -> Left "No word accepted!"
>     Just l -> let sg = legSomeb (LegGram (M.delete ntV g))
>                   subsome :: [RRule nt t s] -> Either String ([t], s)
>                   subsome [] = Left "No word accepted!"
>                   subsome ((r,sem):l) =
>                     let makeWord [] = Right ([],[])
>                         makeWord ((NT nnt):ll) =
>                           do (m, ss) <- sg nnt
>                              (mm, sss) <- makeWord ll
>                              return (m++mm, ss:sss)
>                         makeWord ((T tt):ll) =
>                           do (mm, sss) <- makeWord ll
>                              return (tt:mm, sss)
>                      in
>                    case makeWord r of
>                      Right (ll, mm) -> Right (ll, sem mm)
>                      Left err -> subsome l
>               in subsome l

I found it compiling well if removing this line:

subsome :: [RRule nt t s] -> Either String ([t], s)

It seems to me that the compiler is not sure the two 'nt' are equal.
The ScopedTypeVariables can make the compiler believe they are equal.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Avoiding parametric function binding

2011-12-31 Thread Yucheng Zhang
On Sat, Dec 31, 2011 at 11:09 PM, Kevin Quick  wrote:
>> varElem :: forall x . (Show x) => Var -> x
>> varElem (V1 x) = x
>> varElem (V2 x) = x
>>
>> main = putStrLn . elemStr . varElem $ test
>

The problem here is that you want the return type to depend on the
'value' of Var,
which is not known until runtime.

Maybe you can wrap the 'conflicting' return type inside an existential type:

data VarWrap = forall x . (Show x) => Wrap x

instance Show VarWrap where
show (Wrap x) = show x

varElem :: Var -> VarWrap
varElem (V1 x) = Wrap x
varElem (V2 x) = Wrap x

You will need an 'ExistentialQuantification' language extension to do this.

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


Re: [Haskell-cafe] memorize function with number parameterized types in GHC

2011-11-06 Thread Yucheng Zhang
On Mon, Nov 7, 2011 at 9:29 AM, Bin Jin  wrote:
> Hi
> This method is what I'm looking for. it's a nice general solution, but it
> doesn't solve my problem here.
> I'm using ghc 7.0.3, I tried to cache p2num and montgKeys in the way you
> showed. It seems that ghc doesn't memorize p2num and reject to compile new
> montgKeys.
> I think caching values with dynamic types is complicated in ghc's runtime
> environment. Anyone knows the details?

Adding memorization directly to 'montgKeys' or 'p2num' should be possible,
if you write your own version of MemoTrie dealing with dynamic types.

However, this memorization requires an O(log P) lookup in the trie.
This lookup process will require the whole type structure of P to be
examined, which is of size O(log P).



Yucheng Zhang

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


Re: [Haskell-cafe] memorize function with number parameterized types in GHC

2011-11-06 Thread Yucheng Zhang
On Sun, Nov 6, 2011 at 9:35 PM, Bin Jin  wrote:
> Hi,
> Since I actually didn't use the parameter in calculation, the return value
> only depends on the type
> of input, not the actually value. If it's impossible to cache the result, is
> there another way to
> memorize this "function" ?

Sorry, I haven't considered about 'number parameterized
type' when I answered the question.

However, you can still use a data structure like MemoTrie [1]
to memorize the function. The memorization is trivial, since
you can convert between the number-typed 'undefined' and
'Integer' with the functions 'p2num' and 'num2p' in your
code. I've not tested, but this is an example using MemoTrie:

> import Data.MemoTrie
>
> memoMontgKeys :: (PostiveN p, Integral a, Bits a) => p -> a
> memoMontgKeys = memoMontgKeys' . p2num
>
> memoMontgKeys' :: (Integral a) => Integer -> a
> memoMontgKeys' = memo (montgKeys . num2p)

On the other hand, I think GHC is not expected to do the
memorization automatically. An arbitrary number can turn up
as the argument type of 'montgKeys'. This is similar to a
function with an Integer argument, which GHC does not
memorize now.


[1] http://hackage.haskell.org/package/MemoTrie



Yucheng Zhang

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


Re: [Haskell-cafe] memorize function with number parameterized types in GHC

2011-11-06 Thread Yucheng Zhang
On Sun, Nov 6, 2011 at 9:10 PM, Bin Jin  wrote:
> Hi, everyone
>
> I'm recently trying to implement the Montgomery reduction algorithm[1] in
> Haskell, the code can be found on
> my Github page[2]. After doing some benchmark testing I found that the
> library works rather slow. With the
> help of `trace` function from Debug.Trace, I found that GHC is not magical
> enough to memorize values with
> the same type(well, it's actually dynamically generated number parameterized
> type).
>
> I used binary representation to handle all positive numbers in type system.
>
>> data One = One
>> data D0 a = D0 a
>> data D1 a = D1 a
>> class PostiveN a where
>>     p2num :: (Num b, Bits b) => a -> b
>> instance PostiveN One ...
>> instance PostiveN a => PostiveN (D0 a) ...
>> instance PostiveN a => PostiveN (D1 a) ...
>
> Here is a function that will be called everytime by `(*)` in `Num` typeclass
>> montgKeys :: (PostiveN p, Integral a, Bits a) => p -> a
>
> as you can imagine, I always pass (undefined :: p) as parameter to
> `montgKeys`, so if it's handled
> well, it should be memorized for future usage. But tracing shows that both
> `p2num` and `montgKeys`
> are evaluated every time being called.
>
> So my question is, how to force GHC memorizing this kind of functions?
>
> [1]: http://en.wikipedia.org/wiki/Montgomery_reduction
> [2]: https://github.com/bjin/montg-reduce
>
> Regards,
> Bin

GHC only memorizes data structures, but not functions. See [1].

[1] http://www.haskell.org/haskellwiki/Memoization


--
Yucheng Zhang

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