[Haskell-cafe] open datatypes

2011-02-16 Thread rodrigo.bonifacio
Dear all, Supposing that I have a FlowObject datatype such as:data FlowObject = Activity { ...  }  | Start | End | Proceed | ...I could make "open" this datatype by refactoring this definition through a type class + one datatype for each kind of FlowObject. Such as:data Activity = Activity { ... }data Start = Start ... class FlowObject a instance FlowObject Activityinstance FlowObject Start  Although the second approach opens the FlowObject datatype, it does not resemble a grammar anymore. So: - Is there any other idiom that opens a datatype keeping its similarities with grammars? - Does exist any idiom that allows a developer to introduce new fields into an existing datatype?Thanks in advance,Rodrigo.

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


[Haskell-cafe] Profiling

2010-04-20 Thread rodrigo.bonifacio
Dear all,
I am trying to compile a project with the "-prof -auto-all" profile options. But the compiler returns:
"Could not find module `Text.ParserCombinators.Parsec.Language':Perhaps you haven't installed the profiling libraries for package `parsec-3.1.0'?Use -v to see a list of the files searched for."
When I build the project without the "-prof -auto-all", the project compiles without any error or warning. I build GHC (6.10.4) from source, without changing any build option.
Thanks in advance for any help,
Rodrigo.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Distinct types in a list

2010-01-07 Thread rodrigo.bonifacio
Hi all,

I have a family of parsers that return either (Success t) or (Fail), using the 
following data type:

 data ParserResult a = Success a | Fail String
  deriving (Read, Show, Eq, Ord)

 isSuccess (Success _) = True
 isSuccess (Fail _) = False
 ...

I want to add the results of different parsers to a list. Such as:

 m1 = parseFirstModel file1   -- it returns a ParserResult of t1
 m2 = parseSecondModel file2  -- it returns a ParserResult of t2

 ps = [m1, m2]

In such a way that I could write something like: 

 if and (map isSuccess ps) 
  then process m1 m2
  else ... 

Actually, in the real program I have to check more than two input models. 
However, since Lists do only hold elements of a same type, I couldn't proceed 
in this way. Which improvements to the ParserResult data type should I wrote in 
order to proceed as I want to.

Best regards,

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


[Haskell-cafe] lhs2tex + pretty print

2009-12-10 Thread rodrigo.bonifacio
Dear all,
I want to call a function "f :: Scenario - Doc", using lhs2tex, that returns a Doc of the HughesPJ pretty print library. The returning Doc is embedded with Latex syntax. I mean, calling (show f s) returns some thing like:
"\\subsubsection*{Scenario sc01}\n\\begin{itemize}\n\\item "
Printing this representation to a file leads to a valid Latex file. However, compiling a call such as (\perform{show f s}), using lhs2tex, lads to an invalid latex document. Is there any lhs2tex option that could be used in this case?
Thanks for any help.
Rodrigo.
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Existencial Types

2009-12-03 Thread rodrigo.bonifacio
Dear Luke, thanks for your answers

 If SelectScecario is used for other purposes, then give an explicit 
 cast function

Sure, as I mentioned, we have different transformations and it would be worth 
to filter a list of transformations by a particular type or even apply the list 
of transformations in a particular order considering their type.

 toTransformation :: SelectScenario - Transformation
 toTransformation (SelectScenario ids) = Transformation {
(+) = {- implementation of (+) just as if it were a class method -}
  }

I understand your idea, but I will have to implement several variations of 
toTransformation, one for each kind of transformation. Moreover, I couldn't 
realize how is possible to define a function that could be applied to different 
transformations without using type classes--- I have to restrict the 
types of argument of such a function. Moreover, I couldn't figure out what are 
the benefits of your solution. Please, if possible, could you elaborate 
that a bit more, in order that I could understand  why your design is better (I 
mean, more legible, reusable or concise)?

Thanks in advance,

Rodrigo.

Em 01/12/2009 22:44, Luke Palmer  lrpal...@gmail.com  escreveu:


On Tue, Dec 1, 2009 at 4:21 PM, rodrigo.bonifacio
 wrote:
 Thanks Luke.

 In fact I, will have different implementations of the Transformation type.
 Something like:

 data SelectScenarios = SelectScenarios {

 scIds :: [Id]

 }

What is this different type buying you?  You can never downcast to it later.

 And then I should be able to make SelectScenarios a kind of Transformation.
 So I think that I really need a class. What do you think about it?

 instance Transformation SelectScenario where

 (+)  

