about GADTs on ghci

i have seen the documents in http://www.haskell.org/haskellwiki/Generalised_algebraic_datatype but i can not run the following code on ghci ex: data Term x where K :: Term (a -> b -> a) S :: Term ((a -> b -> c) -> (a -> b) -> a -> c) Const :: a -> Term a (:@) :: Term (a -> b) -> (Term a) -> Term b infixl 6 :@ could any tell me how to run the code? Thanks a lot

On Nov 27, 2007 12:57 PM, Yu-Teh Shen
i have seen the documents in http://www.haskell.org/haskellwiki/Generalised_algebraic_datatype but i can not run the following code on ghci
ex:
data Term x where K :: Term (a -> b -> a) S :: Term ((a -> b -> c) -> (a -> b) -> a -> c) Const :: a -> Term a (:@) :: Term (a -> b) -> (Term a) -> Term b infixl 6 :@
could any tell me how to run the code?
Put it in a file (eg ski.hs), and run: % ghci -fglasgow-exts ski.hs You cannot enter it directly into ghci; you can't define new data types interactively. You can also put the line {-# OPTIONS_GHC -fglasgow-exts #-} At the top, to turn on glasgow extensions whenever GHC compiles this file. Luke

Thanks.
So GADT provide us to generic type to include all types, is it right?
ex:
data Parser tok a where
Zero :: Parser tok ()
One :: Parser tok ()
Check :: (tok -> Bool) -> Parser tok tok
Satisfy :: ([tok] -> Bool) -> Parser tok [tok]
Push :: tok -> Parser tok a -> Parser tok a
Plus :: Parser tok a -> Parser tok b -> Parser tok (Either a b)
Times :: Parser tok a -> Parser tok b -> Parser tok (a,b)
Star :: Parser tok a -> Parser tok [a]
otherwise we need to write something like this (separate the type and
functions):
newtype Parser tok a
zero::Parser tok ()
one :: Parser tok ()
...
On Nov 27, 2007 2:16 PM, Luke Palmer
On Nov 27, 2007 12:57 PM, Yu-Teh Shen
wrote: i have seen the documents in http://www.haskell.org/haskellwiki/Generalised_algebraic_datatype but i can not run the following code on ghci
ex:
data Term x where K :: Term (a -> b -> a) S :: Term ((a -> b -> c) -> (a -> b) -> a -> c) Const :: a -> Term a (:@) :: Term (a -> b) -> (Term a) -> Term b infixl 6 :@
could any tell me how to run the code?
Put it in a file (eg ski.hs), and run:
% ghci -fglasgow-exts ski.hs
You cannot enter it directly into ghci; you can't define new data types interactively.
You can also put the line
{-# OPTIONS_GHC -fglasgow-exts #-}
At the top, to turn on glasgow extensions whenever GHC compiles this file.
Luke

Luke Palmer wrote:
You can also put the line
{-# OPTIONS_GHC -fglasgow-exts #-}
At the top, to turn on glasgow extensions whenever GHC compiles this file.
I was under the impression that it's better to use the LANGUAGE pragma rather than the catch-all Glasgow-exts option. However, I can't actually find a language option for GADTs... somebody care to clarify?

On Tue, Nov 27, 2007 at 07:11:27PM +0000, Andrew Coppin wrote:
I was under the impression that it's better to use the LANGUAGE pragma rather than the catch-all Glasgow-exts option. However, I can't actually find a language option for GADTs... somebody care to clarify?
In GHC 6.8.1 it's "GADTs". "ghc --supported-languages" lists them all. Thanks Ian

On Tue, 2007-11-27 at 19:11 +0000, Andrew Coppin wrote:
Luke Palmer wrote:
You can also put the line
{-# OPTIONS_GHC -fglasgow-exts #-}
At the top, to turn on glasgow extensions whenever GHC compiles this file.
I was under the impression that it's better to use the LANGUAGE pragma rather than the catch-all Glasgow-exts option. However, I can't actually find a language option for GADTs... somebody care to clarify?
{-# LANGUAGE GADTs #-} :) (really!)
participants (5)
-
Andrew Coppin
-
Ian Lynagh
-
Luke Palmer
-
Thomas Schilling
-
Yu-Teh Shen