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 information:

Re: [Haskell-cafe] GADT and instance deriving

2013-05-25 Thread Richard Eisenberg
Hi TP, Thankfully, the problem you have is fixed in HEAD -- the most recent version of GHC that we are actively working on. I am able, using the HEAD build of GHC, to use a `deriving Typeable` annotation to get a Typeable instance for a type that has non-*-kinded parameters. To get the HEAD

Re: [Haskell-cafe] GADT and instance deriving

2013-05-25 Thread TP
Hi Richard, Thanks a lot for your answer. We had a discussion about some Tensor type some time ago: https://groups.google.com/d/msg/haskell-cafe/Rh65kdPkX70/T2zZpV6ZpjoJ Today I have a type constructor Tensor in which there is a data constructor Tensor (among others): data Tensor

Re: [Haskell-cafe] GADT and instance deriving

2013-05-25 Thread Tillmann Rendel
Hi, TP wrote: Today I have a type constructor Tensor in which there is a data constructor Tensor (among others): data Tensor :: Nat - * where [...] Tensor :: String - [IndependentVar] - Tensor order [...] The idea is that, for example, I may have a vector

Re: [Haskell-cafe] GADT and instance deriving

2013-05-25 Thread Richard Eisenberg
Would this work for you? {-# LANGUAGE DataKinds, PolyKinds, GADTs, TypeOperators #-} data Nat = Zero | Succ Nat type One = Succ Zero type Two = Succ One data Operation :: [Nat] -- list of operand orders - Nat -- result order - * where

[Haskell-cafe] Cabal config file Guide

2013-05-25 Thread Daniel Díaz Casanueva
Hello Cafe! As you already know, cabal-install is configured in the file config. It has a lot of fields, but I didn't find a single place where each field is explained with detail. Most of the options are trivial enough to understand what they do without previous explanation, but some of them