So instead of making a type and an instance, just implement it
directly as a Transformation:

selectScenario :: [Id] - Transformation
selectScenario ids = Transformation {
 (+) =  {- whatever implementation you gave for (+) above, using ids -}
 }

If the only purpose of SelectScenario (your type) is to be used
polymorphically as a Transformation, then this approach is isomorphic
-- i.e. anything you can do with the existential type trick you can do
with this approach.

If SelectScecario is used for other purposes, then give an explicit
cast function

toTransformation :: SelectScenario - Transformation
toTransformation (SelectScenario ids) = Transformation {
 (+) = {- implementation of (+) just as if it were a class method -}
 }

Existential types only buy you power when the quantified variable
appears more than once on the right hand side, for example:  forall a.
Num a = (a,a).  But even those can usually be factored out into more
direct representations (I seem to recall Oleg has a proof that they
always can, actually).

Luke



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


[Haskell-cafe] Existencial Types

2009-12-01 Thread rodrigo.bonifacio
Dear all, I wrote the following  types:
 class Transformation t where   (+) :: t - SPLModel  - InstanceModel - InstanceModel
 data Configuration = forall t . Transformation t = Configuration (FeatureExpression, [t]) type ConfigurationKnowledge = [Configuration]
 
I tried to write a function that retrieves the list of transformations of a configuration. Bellow a code snip of such a function.
 transformations ck fc = concat [snd c | (Configuration c) - ck, eval fc (fst c)]
However, compiling this I got:
--- Inferred type is less polymorphic than expected Quantified type variable `t' escapes When checking an existential match that binds c :: (FeatureModel.Types.FeatureExpression, [t]) The pattern(s) have type(s): Configuration The body has type: [t] In a stmt of a list comprehension: (Configuration c) - ck In the first argument of `concat', namely `[snd c | (Configuration c) - ck, eval fc (fst c)]'
---
 
How can I fix this problem?
Thanks,
Rodrigo.
 
 
 
 
 
 
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Existencial Types

2009-12-01 Thread rodrigo.bonifacio
Thanks Luke.
In fact I, will have different implementations of the Transformation type. Something like:
data SelectScenarios = SelectScenarios {
scIds :: [Id]
}
 
And then I should be able to make SelectScenarios a kind of Transformation. So I think that I really need a class. What do you think about it?
instance Transformation SelectScenario where
(+)  
 
Regards,
Rodrigo.
 
 
 
 
 
Em 01/12/2009 19:39, Luke Palmer  lrpal...@gmail.com  escreveu:
On Tue, Dec 1, 2009 at 11:21 AM, David Menendez  wrote: On Tue, Dec 1, 2009 at 1:00 PM, rodrigo.bonifacio  wrote: Dear all, I wrote the following  types: class Transformation t where  (+) :: t - SPLModel  - InstanceModel - InstanceModel data Configuration = forall t . Transformation t = Configuration (FeatureExpression, [t]) type ConfigurationKnowledge = [Configuration]I would suggest doing away with the class in a case like this.data Transformation = Transformation { (+) :: SPLModel - InstanceModel - InstanceModel }data Configuration = Configuration FeatureExpression [Transformation]I suspect that it was OO heritage that l
 ed you to want a class here?Forget that!  :-)Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Scrap your boilerplate traversals

2009-11-25 Thread rodrigo.bonifacio
Hi all,
Is there a non-recursive traversal defined in Data.Generics' modules? I mean, the everywhere traversal first applies a function "f" to the subterms, and then applies "f" to the result. I am wondering if do exists a traversal that applies f only to the subterms.
Thanks in advance,
Rodrigo.
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Converting IO [XmlTree] to [XmlTree]

2009-04-14 Thread rodrigo.bonifacio
Dear Sirs,
I guess this is a very simple question. How can I convert IO [XmlTree] to just a list of XmlTree?
Regards,
Rodrigo.
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] HXT + Segmentation Fault

2009-02-12 Thread rodrigo.bonifacio
Hi all,

I'm trying to parse some XML files using HXT. However, even the examples 
available on the twiki fail. I guess that the problem is related to some 
library version, but I'm not sure.

The error reported is: Segmentation fault.

Thanks in advance. 

Compiling with GHC-6.8.3 running on MAC/OS Tiger

Packages:

