futhark-0.7.4: An optimising compiler for a functional, array-oriented language.

Safe HaskellNone
LanguageHaskell2010

Futhark.Pkg.Types

Contents

Description

Types (and a few other simple definitions) for futhark-pkg.

Synopsis

Documentation

type PkgPath = Text Source #

A package path is a unique identifier for a package, for example github.comuserfoo.

pkgPathFilePath :: PkgPath -> FilePath Source #

Turn a package path (which always uses forward slashes) into a file path in the local file system (which might use different slashes).

newtype PkgRevDeps Source #

The dependencies of a (revision of a) package is a mapping from package paths to minimum versions (and an optional hash pinning).

Constructors

PkgRevDeps (Map PkgPath (SemVer, Maybe Text)) 

prettySemVer :: SemVer -> Text #

Convert a SemVer back to its textual representation.

data SemVer #

An (Ideal) version number that conforms to Semantic Versioning. This is a prescriptive parser, meaning it follows the SemVer standard.

Legal semvers are of the form: MAJOR.MINOR.PATCH-PREREL+META

Example: 1.2.3-r1+commithash

Extra Rules:

  1. Pre-release versions have lower precedence than normal versions.
  2. Build metadata does not affect version precedence.
  3. PREREL and META strings may only contain ASCII alphanumerics.

For more information, see http://semver.org

Constructors

SemVer 
Instances
Eq SemVer

Two SemVers are equal if all fields except metadata are equal.

Instance details

Defined in Data.Versions

Methods

(==) :: SemVer -> SemVer -> Bool #

(/=) :: SemVer -> SemVer -> Bool #

Ord SemVer

Build metadata does not affect version precedence.

Instance details

Defined in Data.Versions

Show SemVer 
Instance details

Defined in Data.Versions

Generic SemVer 
Instance details

Defined in Data.Versions

Associated Types

type Rep SemVer :: Type -> Type #

Methods

from :: SemVer -> Rep SemVer x #

to :: Rep SemVer x -> SemVer #

Semigroup SemVer 
Instance details

Defined in Data.Versions

Monoid SemVer 
Instance details

Defined in Data.Versions

Hashable SemVer 
Instance details

Defined in Data.Versions

Methods

hashWithSalt :: Int -> SemVer -> Int #

hash :: SemVer -> Int #

NFData SemVer 
Instance details

Defined in Data.Versions

Methods

rnf :: SemVer -> () #

Semantic SemVer 
Instance details

Defined in Data.Versions

type Rep SemVer 
Instance details

Defined in Data.Versions

data VUnit #

A single unit of a Version. May be digits or a string of characters. Groups of these are called VChunks, and are the identifiers separated by periods in the source.

Constructors

Digits Word 
Str Text 
Instances
Eq VUnit 
Instance details

Defined in Data.Versions

Methods

(==) :: VUnit -> VUnit -> Bool #

(/=) :: VUnit -> VUnit -> Bool #

Ord VUnit 
Instance details

Defined in Data.Versions

Methods

compare :: VUnit -> VUnit -> Ordering #

(<) :: VUnit -> VUnit -> Bool #

(<=) :: VUnit -> VUnit -> Bool #

(>) :: VUnit -> VUnit -> Bool #

(>=) :: VUnit -> VUnit -> Bool #

max :: VUnit -> VUnit -> VUnit #

min :: VUnit -> VUnit -> VUnit #

Read VUnit 
Instance details

Defined in Data.Versions

Show VUnit 
Instance details

Defined in Data.Versions

Methods

showsPrec :: Int -> VUnit -> ShowS #

show :: VUnit -> String #

showList :: [VUnit] -> ShowS #

Generic VUnit 
Instance details

Defined in Data.Versions

Associated Types

type Rep VUnit :: Type -> Type #

Methods

from :: VUnit -> Rep VUnit x #

to :: Rep VUnit x -> VUnit #

Semigroup VUnit 
Instance details

Defined in Data.Versions

Methods

(<>) :: VUnit -> VUnit -> VUnit #

sconcat :: NonEmpty VUnit -> VUnit #

stimes :: Integral b => b -> VUnit -> VUnit #

Monoid VUnit 
Instance details

Defined in Data.Versions

Methods

mempty :: VUnit #

mappend :: VUnit -> VUnit -> VUnit #

mconcat :: [VUnit] -> VUnit #

Hashable VUnit 
Instance details

Defined in Data.Versions

Methods

hashWithSalt :: Int -> VUnit -> Int #

hash :: VUnit -> Int #

NFData VUnit 
Instance details

Defined in Data.Versions

Methods

rnf :: VUnit -> () #

type Rep VUnit 
Instance details

Defined in Data.Versions

Versions

commitVersion :: Text -> Text -> SemVer Source #

commitVersion timestamp commit constructs a commit version.

isCommitVersion :: SemVer -> Maybe Text Source #

Versions of the form (0,0,0)-timestamp+hash are treated specially, as a reference to the commit identified uniquely with hash (typically the Git commit ID). This function detects such versions.

parseVersion :: Text -> Either (ParseErrorBundle Text Void) SemVer Source #

Unfortunately, Data.Versions has a buggy semver parser that collapses consecutive zeroes in the metadata field. So, we define our own parser here. It's a little simpler too, since we don't need full semver.

Package manifests

data PkgManifest Source #

A structure corresponding to a futhark.pkg file, including comments. It is an invariant that duplicate required packages do not occcur (the parser will verify this).

Instances
Eq PkgManifest Source # 
Instance details

Defined in Futhark.Pkg.Types

Show PkgManifest Source # 
Instance details

Defined in Futhark.Pkg.Types

newPkgManifest :: Maybe PkgPath -> PkgManifest Source #

Possibly given a package path, construct an otherwise-empty manifest file.

pkgRevDeps :: PkgManifest -> PkgRevDeps Source #

The required packages listed in a package manifest.

pkgDir :: PkgManifest -> Maybe FilePath Source #

Where in the corresponding repository archive we can expect to find the package files.

addRequiredToManifest :: Required -> PkgManifest -> (PkgManifest, Maybe Required) Source #

Add new required package to the package manifest. If the package was already present, return the old version.

removeRequiredFromManifest :: PkgPath -> PkgManifest -> Maybe (PkgManifest, Required) Source #

Remove a required package from the manifest. Returns Nothing if the package was not found in the manifest, and otherwise the new manifest and the Required that was present.

prettyPkgManifest :: PkgManifest -> Text Source #

Prettyprint a package manifest such that it can be written to a futhark.pkg file.

type Comment = Text Source #

A line comment.

data Commented a Source #

Wraps a value with an annotation of preceding line comments. This is important to our goal of being able to programmatically modify the futhark.pkg file while keeping comments intact.

Constructors

Commented 

Fields

Instances
Functor Commented Source # 
Instance details

Defined in Futhark.Pkg.Types

Methods

fmap :: (a -> b) -> Commented a -> Commented b #

(<$) :: a -> Commented b -> Commented a #

Foldable Commented Source # 
Instance details

Defined in Futhark.Pkg.Types

Methods

fold :: Monoid m => Commented m -> m #

foldMap :: Monoid m => (a -> m) -> Commented a -> m #

foldr :: (a -> b -> b) -> b -> Commented a -> b #

foldr' :: (a -> b -> b) -> b -> Commented a -> b #

foldl :: (b -> a -> b) -> b -> Commented a -> b #

foldl' :: (b -> a -> b) -> b -> Commented a -> b #

foldr1 :: (a -> a -> a) -> Commented a -> a #

foldl1 :: (a -> a -> a) -> Commented a -> a #

toList :: Commented a -> [a] #

null :: Commented a -> Bool #

length :: Commented a -> Int #

elem :: Eq a => a -> Commented a -> Bool #

maximum :: Ord a => Commented a -> a #

minimum :: Ord a => Commented a -> a #

sum :: Num a => Commented a -> a #

product :: Num a => Commented a -> a #

Traversable Commented Source # 
Instance details

Defined in Futhark.Pkg.Types

Methods

traverse :: Applicative f => (a -> f b) -> Commented a -> f (Commented b) #

sequenceA :: Applicative f => Commented (f a) -> f (Commented a) #

mapM :: Monad m => (a -> m b) -> Commented a -> m (Commented b) #

sequence :: Monad m => Commented (m a) -> m (Commented a) #

Eq a => Eq (Commented a) Source # 
Instance details

Defined in Futhark.Pkg.Types

Methods

(==) :: Commented a -> Commented a -> Bool #

(/=) :: Commented a -> Commented a -> Bool #

Show a => Show (Commented a) Source # 
Instance details

Defined in Futhark.Pkg.Types

data Required Source #

An entry in the required section of a futhark.pkg file.

Constructors

Required 

Fields

Instances
Eq Required Source # 
Instance details

Defined in Futhark.Pkg.Types

Show Required Source # 
Instance details

Defined in Futhark.Pkg.Types

futharkPkg :: FilePath Source #

The name of the file containing the futhark-pkg manifest.

Parsing package manifests

errorBundlePretty #

Arguments

:: (Stream s, ShowErrorComponent e) 
=> ParseErrorBundle s e

Parse error bundle to display

-> String

Textual rendition of the bundle

Pretty-print a ParseErrorBundle. All ParseErrors in the bundle will be pretty-printed in order together with the corresponding offending lines by doing a single efficient pass over the input stream. The rendered String always ends with a newline.

Since: megaparsec-7.0.0

Build list

newtype BuildList Source #

A mapping from package paths to their chosen revisions. This is the result of the version solver.

Constructors

BuildList 
Instances
Eq BuildList Source # 
Instance details

Defined in Futhark.Pkg.Types

Show BuildList Source # 
Instance details

Defined in Futhark.Pkg.Types

prettyBuildList :: BuildList -> Text Source #

Prettyprint a build list; one package per line and newline-terminated.