futhark-0.25.15: An optimising compiler for a functional, array-oriented language.
Safe HaskellSafe-Inferred
LanguageGHC2021

Futhark.Pkg.Types

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)) 

data Chunk #

A logical unit of a version number.

Either entirely numerical (with no leading zeroes) or entirely alphanumerical (with a free mixture of numbers, letters, and hyphens.)

Groups of these (like Release) are separated by periods to form a full section of a version number.

Examples:

1
20150826
r3
0rc1-abc3

Constructors

Alphanum !Text 

Instances

Instances details
Data Chunk 
Instance details

Defined in Data.Versions

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Chunk -> c Chunk #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Chunk #

toConstr :: Chunk -> Constr #

dataTypeOf :: Chunk -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Chunk) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Chunk) #

gmapT :: (forall b. Data b => b -> b) -> Chunk -> Chunk #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Chunk -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Chunk -> r #

gmapQ :: (forall d. Data d => d -> u) -> Chunk -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Chunk -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Chunk -> m Chunk #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Chunk -> m Chunk #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Chunk -> m Chunk #

Generic Chunk 
Instance details

Defined in Data.Versions

Associated Types

type Rep Chunk :: Type -> Type #

Methods

from :: Chunk -> Rep Chunk x #

to :: Rep Chunk x -> Chunk #

Read Chunk 
Instance details

Defined in Data.Versions

Show Chunk 
Instance details

Defined in Data.Versions

Methods

showsPrec :: Int -> Chunk -> ShowS #

show :: Chunk -> String #

showList :: [Chunk] -> ShowS #

NFData Chunk 
Instance details

Defined in Data.Versions

Methods

rnf :: Chunk -> () #

Eq Chunk 
Instance details

Defined in Data.Versions

Methods

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

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

Hashable Chunk 
Instance details

Defined in Data.Versions

Methods

hashWithSalt :: Int -> Chunk -> Int #

hash :: Chunk -> Int #

Lift Chunk 
Instance details

Defined in Data.Versions

Methods

lift :: Quote m => Chunk -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Chunk -> Code m Chunk #

type Rep Chunk 
Instance details

Defined in Data.Versions

type Rep Chunk = D1 ('MetaData "Chunk" "Data.Versions" "versions-6.0.6-fc70ca70a38ebfe96f276daca8fb7f7ffdac92c939ef890cee2fd67803647885" 'False) (C1 ('MetaCons "Numeric" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word)) :+: C1 ('MetaCons "Alphanum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))

newtype Release #

Chunks have comparison behaviour according to SemVer's rules for preleases.

Constructors

Release (NonEmpty Chunk) 

Instances

Instances details
Data Release 
Instance details

Defined in Data.Versions

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Release -> c Release #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Release #

toConstr :: Release -> Constr #

dataTypeOf :: Release -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Release) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Release) #

gmapT :: (forall b. Data b => b -> b) -> Release -> Release #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Release -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Release -> r #

gmapQ :: (forall d. Data d => d -> u) -> Release -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Release -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Release -> m Release #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Release -> m Release #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Release -> m Release #

Generic Release 
Instance details

Defined in Data.Versions

Associated Types

type Rep Release :: Type -> Type #

Methods

from :: Release -> Rep Release x #

to :: Rep Release x -> Release #

Read Release 
Instance details

Defined in Data.Versions

Show Release 
Instance details

Defined in Data.Versions

NFData Release 
Instance details

Defined in Data.Versions

Methods

rnf :: Release -> () #

Eq Release 
Instance details

Defined in Data.Versions

Methods

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

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

Ord Release 
Instance details

Defined in Data.Versions

Hashable Release 
Instance details

Defined in Data.Versions

Methods

hashWithSalt :: Int -> Release -> Int #

hash :: Release -> Int #

Lift Release 
Instance details

Defined in Data.Versions

Methods

lift :: Quote m => Release -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Release -> Code m Release #

type Rep Release 
Instance details

Defined in Data.Versions

type Rep Release = D1 ('MetaData "Release" "Data.Versions" "versions-6.0.6-fc70ca70a38ebfe96f276daca8fb7f7ffdac92c939ef890cee2fd67803647885" 'True) (C1 ('MetaCons "Release" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Chunk))))

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 and hyphens.

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

Constructors

SemVer 

Instances

Instances details
Data SemVer 
Instance details

Defined in Data.Versions

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SemVer -> c SemVer #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SemVer #

toConstr :: SemVer -> Constr #

dataTypeOf :: SemVer -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SemVer) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SemVer) #

gmapT :: (forall b. Data b => b -> b) -> SemVer -> SemVer #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SemVer -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SemVer -> r #

gmapQ :: (forall d. Data d => d -> u) -> SemVer -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SemVer -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SemVer -> m SemVer #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SemVer -> m SemVer #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SemVer -> m SemVer #

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 #

Show SemVer 
Instance details

Defined in Data.Versions

NFData SemVer 
Instance details

Defined in Data.Versions

Methods

rnf :: SemVer -> () #

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

Hashable SemVer 
Instance details

Defined in Data.Versions

Methods

hashWithSalt :: Int -> SemVer -> Int #

hash :: SemVer -> Int #

Semantic SemVer 
Instance details

Defined in Data.Versions

Lift SemVer 
Instance details

Defined in Data.Versions

Methods

lift :: Quote m => SemVer -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => SemVer -> Code m SemVer #

type Rep SemVer 
Instance details

Defined in Data.Versions

type Rep SemVer = D1 ('MetaData "SemVer" "Data.Versions" "versions-6.0.6-fc70ca70a38ebfe96f276daca8fb7f7ffdac92c939ef890cee2fd67803647885" 'False) (C1 ('MetaCons "SemVer" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_svMajor") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word) :*: S1 ('MetaSel ('Just "_svMinor") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word)) :*: (S1 ('MetaSel ('Just "_svPatch") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word) :*: (S1 ('MetaSel ('Just "_svPreRel") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Release)) :*: S1 ('MetaSel ('Just "_svMeta") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text))))))

prettySemVer :: SemVer -> Text #

Convert a SemVer back to its textual representation.

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

Instances details
Show PkgManifest Source # 
Instance details

Defined in Futhark.Pkg.Types

Eq 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

Instances details
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 #

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) #

Functor Commented Source # 
Instance details

Defined in Futhark.Pkg.Types

Methods

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

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

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

Defined in Futhark.Pkg.Types

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

Defined in Futhark.Pkg.Types

Methods

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

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

data Required Source #

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

Constructors

Required 

Fields

Instances

Instances details
Show Required Source # 
Instance details

Defined in Futhark.Pkg.Types

Eq 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

parsePkgManifest :: FilePath -> Text -> Either (ParseErrorBundle Text Void) PkgManifest Source #

Parse a pretty as a PkgManifest. The FilePath is used for any error messages.

parsePkgManifestFromFile :: FilePath -> IO PkgManifest Source #

Read contents of file and pass it to parsePkgManifest.

errorBundlePretty #

Arguments

:: (VisualStream s, TraversableStream 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 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

Instances details
Show BuildList Source # 
Instance details

Defined in Futhark.Pkg.Types

Eq BuildList Source # 
Instance details

Defined in Futhark.Pkg.Types

prettyBuildList :: BuildList -> Text Source #

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