Cabal-1.2.4.0, HUnit-1.2.0.0, QuickCheck-1.1.0.0, array-0.1.0.0,
 base-3.0.2.0, bitset-0.6, bytestring-0.9.0.1.1, cgi-3001.1.6.0,
 containers-0.1.0.2, curl-1.3.3, directory-1.0.0.1, fgl-5.4.2.0,
 filepath-1.1.0.0, funsat-0.5.1, ghc-6.8.3, haskell-src-1.0.1.2,
 haskell98-1.0.1.0, hpc-0.5.0.1, html-1.0.1.1, hxt-8.1.0,
 (mtl-1.1.0.1), mtl-1.1.0.2, (network-2.2.0.0), network-2.2.0.1,
 old-locale-1.0.0.0, old-time-1.0.0.0, packedstring-0.1.0.0,
 parallel-1.0.0.1, parse-dimacs-1.2, parsec-2.1.0.1, parsec-3.0.0,
 pcre-light-0.3.1, pretty-1.0.0.0, process-1.0.0.1, random-1.0.0.0,
 readline-1.0.1.0, regex-base-0.72.0.1, regex-compat-0.71.0.1,
 regex-posix-0.72.0.2, rts-1.0, stm-2.1.1.1, tagsoup-0.6,
 template-haskell-2.2.0.0, time-1.1.2.1, unix-2.3.0.1,
 xhtml-3000.2.0.0
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Converting Lists to Sets

2009-02-03 Thread rodrigo.bonifacio
Hi all,

I'm trying to use the Funsat library. One of its data types is CNF:

data CNF = CNF {
 numVars :: Int
 numClauses :: Int
 clauses :: Set Clause
}

I have a list of clauses, but I'm getting an error when converting such a list 
to a Set. Using the fromList function, the ghc compiler reports that the 
fromList function is not applicable to literals. 

type Clause = [Lit] 

newtype Lit = L {
 unLit :: Int
}

So, my question is: How can I solve this problem?

Thanks in advance,

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


[Haskell-cafe] Error building Sdf2Haskell

2009-01-12 Thread rodrigo.bonifacio
Hi all,
I'm trying to build the Sdf2Haskell library. However, I've got the following problem:
Making all in generatorlocate: illegal option -- nusage: locate [-0Scims] [-l limit] [-d database] pattern ...default database: `/var/db/locate.database' or $LOCATE_PATHmake Sdf.tbllocate: illegal option -- nusage: locate [-0Scims] [-l limit] [-d database] pattern ...default database: `/var/db/locate.database' or $LOCATE_PATHmake[2]: `Sdf.tbl' is up to date.make Sdf.hslocate: illegal option -- nusage: locate [-0Scims] [-l limit] [-d database] pattern ...default database: `/var/db/locate.database' or $LOCATE_PATHmake[2]: `Sdf.hs' is up to date.make SyntaxATermConvertibleInstances.hslocate: illegal option -- nusage: locate [-0Scims] [-l limit] [-d database] pattern ...default database: `/var/db/locate.database' or $LOCATE_PATHmake[2]: `SyntaxATermConvertibleInstances.hs' is up to date.ghc -fglasgow-exts -fallow-overlapping-instances -fallo
 w-undecidable-instances -package data -package lang -i/Users/rbonifacio/tmp/strafunski/Sdf2Haskell-2.3/../StrategyLib/library:/Users/rbonifacio/tmp/strafunski/Sdf2Haskell-2.3/../StrategyLib/models/drift-default: -package util -i/Users/rbonifacio/tmp/strafunski/Sdf2Haskell-2.3/../ATermLib/library:/Users/rbonifacio/tmp/strafunski/Sdf2Haskell-2.3/../StrategyLib/examples/haskell: --make Sdf2Haskell.hs -o Sdf2Haskellcommand line: unknown package: datamake[1]: *** [Sdf2Haskell] Error 1make: *** [all-recursive] Error 1
I guess that the main problem is the *unknown data package*. Does anybody know where can I find such a package?
The version of GHC installed in my environment is 6.8.3.
Thanks in advance.
Rodrigo
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] data, util, and lang packages

2009-01-12 Thread rodrigo.bonifacio
Hi all, I'm trying to build a library whose configuration process requires the data, util, and lang packages. I guess that these are *deprecated* packages, since the library is said to be ghc 6.4.1 compliant.
Which packages should I use instead?
Where can I find such packages (if they are not deprecated)
Thanks in advance.
Rodrigo.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] A pattern type signature cannot bind scoped type variables `t'

