confusion about parameterized types.

Here is a record I defined
module PrepData where data Value = Cost Int | ID Int type Tname = String data StudentsOrActivites = Students String | Activities String data Table soa v = PopTable { tableName :: Tname , tableColumns :: [(soa, v)] } deriving (Show, Read)
I'm trying to define another record in terms of Table
data ProcessData = ProcessData { flatfile :: String , processfunc :: String ->
what I would like processfunc to be is a function that takes a String and returns a Table. The type variables are tripping me up. Could someone help me work out the syntax, and the clarifying of my intent?

Okay, ski (of Freenode fame) helped me with the first problem. Now I need to figure out how to use specific types. given
module Main where import System.Environment import PrepData
data ProcessData = ProcessData { flatfile :: String , processfunc :: [String] -> Table StudentsOrActivities Value }
main = undefined
and
module PrepData where data Value = Cost Int | ID Int type Tname = String data StudentsOrActivities = Students String | Activities String data Table soa v = PopTable { tableName :: Tname , tableColumns :: [(soa, v)] } deriving (Show, Read)
popStudents :: [String] -> Table Students ID popStudents flatFile = undefined
is it clear what I am trying to do in popStudents? here's the error I get PrepData.lhs:10:35: Not in scope: type constructor or class `Students' PrepData.lhs:10:44: Not in scope: type constructor or class `ID'

If I understand you correctly, you want to have a string of data about students and activities? I think it would look better like this: data Record = Student { name :: String, id :: Int} | Activity { name :: String, cost :: Int } deriving (Show, Read) then you could convert your data to a string and back like this, line by line in ghci:
let myMixedData = [Student "John" 0, Student "Greg" 1, Activity "tennis" 35]
Type of myMixedData is [Record] -- a list of records.
let flatFile = show myMixedData
flatFile is a String -- something textual that you can write to a file for example.
let myMixedData2 = read flatFile :: [Record]
Now the string is read back to a list of records, like it was before. Note that when you derive a Read instance for your data and use the 'read' function, you have to specifie the type of the result, otherwise the function won't know, what kind of data you want out of it.
here's the error I get PrepData.lhs:10:35: Not in scope: type constructor or class `Students' PrepData.lhs:10:44: Not in scope: type constructor or class `ID'
You get this error, because Students and ID are data constructors -- functions that take a value and return another. If you do ":t Students" in ghci, when your module is loaded, you would get "Students :: String -> StudentsOrActivities", which means that Student takes a String as an argument and returns data of a type StudentsOrActivities. So StudentsOrActivities and Value are types, but Students and ID are data constructors -- functions that make a value of their appropriate types. So for your functions "popStudents" signature would have to look like this:
popStudents :: String -> Table StudentsOrActivities Value and it doesn't matter if it only returns a Table with students' names and ids. This is why I had declared my Record type with the students name and id together -- so someone coudldn't write something like this with the Table data: Table "mess" [(Students "Tom", Cost 100)] which is a valid Table data, but dosn't make sense unless you plan to represent the cost of some people too.
Ask on, if something was unclear.
Markus
On Mon, Aug 30, 2010 at 7:54 PM, Michael Litchard
Okay, ski (of Freenode fame) helped me with the first problem. Now I need to figure out how to use specific types.
given
module Main where import System.Environment import PrepData
data ProcessData = ProcessData { flatfile :: String , processfunc :: [String] -> Table StudentsOrActivities Value }
main = undefined
and
module PrepData where data Value = Cost Int | ID Int type Tname = String data StudentsOrActivities = Students String | Activities String data Table soa v = PopTable { tableName :: Tname , tableColumns :: [(soa, v)] } deriving (Show, Read)
popStudents :: [String] -> Table Students ID popStudents flatFile = undefined
is it clear what I am trying to do in popStudents?
here's the error I get PrepData.lhs:10:35: Not in scope: type constructor or class `Students'
PrepData.lhs:10:44: Not in scope: type constructor or class `ID' _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

It also occurred to me that, if you want to print or write to file
your data, and read it back, then the deriving of Show and Read
classes is all you need to do -- the the show and read functions are
created for you automatically. This way you don't need the ProcessData
with the string and string-to-data converter function in it -- 'read'
is that function! You just read a string from a file, call read on it
(not forgetting to specify the type), and you have your data.
On Mon, Aug 30, 2010 at 9:11 PM, Markus Läll
If I understand you correctly, you want to have a string of data about students and activities?
I think it would look better like this:
data Record = Student { name :: String, id :: Int} | Activity { name :: String, cost :: Int } deriving (Show, Read)
then you could convert your data to a string and back like this, line by line in ghci:
let myMixedData = [Student "John" 0, Student "Greg" 1, Activity "tennis" 35]
Type of myMixedData is [Record] -- a list of records.
let flatFile = show myMixedData
flatFile is a String -- something textual that you can write to a file for example.
let myMixedData2 = read flatFile :: [Record]
Now the string is read back to a list of records, like it was before.
Note that when you derive a Read instance for your data and use the 'read' function, you have to specifie the type of the result, otherwise the function won't know, what kind of data you want out of it.
here's the error I get PrepData.lhs:10:35: Not in scope: type constructor or class `Students' PrepData.lhs:10:44: Not in scope: type constructor or class `ID'
You get this error, because Students and ID are data constructors -- functions that take a value and return another. If you do ":t Students" in ghci, when your module is loaded, you would get "Students :: String -> StudentsOrActivities", which means that Student takes a String as an argument and returns data of a type StudentsOrActivities. So StudentsOrActivities and Value are types, but Students and ID are data constructors -- functions that make a value of their appropriate types.
So for your functions "popStudents" signature would have to look like this:
popStudents :: String -> Table StudentsOrActivities Value and it doesn't matter if it only returns a Table with students' names and ids. This is why I had declared my Record type with the students name and id together -- so someone coudldn't write something like this with the Table data: Table "mess" [(Students "Tom", Cost 100)] which is a valid Table data, but dosn't make sense unless you plan to represent the cost of some people too.
Ask on, if something was unclear.
Markus
On Mon, Aug 30, 2010 at 7:54 PM, Michael Litchard
wrote: Okay, ski (of Freenode fame) helped me with the first problem. Now I need to figure out how to use specific types.
given
module Main where import System.Environment import PrepData
data ProcessData = ProcessData { flatfile :: String , processfunc :: [String] -> Table StudentsOrActivities Value }
main = undefined
and
module PrepData where data Value = Cost Int | ID Int type Tname = String data StudentsOrActivities = Students String | Activities String data Table soa v = PopTable { tableName :: Tname , tableColumns :: [(soa, v)] } deriving (Show, Read)
popStudents :: [String] -> Table Students ID popStudents flatFile = undefined
is it clear what I am trying to do in popStudents?
here's the error I get PrepData.lhs:10:35: Not in scope: type constructor or class `Students'
PrepData.lhs:10:44: Not in scope: type constructor or class `ID' _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Okay, ski (of Freenode fame) helped me with the first problem. Now I need to figure out how to use specific types. given
module Main where import System.Environment import PrepData
data ProcessData = ProcessData { flatfile :: String , processfunc :: [String] -> Table StudentsOrActivities Value }
main = undefined
and
module PrepData where data Value = Cost Int | ID Int type Tname = String data StudentsOrActivities = Students String | Activities String data Table soa v = PopTable { tableName :: Tname , tableColumns :: [(soa, v)] } deriving (Show, Read)
popStudents :: [String] -> Table Students ID popStudents flatFile = undefined
is it clear what I am trying to do in popStudents? here's the error I get PrepData.lhs:10:35: Not in scope: type constructor or class `Students' PrepData.lhs:10:44: Not in scope: type constructor or class `ID'

Students and ID are constructors, not types. You need to change the
type signature from:
popStudents :: [String] -> Table Students ID
to:
popStudents :: [String] -> Table StudentsOrActivities Value
You might want to re-think the way you're doing this though, as I
don't think this is really want you want. Maybe you need to make
Students and Activities seperate types and create some sort of common
class that they can both be instances of? What exactly do they have in
common with each other? If you're just trying to create an abstraction
over a SQL table, you should probably look at the way HSQL or one of
the other SQL libraries handles the issue (usually with a class that
requires a fromSQL function or similar).
-R. Kyle Murphy
--
Curiosity was framed, Ignorance killed the cat.
On Mon, Aug 30, 2010 at 12:55, Michael Litchard
Okay, ski (of Freenode fame) helped me with the first problem. Now I need to figure out how to use specific types.
given
module Main where import System.Environment import PrepData
data ProcessData = ProcessData { flatfile :: String , processfunc :: [String] -> Table StudentsOrActivities Value }
main = undefined
and
module PrepData where data Value = Cost Int | ID Int type Tname = String data StudentsOrActivities = Students String | Activities String data Table soa v = PopTable { tableName :: Tname , tableColumns :: [(soa, v)] } deriving (Show, Read)
popStudents :: [String] -> Table Students ID popStudents flatFile = undefined
is it clear what I am trying to do in popStudents?
here's the error I get PrepData.lhs:10:35: Not in scope: type constructor or class `Students'
PrepData.lhs:10:44: Not in scope: type constructor or class `ID' _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (3)
-
Kyle Murphy
-
Markus Läll
-
Michael Litchard