Skip to content

Commit

Permalink
Allow use of prime symbol in type names.
Browse files Browse the repository at this point in the history
  • Loading branch information
garyb committed May 27, 2016
1 parent 83be9a5 commit 0619bd5
Show file tree
Hide file tree
Showing 5 changed files with 49 additions and 19 deletions.
20 changes: 20 additions & 0 deletions examples/passing/PrimedTypeName.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
module Main (T, T', T'', T''', main) where

import Prelude
import Control.Monad.Eff.Console (log)

data T a = T
type T' = T Unit

data T'' = TP

foreign import data T''' *

instance eqTEq T'' where
eq _ _ = true

type A' a b = b a

infixr 4 type A' as ↫

main = log "Done"
9 changes: 9 additions & 0 deletions src/Language/PureScript/Parser/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,9 +16,18 @@ import Language.PureScript.Parser.State

import qualified Text.Parsec as P

-- |
-- Parse a general proper name.
--
properName :: TokenParser (ProperName a)
properName = ProperName <$> uname

-- |
-- Parse a proper name for a type.
--
typeName :: TokenParser (ProperName 'TypeName)
typeName = ProperName <$> tyname

-- |
-- Parse a module name
--
Expand Down
10 changes: 5 additions & 5 deletions src/Language/PureScript/Parser/Declarations.hs
Original file line number Diff line number Diff line change
Expand Up @@ -66,7 +66,7 @@ kindedIdent = (, Nothing) <$> identifier
parseDataDeclaration :: TokenParser Declaration
parseDataDeclaration = do
dtype <- (reserved "data" *> return Data) <|> (reserved "newtype" *> return Newtype)
name <- indented *> properName
name <- indented *> typeName
tyArgs <- many (indented *> kindedIdent)
ctors <- P.option [] $ do
indented *> equals
Expand All @@ -80,7 +80,7 @@ parseTypeDeclaration =

parseTypeSynonymDeclaration :: TokenParser Declaration
parseTypeSynonymDeclaration =
TypeSynonymDeclaration <$> (reserved "type" *> indented *> properName)
TypeSynonymDeclaration <$> (reserved "type" *> indented *> typeName)
<*> many (indented *> kindedIdent)
<*> (indented *> equals *> noWildcards parsePolyType)

Expand Down Expand Up @@ -108,7 +108,7 @@ parseValueDeclaration = do

parseExternDeclaration :: TokenParser Declaration
parseExternDeclaration = reserved "foreign" *> indented *> reserved "import" *> indented *>
(ExternDataDeclaration <$> (reserved "data" *> indented *> properName)
(ExternDataDeclaration <$> (reserved "data" *> indented *> typeName)
<*> (indented *> doubleColon *> parseKind)
<|> (do ident <- parseIdent
ty <- indented *> doubleColon *> noWildcards parsePolyType
Expand All @@ -132,7 +132,7 @@ parseFixityDeclaration = do
where
typeFixity fixity =
TypeFixity fixity
<$> (reserved "type" *> parseQualified properName)
<$> (reserved "type" *> parseQualified typeName)
<*> (reserved "as" *> parseOperator)
valueFixity fixity =
ValueFixity fixity
Expand Down Expand Up @@ -169,7 +169,7 @@ parseDeclarationRef =
<|> (TypeOpRef <$> (indented *> reserved "type" *> parens parseOperator))
where
parseTypeRef = do
name <- properName
name <- typeName
dctors <- P.optionMaybe $ parens (symbol' ".." *> pure Nothing <|> Just <$> commaSep properName)
return $ TypeRef name (fromMaybe (Just []) dctors)

Expand Down
27 changes: 14 additions & 13 deletions src/Language/PureScript/Parser/Lexer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,8 +41,8 @@ module Language.PureScript.Parser.Lexer
, commaSep1
, lname
, qualifier
, tyname
, uname
, uname'
, mname
, reserved
, symbol
Expand Down Expand Up @@ -213,8 +213,9 @@ parseToken = P.choice
, P.try $ P.char '_' *> P.notFollowedBy identLetter *> pure Underscore
, HoleLit <$> P.try (P.char '?' *> P.many1 identLetter)
, LName <$> parseLName
, do uName <- parseUName
(guard (validModuleName uName) >> Qualifier uName <$ P.char '.') <|> pure (UName uName)
, parseUName >>= \uName ->
(guard (validModuleName uName) >> Qualifier uName <$ P.char '.')
<|> pure (UName uName)
, Symbol <$> parseSymbol
, CharLiteral <$> parseCharLiteral
, StringLiteral <$> parseStringLiteral
Expand All @@ -226,7 +227,7 @@ parseToken = P.choice
parseLName = (:) <$> identStart <*> P.many identLetter

parseUName :: P.Parsec String u String
parseUName = (:) <$> P.upper <*> P.many uidentLetter
parseUName = (:) <$> P.upper <*> P.many identLetter

parseSymbol :: P.Parsec String u String
parseSymbol = P.many1 symbolChar
Expand All @@ -237,9 +238,6 @@ parseToken = P.choice
identLetter :: P.Parsec String u Char
identLetter = P.alphaNum <|> P.oneOf "_'"

uidentLetter :: P.Parsec String u Char
uidentLetter = P.alphaNum <|> P.char '_'

symbolChar :: P.Parsec String u Char
symbolChar = P.satisfy isSymbolChar

Expand Down Expand Up @@ -430,6 +428,12 @@ reserved s = token go P.<?> show s

uname :: TokenParser String
uname = token go P.<?> "proper name"
where
go (UName s) | validUName s = Just s
go _ = Nothing

tyname :: TokenParser String
tyname = token go P.<?> "type name"
where
go (UName s) = Just s
go _ = Nothing
Expand All @@ -440,12 +444,6 @@ mname = token go P.<?> "module name"
go (UName s) | validModuleName s = Just s
go _ = Nothing

uname' :: String -> TokenParser ()
uname' s = token go P.<?> show s
where
go (UName s') | s == s' = Just ()
go _ = Nothing

symbol :: TokenParser String
symbol = token go P.<?> "symbol"
where
Expand Down Expand Up @@ -496,6 +494,9 @@ identifier = token go P.<?> "identifier"
validModuleName :: String -> Bool
validModuleName s = '_' `notElem` s

validUName :: String -> Bool
validUName s = '\'' `notElem` s

-- |
-- A list of purescript reserved identifiers
--
Expand Down
2 changes: 1 addition & 1 deletion src/Language/PureScript/Parser/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,7 @@ parseTypeVariable = do
return $ TypeVar ident

parseTypeConstructor :: TokenParser Type
parseTypeConstructor = TypeConstructor <$> parseQualified properName
parseTypeConstructor = TypeConstructor <$> parseQualified typeName

parseForAll :: TokenParser Type
parseForAll = mkForAll <$> ((reserved "forall" <|> reserved "") *> P.many1 (indented *> identifier) <* indented <* dot)
Expand Down

0 comments on commit 0619bd5

Please sign in to comment.