2009-01-12 Thread rodrigo.bonifacio
Hi all,
I'm trying to build a library that has the following code:
hasTypeOf (TermRep (dx,_,_)) (x::t) = ((fromDynamic dx)::Maybe t)
 
When I try to compile with ghc-6.8.3 I got the following error:
../../StrategyLib/models/drift-default//TermRep.hs:63:30: A pattern type signature cannot bind scoped type variables `t' unless the pattern has a rigid type context In the pattern: x :: t In the definition of `hasTypeOf': hasTypeOf (TermRep (dx, _, _)) (x :: t) = ((fromDynamic dx) :: Maybe t)
 
How can I solve this problem? Is there any option to ignore this erro when compiling with ghc-6.8.3?
Thanks for any help.
Rodrigo.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Getting module functions

2008-07-11 Thread rodrigo.bonifacio
Hi all,

Is there any function that can be used for retrieving the exposed functions of 
a given module?

Thanks,

Rodrigo.

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


[Haskell-cafe] Mutual recursive data types

2008-04-29 Thread rodrigo.bonifacio
Hi all,

I have the following data types:

type Id = String
type Action = String
type State = String
type Response = String

data Scenario = Scenario Description [Step]
data Step = Step Id Scenario Action State Response

So, there is a mutual recursion between Scenario and Step. Now, consider the 
following function:

xmlScenario2Scenario :: XmlScenario - Scenario
xmlScenario2Scenario (XmlScenario description steps) =
 Scenario  description [xmlStep2Step x | x -steps]

How can I send scenario as an argument for xmlStep2Step?

I've tried let and where but I get in a loop.

Thanks a lot,

Rodrigo.



---
Rodrigo Bonifácio de Almeida
Universidade Católica de Brasília
 - Grupo de Engenharia de Software
 - JavaComBr (www.ucb.br/java)

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


Re: [Haskell-cafe] Processing XML with HXT

2008-04-23 Thread rodrigo.bonifacio
Hi Uwe Schmidt, thanks a lot.

Just one more question, I didn't find any example describing how to get the 
text information of a XML element in the picklers tutorial. So, if the use case 
element is described as follwing:

useCase
   idUC_01/id
   nameOpening .../name
   descriptionThis use case describes how.../description
/useCase

How can I set the id, name and desription of a use case?

-- use case data type
data UseCaseModel = UCM Name [UseCase]
data UseCase = UseCase Id Name Description deriving (Show)

-- I tried the following picler implementation
-- but I think that it is not correct.
instance XmlPickler UseCase where
xpickle = xpUseCase

xpUseCase :: PU  UseCase
xpUseCase =
xpElem useCase $
xpWrap ( \ (i, n, d) - UseCase i n d,
\t - (ucId t, name t, description t))  $
   (xpTriple (xpElem id xpText)
 (xpElem name xpText)
 (xpElem description xpText))

 Hi Rodrigo,

  I´m just starting with HXT. My question is, how can I expose a use case 
  from the main function below (the XmlPickler for UseCase has been already 
  defined):
 
  main :: IO ()
  main = do
runX ( xunpickleDocument xpUseCase [ (a_validate,v_0) ],  uc.xml )
return ()
 
  For example, if I just want to show the use case contents, how can I call 
  show for a retrived use case.

 -

 1. version

 main :: IO ()
 main = do
[x] - runX ( xunpickleDocument xpUseCase [ (a_validate,v_0) ],  
 uc.xml )
print x
return ()

 x is processed outside the arrow

 -
 2. version

 main :: IO ()
 main = do
runX ( xunpickleDocument xpUseCase [ (a_validate,v_0) ],  uc.xml
   
   arrIO print
 )
return ()

 x is processed within an arrow by lifting the print function to then arrow 
 level.

 

 There is a new wiki page about picklers
 http://www.haskell.org/haskellwiki/HXT/Conversion_of_Haskell_data_from/to_XML

 Cheers,

   Uwe

 --

 Uwe Schmidt
 Web: http://www.fh-wedel.de/~si/


---
Rodrigo Bonifácio de Almeida
Universidade Católica de Brasília
 - Grupo de Engenharia de Software
 - JavaComBr (www.ucb.br/java)

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


[Haskell-cafe] Processing XML with HXT

2008-04-22 Thread rodrigo.bonifacio
Hi all,

I´m just starting with HXT. My question is, how can I expose a use case from 
the main function below (the XmlPickler for UseCase has been already defined):

