Skip to content
Snippets Groups Projects
Commit 216bfb01 authored by Will Partain's avatar Will Partain
Browse files

[project @ 1996-07-26 20:58:52 by partain]

Final changes for 2.01
parent 5eb1c77c
No related merge requests found
Showing
with 64 additions and 31 deletions
......@@ -55,8 +55,8 @@
(modify-syntax-entry ?\f "> b" haskell-mode-syntax-table)
(modify-syntax-entry ?\n "> b" haskell-mode-syntax-table)
(modify-syntax-entry ?\" "\"" haskell-mode-syntax-table)
(modify-syntax-entry ?\' "_" haskell-mode-syntax-table)
(modify-syntax-entry ?_ "_" haskell-mode-syntax-table)
(modify-syntax-entry ?\' "w" haskell-mode-syntax-table)
(modify-syntax-entry ?_ "w" haskell-mode-syntax-table)
(modify-syntax-entry ?\\ "." haskell-mode-syntax-table)
(modify-syntax-entry ?\( "()" haskell-mode-syntax-table)
(modify-syntax-entry ?\) ")(" haskell-mode-syntax-table)
......@@ -81,8 +81,6 @@
(setq comment-column 40)
(make-local-variable 'comment-indent-function)
(setq comment-indent-function 'haskell-comment-indent)
;(make-local-variable 'font-lock-keywords)
;(setq font-lock-keywords haskell-literate-font-lock-keywords)
)
(defun haskell-mode ()
......@@ -106,6 +104,8 @@ M-TAB toggles the state of the bird track on the current-line.
Entry to this mode calls haskell-mode-hook and haskell-literate-mode-hook."
(interactive)
(haskell-vars)
(make-local-variable 'font-lock-keywords)
(setq font-lock-keywords haskell-literate-font-lock-keywords)
(setq major-mode 'haskell-literate-mode)
(setq mode-name "Literate Haskell")
(use-local-map haskell-literate-mode-map)
......@@ -190,12 +190,13 @@ Entry to this mode calls haskell-mode-hook and haskell-literate-mode-hook."
(list
'("^[^>\n].*$" . font-lock-comment-face)
(concat "\\b\\("
(mapconcat 'identity
'("case" "class" "data" "default" "deriving" "else" "hiding"
"if" "import" "in" "infix" "infixl" "infixr" "instance"
"interface" "let" "module" "of" "renaming" "then" "to"
"type" "where")
"\\|")
"\\)\\b")
(mapconcat 'identity
'("case" "class" "data" "default" "deriving" "else"
"hiding" "if" "import" "in" "infix" "infixl"
"infixr" "instance" "interface" "let" "module"
"of" "renaming" "then" "to" "type" "where")
"\\|")
"\\)\\b")
; '("(\\|)\\|\\[\\|\\]\\|,\\|[\\\\!$#^%&*@~?=-+<>.:]+" . font-lock-function-name-face)
))
......@@ -25,11 +25,12 @@ import DsUtils
import MatchCon ( matchConFamily )
import MatchLit ( matchLiterals )
import FieldLabel ( allFieldLabelTags, fieldLabelTag )
import Id ( idType, mkTupleCon,
import FieldLabel ( FieldLabel {- Eq instance -} )
import Id ( idType, mkTupleCon, dataConFieldLabels,
dataConArgTys, recordSelectorFieldLabel,
GenId{-instance-}
)
import Name ( Name {--O only-} )
import PprStyle ( PprStyle(..) )
import PprType ( GenType{-instance-}, GenTyVar{-ditto-} )
import PrelVals ( pAT_ERROR_ID )
......@@ -337,12 +338,12 @@ tidy1 v (RecPat con_id pat_ty rpats) match_result
-- Boring stuff to find the arg-tys of the constructor
(_, inst_tys, _) = {-trace "Match.getAppDataTyConExpandingDicts" $-} getAppDataTyConExpandingDicts pat_ty
con_arg_tys' = dataConArgTys con_id inst_tys
tagged_arg_tys = con_arg_tys' `zip` allFieldLabelTags
tagged_arg_tys = con_arg_tys' `zip` (dataConFieldLabels con_id)
-- mk_pat picks a WildPat of the appropriate type for absent fields,
-- and the specified pattern for present fields
mk_pat (arg_ty, tag) = case [pat | (sel_id,pat,_) <- rpats,
fieldLabelTag (recordSelectorFieldLabel sel_id) == tag
mk_pat (arg_ty, lbl) = case [pat | (sel_id,pat,_) <- rpats,
recordSelectorFieldLabel sel_id == lbl
] of
(pat:pats) -> ASSERT( null pats )
pat
......
......@@ -7,5 +7,4 @@ SUBDIRS = reader \
deSugar \
printing \
ccall \
deriving \
bugs
deriving
......@@ -2,7 +2,7 @@
module Test where
import PreludeGlaIO
import PreludeGlaST
-- simple functions
......
......@@ -2,20 +2,20 @@
module Test where
import PreludeGlaIO
import PreludeGlaST
-- Test returning results
a :: PrimIO _MallocPtr
a :: PrimIO ForeignObj
a = _ccall_ a
b :: PrimIO _StablePtr
b :: PrimIO StablePtr
b = _ccall_ b
-- Test taking arguments
c :: _MallocPtr -> PrimIO Int
c :: ForeignObj -> PrimIO Int
c x = _ccall_ c x
d :: _StablePtr -> PrimIO Int
d :: StablePtr -> PrimIO Int
d x = _ccall_ d x
--!!! cc003 -- ccall with unresolved polymorphism (should fail)
module Test where
import PreludeGlaIO
import PreludeGlaST
fubar :: PrimIO Int
fubar = ccall f `seqPrimIO` ccall b
......
--!!! cc004 -- ccall with synonyms, polymorphic type variables and user type variables.
module Test where
import PreludeGlaIO
import PreludeGlaST
-- Since I messed up the handling of polymorphism originally, I'll
-- explicitly test code with UserSysTyVar (ie an explicit polymorphic
......
......@@ -3,6 +3,9 @@
-- do all the right types get stuck on all the
-- Nils and Conses?
module ShouldSucceed where
f x = [[], []]
g x = ([], [], [])
--!!! ds026 -- classes -- incl. polymorphic method
module ShouldSucceed where
class Foo a where
op :: a -> a
......
--!!! ds028: failable pats in top row
module ShouldSucceed where
-- when the first row of pats doesn't have convenient
-- variables to grab...
......
module ShouldSucceed where
foldPair :: (a->a->a,b->b->b) -> (a,b) -> [(a,b)] -> (a,b)
foldPair fg ab [] = ab
foldPair fg@(f,g) ab ((a,b):abs) = (f a u,g b v)
......
--!!! recursive funs tangled in an AbsBind
module ShouldSucceed where
flatten :: Int -- Indentation
-> Bool -- True => just had a newline
-> Float -- Current seq to flatten
......
--!!! AbsBinds with tyvars, no dictvars, but some dict binds
--
module ShouldSucceed where
f x y = (fst (g y x), x+(1::Int))
g x y = (fst (f x y), y+(1::Int))
--!!! make sure correct type applications get put in
--!!! when (:) is saturated.
module ShouldSucceed where
f = (:)
--!!! canonical weird example for "deriving"
module ShouldSucceed where
data X a b
= C1 (T a)
| C2 (Y b)
| C3 (X b a)
deriving Text
deriving (Read, Show)
data Y b
= D1
| D2 (X Int b)
deriving Text
deriving (Read, Show)
data T a
= E1
instance Eq a => Text (T a) where
instance Eq a => Show (T a) where
showsPrec = error "show"
instance Eq a => Read (T a) where
readsPrec = error "read"
module ShouldSucceed where
data Z a b
= C1 (T a)
| C2 (Z [a] [b])
deriving Text
deriving (Show, Read)
data T a
= E1
instance Eq a => Text (T a) where
instance Eq a => Show (T a) where
showsPrec = error "show"
instance Eq a => Read (T a) where
readsPrec = error "read"
--!!! This is the example given in TcDeriv
--
module ShouldSucceed where
data T a b
= C1 (Foo a) (Bar b)
| C2 Int (T b a)
......
--!!! simple example of deriving Ord (and, implicitly, Eq)
--
module ShouldSucceed where
data Foo a b
= C1 a Int
| C2 b Double
......
--!!! simple example of deriving Enum
--
module ShouldSucceed where
data Foo = Foo1 | Foo2 | Foo3 | Foo4 | Foo5 | Foo6 | Foo7 | Foo8
deriving Enum
--!!! simple examples of deriving Ix
--
module ShouldSucceed where
import Ix
data Foo = Foo1 | Foo2 | Foo3 | Foo4 | Foo5 | Foo6 | Foo7 | Foo8
deriving Ix
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment