{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Language.Futhark.Core
( Uniqueness(..)
, StreamOrd(..)
, Commutativity(..)
, locStr
, Name
, nameToString
, nameFromString
, nameToText
, nameFromText
, VName(..)
, baseTag
, baseName
, baseString
, pretty
, defaultEntryPoint
, Int8, Int16, Int32, Int64
, Word8, Word16, Word32, Word64
)
where
import Data.Int (Int8, Int16, Int32, Int64)
import Data.String
import Data.Word (Word8, Word16, Word32, Word64)
import Data.Loc
import qualified Data.Text as T
import Futhark.Util.Pretty
data Uniqueness = Nonunique
| Unique
deriving (Eq, Ord, Show)
instance Semigroup Uniqueness where
(<>) = min
instance Monoid Uniqueness where
mempty = Unique
instance Pretty Uniqueness where
ppr Unique = star
ppr Nonunique = empty
data StreamOrd = InOrder
| Disorder
deriving (Eq, Ord, Show)
data Commutativity = Noncommutative
| Commutative
deriving (Eq, Ord, Show)
instance Semigroup Commutativity where
(<>) = min
instance Monoid Commutativity where
mempty = Commutative
defaultEntryPoint :: Name
defaultEntryPoint = nameFromString "main"
newtype Name = Name T.Text
deriving (Show, Eq, Ord, IsString, Semigroup)
instance Pretty Name where
ppr = text . nameToString
nameToString :: Name -> String
nameToString (Name t) = T.unpack t
nameFromString :: String -> Name
nameFromString = Name . T.pack
nameToText :: Name -> T.Text
nameToText (Name t) = t
nameFromText :: T.Text -> Name
nameFromText = Name
locStr :: SrcLoc -> String
locStr (SrcLoc NoLoc) = "unknown location"
locStr (SrcLoc (Loc (Pos file line1 col1 _) (Pos _ line2 col2 _)))
| line1 == line2 =
first_part ++ "-" ++ show col2
| otherwise =
first_part ++ "-" ++ show line2 ++ ":" ++ show col2
where first_part = file ++ ":" ++ show line1 ++ ":" ++ show col1
data VName = VName !Name !Int
deriving (Show)
baseTag :: VName -> Int
baseTag (VName _ tag) = tag
baseName :: VName -> Name
baseName (VName vn _) = vn
baseString :: VName -> String
baseString = nameToString . baseName
instance Eq VName where
VName _ x == VName _ y = x == y
instance Ord VName where
VName _ x `compare` VName _ y = x `compare` y