main :: IO ()
main = do
  runX ( xunpickleDocument xpUseCase [ (a_validate,v_0) ],  uc.xml )
  return ()

For example, if I just want to show the use case contents, how can I call 
show for a retrived use case.

Thanks in advance.

Rodrigo.

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


[Haskell-cafe] Installing HaXml

2008-04-15 Thread rodrigo.bonifacio
Hi all,

I've tried to install HaXml as explained in the documentation:

 runhaskell Setup.hs configure

However, I get as response:

dyld: Library not loaded: GNUreadline.framework/Versions/A/GNUreadline
  Referenced from: /usr/local/bin/runhaskell
  Reason: image not found
Trace/BPT trap

Any idea about this problem?

Some comments about my configuration:

Mac/OS Darwin 8.11.1
GHC-6.6
Hugs - Version September 2006

Thanks in advance,

Rodrigo.

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


Re: [Haskell-cafe] QuickCheck

2008-03-17 Thread rodrigo.bonifacio
Hi all,

Is it possible to define a limit for the size of children list bellow?

I've tried:

children - resize (10 (listGen featureGenNormal))

But it didn't work.

Thanks a lot,

Rodrigo.


 Sebastian Sylvan:
  featureGenNormal = do
  id - stringGen
  name - stringGen
  featuretype - arbitrary
  grouptype - arbitrary
  children - arbitrary
  properties - listGen stringGen
  return (Feature id name featuretype grouptype children properties)

 Ryan Ingram wrote:
   Also, you can shorten this significantly with liftM or ap (from 
  Control.Monad):

 True, but in this case I like being able to see meaningful
 names for each parameter of the constructor.


---
Rodrigo Bonifácio de Almeida
Universidade Católica de Brasília
 - Grupo de Engenharia de Software
 - JavaComBr (www.ucb.br/java)

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


[Haskell-cafe] QuickCheck

2008-03-16 Thread rodrigo.bonifacio
Hi all,

I'm trying to use the quick-check library for checking some properties of a 
user defined data type. Bellow the target data type:

data Feature =
 Feature Id Name FeatureType GroupType Children Properties |
 FeatureError

where:

Id = String
Name = String
FeatureType = int
GroupType = int
Children = [Feature]
Propertyes = [String]


I've written the following quick-check property:

prop_AlternativeFeature :: Feature - Feature - QuickCheck.Property
prop_AlternativeFeature fm fc = length (children fc) == 0 == length  
(checkAlternativeFeature fm fc)  0

When I try to check such property, the result is:

ERROR ./EshopModelChecking.hs:11 - Type error in instance member binding
*** Term   : arbitrary
*** Type   : Feature
*** Does not match : Gen Feature

I think that I need to write some arbitrary or generator functions, but I 
didn't realize how to do that with the availalble quick-checking documentation.

Any help will be welcome.

Thanks in advance.

Rodrigo.

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


Re: [Haskell-cafe] QuickCheck

2008-03-16 Thread rodrigo.bonifacio
Dear Sebastian Sylvan,

Thanks for your datailed answer. It saved me a lot of time.

Best regards,

