Re: [Haskell-cafe] writing a function to make a correspondance between type-level integers and value-level integers

2013-06-22 Thread TP
s1.dlut.edu.cn/newVersion/Files/dsxx/610.pdf But this library (and the corresponding article) may help me in the future. Thanks, TP ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] putting the result of a function in `infix` declaration

2013-06-23 Thread TP
olynomial of second degree to be used at runtime. We would put some placeholders in the code where the result of the pre- processing calculation would enter. Thanks in advance, TP ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell

Re: [Haskell-cafe] writing a function to make a correspondance between type-level integers and value-level integers

2013-06-25 Thread TP
condensed and easy to remember notation; still better if it is easily extended to higher dimensions/orders (unfortunately, generally these notations are not taught at university). Regards, TP o...@okmij.org wrote: > Well, I guess you might be interested in geometric algebra then >

[Haskell-cafe] some questions about Template Haskell

2013-06-28 Thread TP
: j = 3 and then define in another module: --- h x = $([|j|]) main = do print $ h undefined --- I obtain "3" as expected. However, I do not achieve to make this system work with an infix declaration: infix $([| j |]) + I obtain: parse error on inpu

Re: [Haskell-cafe] some questions about Template Haskell

2013-06-29 Thread TP
TP wrote: > 2/ If I define in a module: > > j = 3 > > and then define in another module: > > --- > h x = $([|j|]) > main = do > print $ h undefined > --- > > I obtain "3" as expected. > > However,

Re: [Haskell-cafe] some questions about Template Haskell

2013-06-30 Thread TP
Base n ++ " = " )) ++ show $(varE n) ) |] by pr n = [| putStrLn ( $([| (nameBase n) ++ " = " |]) ++ show $(varE n) ) |] I again get the error """ No instance for (Lift Name) arising from a use of `n' Possible fix: add an instance declaratio

Re: [Haskell-cafe] some questions about Template Haskell

2013-07-01 Thread TP
parser needs a way to generate an AST > representation, which is what Lift is for. Ok, I think I understand that (we need some method to transform a value at data level in a token of an AST), but it seems to me it does not answer my question above. But I am probably wrong. Thanks TP

Re: [Haskell-cafe] some questions about Template Haskell

2013-07-02 Thread TP
above in Haskell works in MetaOCaml). What is strange is that: * in the version using "lift", the definition of lift asks for the output of (nameBase n) to be an instance of Lift, what is the case because it is a string (cf my previous post in this thread). * whereas in the s

[Haskell-cafe] typeclass constraints

2013-08-23 Thread TP
guage.Haskell.TH.Syntax p :: Lift a => a -> ExpQ p n = [| show n |] it works correctly. Why GHC is able to infer the typeclass constraint (Num a) in 1/, but not (Lift a) in 2/? Thanks in advance, TP ___ Haskell-Cafe mailin

Re: [Haskell-cafe] typeclass constraints

2013-08-23 Thread TP
Adam Gundry wrote: > If you leave off the type signature, as you did for sum', the > right thing will be inferred. Thanks Adam and Ivan. Very stupid question... TP ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.

[Haskell-cafe] reasons why Template Haskell does not propose something similar to Python exec() or eval()

2013-08-24 Thread TP
am unable to list them. I think it is important to have the reasons in mind. Could you help me? Thanks in advance, TP PS: the complete Haskell example: --- module MakeVard where import Language.Haskell.TH makeVard :: Monad m => String -> m [Dec] -- Equiva

[Haskell-cafe] Template Haskell: let statement in a splice put in the "main = do" part of a program?

2013-08-24 Thread TP
only be done by doE (or DoE) and compE (or CompE) according to http://www.haskell.org/ghc/docs/latest/html/libraries/template-haskell-2.8.0.0/Language-Haskell-TH.html#v:doE But doE is not a solution as we have seen above, and compE is to construct list comprehensions, which is a different thin

Re: [Haskell-cafe] Template Haskell: let statement in a splice put in the "main = do" part of a program?

2013-08-24 Thread TP
do with a let-statement; it requires something else > following it. You have nothing following it, as shown by the above > fragment from the error message. Yes, I have explained why: to be able to see the evaluation of the splice; otherwise I obtain "Not in sc

Re: [Haskell-cafe] reasons why Template Haskell does not propose something similar to Python exec() or eval()

2013-08-25 Thread TP
(IntegerL 1))) > :i parseDecs parseDecs :: String -> Either String [Language.Haskell.TH.Syntax.Dec] -- Defined in `Language.Haskell.Meta.Parse' > :i parseExp parseExp :: String -> Either String Language.Haskell.TH.Syntax.

Re: [Haskell-cafe] Template Haskell: let statement in a splice put in the "main = do" part of a program?

2013-08-27 Thread TP
tick to non-let expressions in the "main" part of a script, when it comes to TH. It should nevertheless allow me to call functions, make tests, etc. Thanks, TP ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] using "default" declaration for overloaded numeric operations

2013-09-21 Thread TP
t get any error below. $ ghci > import Data.Ratio > 2::Rational 2 % 1 Thanks in advance, TP ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] type-level integers, type-level operators, and most specific overlapping instance

2013-09-21 Thread TP
ion (Tensor n) Scalar (Tensor n) -- Defined at test_overlapping_instance_with_typelevelinteger_test.hs:34:10 In the expression: s * s In an equation for `a': a = s * s In the expression: do { let s = ...; let a = s * s; print a } Thanks in ad

Re: [Haskell-cafe] type-level integers, type-level operators, and most specific overlapping instance

2013-09-21 Thread TP
it does not look at the most specific instance by examining the instance context? Is it OK, or is it a deficiency? Thanks, TP - {-# LANGUAGE DataKinds #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE

Re: [Haskell-cafe] type-level integers, type-level operators, and most specific overlapping instance

2013-09-22 Thread TP
TP wrote: > But I have still a question: is the behavior of GHC correct in the example > of my initial post? See here: http://www.haskell.org/ghc/docs/7.6.3/html/users_guide/type-class-extensions.html#instance-overlap """ When matching, GHC takes no account of the co

