module ModuleBase where import TermParser ( lexer ) import InOut ( Input, Output, input, output ) import qualified Text.ParserCombinators.Parsec.Token as Token import Text.PrettyPrint.HughesPJ ( text ) import qualified System.Path as Path import Control.Applicative ( liftA2, (<$>) ) import qualified Data.Foldable as Fold newtype Name = Name {deconsName :: String} deriving (Eq, Ord, Show) instance Input Name where input = Name <$> Token.identifier lexer instance Output Name where output (Name n) = text n mainName :: Name mainName = Name "Main" noName :: Name noName = Name "" tellName :: Name -> String tellName (Name n) = "module " ++ n newtype Version = Version Integer deriving (Eq, Ord, Show) noVersion :: Maybe Version noVersion = Nothing initVersion :: Version initVersion = Version 0 nextVersion :: Version -> Version nextVersion (Version k) = Version (k+1) equalVersion :: Maybe Version -> Maybe Version -> Bool equalVersion u v = Fold.or $ liftA2 (==) u v data Source = File Path.AbsFile | Editor Name deriving (Show) maybeEditor :: Source -> Maybe Name maybeEditor (File _) = Nothing maybeEditor (Editor name) = Just name formatSource :: Source -> String formatSource (File path) = Path.toString path formatSource (Editor name) = deconsName name