Rodrigo.

 On Sun, Mar 16, 2008 at 5:42 PM, rodrigo.bonifacio 
 [EMAIL PROTECTED] wrote:

  Hi all,
 
  I'm trying to use the quick-check library for checking some properties of
  a user defined data type. Bellow the target data type:
 
  data Feature =
   Feature Id Name FeatureType GroupType Children Properties |
   FeatureError
 
  where:
 
  Id = String
  Name = String
  FeatureType = int
  GroupType = int
  Children = [Feature]
  Propertyes = [String]
 
 
  I've written the following quick-check property:
 
  prop_AlternativeFeature :: Feature - Feature - QuickCheck.Property
  prop_AlternativeFeature fm fc = length (children fc) == 0 == length
   (checkAlternativeFeature fm fc)  0
 
  When I try to check such property, the result is:
 
  ERROR ./EshopModelChecking.hs:11 - Type error in instance member binding
  *** Term   : arbitrary
  *** Type   : Feature
  *** Does not match : Gen Feature
 
  I think that I need to write some arbitrary or generator functions, but I
  didn't realize how to do that with the availalble quick-checking
  documentation.
 
  Any help will be welcome.
 
 
 You use the available functions to build up a generator for your data type.

 First, let's give the instanc itself. For this I'm just going to use the
 frequency function to use featureGenNormal five times more often than
 return FeatureError. This means that will get a FeatureError every now and
 then, but mostly you'll get featureGenNormal (see below). You can change
 these frequences, of course.

 instance Arbitrary Feature where
 arbitrary = do
 frequency [ (5, featureGenNormal),  (1, return FeatureError) ]

 In order to write featureGenNormal, we need to be able to generate random
 values of each of the parts of the data type. Often these types will already
 have Arbitrary instances, so generating an isntance for your type is quite
 often just a matter of calling arbitrary for each component, and then
 returning a datatype. However, there is no Arbitrary instance for String,
 which is a bit annoying, so let's write our own generator for strings.

 First a generator for a single letter:

 letterGen = oneof $ map return $ ['a'..'z'] ++ ['A'..'Z']

 Then a combinator for generating a list of values given a generator for a
 single value:

 listGen :: Gen a - Gen [a]
 listGen g = do
 x - g
 xs - frequency [ (1, return []), (10, listGen g) ]
 return (x:xs)

 And then we use this to build our stringGen generator.

 stringGen :: Gen String
 stringGen = listGen letterGen

 Now, we have all we need to write the featureGenNormal generator:

 featureGenNormal = do
 id - stringGen
 name - stringGen
 featuretype - arbitrary
 grouptype - arbitrary
 children - arbitrary
 properties - listGen stringGen
 return (Feature id name featuretype grouptype children properties)


 Note that we use arbitrary to generate the list of children recursively.

 --
 Sebastian Sylvan
 +44(0)7857-300802
 UIN: 44640862


---
Rodrigo Bonifácio de Almeida
Universidade Católica de Brasília
 - Grupo de Engenharia de Software
 - JavaComBr (www.ucb.br/java)

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


[Haskell-cafe] Basic question....

2007-08-17 Thread rodrigo.bonifacio
Hi all.

I want to create the following polymorphic type (EnvItem) that we can apply two 
functions (envKey and envValue). I tried the following:

 type Key = String

 data EnvItem a = EnvItem (Key, a)

 envKey :: EnvItem (Key, a) - String
 envKey EnvItem (key, value) = key

 envValue :: EnvValue(Key, a) - a
 envValue EnvItem (key, value) = value

But this is resulting in the error: [Constructor EnvItem must have exactly 1 
argument in pattern]

I think this is a very basic problem, but I don't know what is wrong.

Regards,

Rodrigo.

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


[Haskell-cafe] Defining new operators

2007-08-10 Thread rodrigo.bonifacio
Hi all,

Given the follwing function:

 owner :: Step - Scenario
 owner (Step id scenario action state response) = scenario

Is it possible to define the owner function in such way that I can write 
x.owner (returning the scenario related with the Step x)?

Thanks in advance,

Rodrigo.

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


[Haskell-cafe] New Eq instance

2007-08-09 Thread rodrigo.bonifacio
Hello,

I had defined the follwing data type:

data Step = Step Id Scenario Action State Response

How can I define Step as an Eq Instance, in such way that two steps are 
equals if they have the same Id (Id is defined as a synonimous for the String 
type).

I tried the following code, but something is wrong

instance Eq Step where
  Step id1 scenario1 action1 state1 response1 == Step id2 scenario2 action2 
state2 response2 = id == id
  _ == _ = False

ps.: sorry, this kind of basic question can be sent to this list?

Thanks in advance.

Rodrigo.

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


[Haskell-cafe] mutually recursive types

2007-08-08 Thread rodrigo.bonifacio
Hi, I am learning the haskell programming language and had tried to define the 
following types:

type Scenario = (String, String, [Step])
type Step = (String, Scenario, String, String, String)

Notice that Scenario depends on a list of steps and Step has a dependence with 
scenario. I know that this is a kind of bad smell in Haskell, are there 
any pattern or language idiom to deal with cyclical dependences?

Regards,

Rodrigo.





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


[Haskell-cafe] Defining new operators

2007-08-08 Thread rodrigo.bonifacio
Hello,

I have created the following function:

dist :: String - [[String]] - [[String]]
dist x  y = [ x:e | e-y ]

eg.:

dist 1M [[], [2M], [2M, 3M]] = [[1M],[1M,2M],[1M,2M, 3M]]

How can I create an operator that perform the same function as dist? I want to 
write something like:

1M ++ [[], [2M], [2M, 3M]]

Thanks in advance.

Rodrigo.


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