Re: [Haskell-cafe] type-level integers, type-level operators, and most specific overlapping instance

2013-09-22 Thread TP
ot; So, what do I miss? Isn't the vocabulary different here? And I do not understand what is written if I take your definition (which is indeed the definition in the Haskell report). Thanks in advance, TP ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] parse error in pattern, and byte code interpreter

2012-01-14 Thread TP
e below? 2/ It seems there is no possibility to generate bytecode, contrary to OCaml. Is it correct? Is there an alternative? What is interesting with bytecode run with "ocamlrun" is that the process of generating the bytecode is very fast, so it is very convenient to test the program being w

[Haskell-cafe] function composition

2012-01-15 Thread TP
gument of `(°)', namely `q' In the expression: p ° q Prelude> What's the problem here? How can I obtain the type of p°q? Thanks in advance, TP ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] adding the elements of two lists

2012-03-25 Thread TP
the correct way to do that? I have tried: --- instance Num ListOfInt where l1 + l2 = ListOfInt $ getZipList $ (+) <$> ZipList (getList l1) <*> ZipList (getList l2) --- Isn't it too

[Haskell-cafe] get a string representation (show) of a function argument

2012-03-31 Thread TP
Hi, I don't known the advanced features and extensions of GHC at all. Look at the following program: f :: Integer -> Integer -> IO Integer f a b = do print $ "first argument=" ++ (show a) print $ "second argument=" ++ (show b) print $ a+b return (a+b) main = do

[Haskell-cafe] using FlexibleInstances and OverlappingInstances

2012-04-07 Thread TP
instance Show a => Show [a] -- Defined in GHC.Show instance [overlap ok] Show [Foo] -- Defined at test_overlappinginstances.hs:5:10-19 The overlap is ok ("overlap ok" does not appear if not using the prag

Re: [Haskell-cafe] using FlexibleInstances and OverlappingInstances

2012-04-07 Thread TP
instances at: http://book.realworldhaskell.org/read/using-typeclasses.html#id608052 but it does not seem to work well; or it is rather tricky: I have been unable to make my initial post example work with overlapping instances. However, I don't see why it could not work. Thanks TP ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] "desactivate" my Show instance implementations temporarily

2012-04-22 Thread TP
have I to comment all the Show instances of my code, and add "Show" in "deriving (...)" for each of my types? If this is the only possibility, is there some script around here to do that automatically? Thanks in advance, TP ___ Has

Re: [Haskell-cafe] "desactivate" my Show instance implementations temporarily

2012-04-22 Thread TP
etty printing (not over several lines as in classical Computer Algebra Sytems). Why not using my own Show implementation to do that? TP ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] phantom types

2012-08-17 Thread TP
Hi, I am currently reading documentation on Generalized Algebraic Data Types: http://en.wikibooks.org/wiki/Haskell/GADT I have a question concerning this page. Let us consider the following code proposed in the page: -- -- Phantom type variable a (does not appea

Re: [Haskell-cafe] phantom types

2012-08-17 Thread TP
) does not allow to know the type of a. It may be of type Expr String as you have shown: *Main> let expr = I 5 :: Expr String *Main> expr I 5 *Main> :t expr expr :: Expr String So we may have anything for «a» in «Expr a» input type of eval. These multiplicity of values for «a» cannot matc

[Haskell-cafe] partially applied data constructor and corresponding type

2013-04-27 Thread TP
in "pseudo-language": data Vector = TensorVar 1 String Because a vector is a tensor of order 1. Is this possible? I have tried type synonyms and newtypes without any success. Thanks a lot, TP ___ Haskell-Cafe mailing list Haskell-C

Re: [Haskell-cafe] partially applied data constructor and corresponding type

2013-04-27 Thread TP
ds to TensorVar with the integer equal to 1. The idea is to avoid duplicating code, by reusing the tensor type and data constructor. At some place in my code, in some definition (say, of a vector product), I want vectors and not more general tensors. TP On Saturday, April 27, 2013 16:16:49 Yury Su

Re: [Haskell-cafe] partially applied data constructor and corresponding type

2013-04-28 Thread TP
the following days, according to my needs. Thanks a lot, TP On Sunday, April 28, 2013 07:58:58 Stephen Tetley wrote: > What you probably want are type level integers (naturals) > > Yury Sulsky used them in the message above - basically you can't use > literal numbers 1,2,3,... et

Re: [Haskell-cafe] partially applied data constructor and corresponding type

2013-04-29 Thread TP
s. Thanks, TP On Monday, April 29, 2013 08:19:43 Richard Eisenberg wrote: > There's a lot of recent work on GHC that might be helpful to you. Is it > possible for your application to use GHC 7.6.x? If so, you could so > something like this: > > {-# LANGUAGE DataKinds, GADTs

[Haskell-cafe] question about GADT and deriving automatically a Show instance

2013-05-17 Thread TP
GHC stack-space overflow: current limit is 536870912 bytes. Use the `-K' option to increase it. Why (I imagine this is because there is an infinite loop in the construction of the show function)? Is there any workaround? Thanks, TP ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] question about GADT and deriving automatically a Show instance

2013-05-17 Thread TP
, father :: Person Gender } -> Person Gender deriving instance Show (Person Gender) main = do let a = Alive "Joe" 60 Dead :: Person Male let b = Alive "Jim" 70 a :: Person Male print a print b How to modify it? Thanks a l

Re: [Haskell-cafe] question about GADT and deriving automatically a Show instance

2013-05-18 Thread TP
data Gender = Male | Female data Person :: Gender -> * where Dead :: forall (a :: Gender). Person a Alive :: { name :: String , weight :: Float , father :: forall (a :: Gender). Person a } -> forall (b :: Gender). Person b deriving instance Sho

Re: [Haskell-cafe] question about GADT and deriving automatically a Show instance

2013-05-18 Thread TP
ead :: Person a > Alive :: { name :: String > , weight :: Float > , father :: Person b } -> Person a > > deriving instance Show (Person a) Thanks so much, it is now perfectly clear. A lot of things learned with this dummy example. TP ___

Re: [Haskell-cafe] partially applied data constructor and corresponding type

2013-05-18 Thread TP
Richard Eisenberg wrote: > There's a lot of recent work on GHC that might be helpful to you. Is it > possible for your application to use GHC 7.6.x? If so, you could so > something like this: > > {-# LANGUAGE DataKinds, GADTs, KindSignatures #-} > > data Nat = Zero | Succ Nat > > type One = Suc

[Haskell-cafe] accessing a type variable in instance declaration

2013-05-22 Thread TP
++ str ++ ” of order ” ++ (show (c2num order)) Thanks in advance, TP ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] accessing a type variable in instance declaration

2013-05-22 Thread TP
So, in the first case, c has a too restricted kind, and in the second one, it has a too broad kind in the definition of cpred. I have tried several things without any success. How to compile that code? Thanks, TP ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] question about type constructors

2013-05-22 Thread TP
The reason is that the information that p1 and p2 are Male seems to be "lost" when we construct the child "Child "Jack" p1 p2", probably because GHC only sees that in the type signature of Child, we have a mo

Re: [Haskell-cafe] question about type constructors

2013-05-23 Thread TP
ot;, "Child3" (imagining a world where every people has three children). The problem is that I am compelled to repeat the context "(PrettyPrint (Person a), PrettyPrint (Person b))" for each one of the constructors. Is there any way to specify the context onl

[Haskell-cafe] GADT and instance deriving

2013-05-24 Thread TP
Box (2::Float) print $ a == b print $ a == a -- Is this the right way to go? Is there any other solution? Thanks, TP ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] GADT and instance deriving

2013-05-24 Thread TP
ite a Typeable instance if you want one. The process is somewhat trickier than you might expect, due to the fact that Typeable does some unsafe stuff. But there are plenty of examples for how to do it safely. """ Where are these examples that can

Re: [Haskell-cafe] GADT and instance deriving

2013-05-25 Thread TP
TP wrote: > Where are these examples that can help me to write my instance? > I have tried to read the source of the implemented instances in > data.typeable, not so easy for me. Ok, by doing a better search on Google ("instance typeable " blog), I have found interesting

Re: [Haskell-cafe] GADT and instance deriving

2013-05-25 Thread TP
untime dimension checks, everything is detected at compilation. So the choice of putting the order in the type seems to be correct. My only need to use Typeable comes from the heterogeneous list. But how to do without? Thanks, TP Richard Eisenberg wrote: > Thankfully, the problem you have

Re: [Haskell-cafe] GADT and instance deriving

2013-05-26 Thread TP
prefer). So I have three instances for scalar product '⋅'. I don't see how to combine this idea of overloading or derivation function with what you proposed. But I have perhaps missed something. Thanks, TP (*): That is to say the list of tensors of which one tensor depends, e.g.

[Haskell-cafe] question about "singletons"

2013-05-31 Thread TP
g a) main = do let one = undefined :: Sing ('Succ 'Zero) print one --- The error is simply: --- test_noinhabitant_corrected.hs: Void showsPrec --- Why? Thanks, TP References: -- (1): https://groups.google.com/fo

Re: [Haskell-cafe] question about "singletons"

2013-06-01 Thread TP
ial examples in part (1) of Post Scriptum below. We have a concrete type Foo clearly of kind `*`, so bottom (undefined in Haskell) is an inhabitant of Foo. Why should I be compelled to add another inhabitant (a data constructor) to get bottom printed? Bottom existence is independent from oth

Re: [Haskell-cafe] question about "singletons"

2013-06-02 Thread TP
> discovery of undefined in a running program. (GHC has implemented an > exception that allows exception-handling code, written in the IO monad, to > catch a use of undefined, but I would be highly suspicious of code that > used this feature.) Interesting, I will remember that. T

[Haskell-cafe] Typeable typeclass and type-level naturals

2013-06-02 Thread TP
with GHC 7.6.2, the message is different because recent improvements in Typeable are not present (1). What is the problem? I've tried different things without success. Tell me if the "beginners" diffusion list is more suitable than Haskell- Cafe. Thanks, TP (1): http://hauptwerk.bl

Re: [Haskell-cafe] Typeable typeclass and type-level naturals

2013-06-04 Thread TP
’ What is the problem? Is it possible that it is a bug in GHC? Indeed, we had unwanted similar error messages recently: http://hackage.haskell.org/trac/ghc/ticket/7704 Thanks, TP PS: the complete program for a test that shows the error: -- {-# LANGUAGE GADTs

Re: [Haskell-cafe] Typeable typeclass and type-level naturals

2013-06-05 Thread TP
'Zero deriving instance Typeable 'Succ data Box where Box :: (Typeable s, Show s, Eq s) => s -> Box deriving Typeable data Proxy a = P deriving (Typeable, Show, Eq) deriving instance Show Box instance Eq Box where (Box s1) == (Box s2) = Just s1 == cast s2 main = d

[Haskell-cafe] writing a function to make a correspondance between type-level integers and value-level integers

2013-06-09 Thread TP
Nat (P (Succ n)) = SSucc (mkSNat (P n)) main = do let one = undefined :: Proxy ('Succ 'Zero) print one print $ mkSNat (P one) -- Thanks, TP References: --- [1]: https://groups.google.com/forum/?fromgroups#!topic/haskell-c

Re: [Haskell-cafe] writing a function to make a correspondance between type-level integers and value-level integers

2013-06-09 Thread TP
ade `'Succ n` and `Zero` instances of MkSNat; are we compelled to put a constraint because Haskell makes the hypothesis that o could be another type of kind Nat different from `'Succ n` and `Zero`? If yes, is it related to the sentence I have already read: "Typeclasses are op

Re: [Haskell-cafe] writing a function to make a correspondance between type-level integers and value-level integers

2013-06-10 Thread TP
gnitude 10^4 lines), it is necessary to have types (I would not use Haskell for a small script, of course). I feel also, from my coding experience, that states are a real problem in traditional C/C++/Python/... code, and I want to give a try with Haskell, monads, perhaps arrows, reactive progra