Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Futhark.Pkg.Types
Description
Types (and a few other simple definitions) for futhark-pkg.
Synopsis
- type PkgPath = Text
- pkgPathFilePath :: PkgPath -> FilePath
- newtype PkgRevDeps = PkgRevDeps (Map PkgPath (SemVer, Maybe Text))
- data Chunk = Alphanum !Text
- newtype Release = Release (NonEmpty Chunk)
- data SemVer = SemVer {}
- prettySemVer :: SemVer -> Text
- commitVersion :: Text -> Text -> SemVer
- isCommitVersion :: SemVer -> Maybe Text
- parseVersion :: Text -> Either (ParseErrorBundle Text Void) SemVer
- data PkgManifest = PkgManifest {}
- newPkgManifest :: Maybe PkgPath -> PkgManifest
- pkgRevDeps :: PkgManifest -> PkgRevDeps
- pkgDir :: PkgManifest -> Maybe FilePath
- addRequiredToManifest :: Required -> PkgManifest -> (PkgManifest, Maybe Required)
- removeRequiredFromManifest :: PkgPath -> PkgManifest -> Maybe (PkgManifest, Required)
- prettyPkgManifest :: PkgManifest -> Text
- type Comment = Text
- data Commented a = Commented {}
- data Required = Required {}
- futharkPkg :: FilePath
- parsePkgManifest :: FilePath -> Text -> Either (ParseErrorBundle Text Void) PkgManifest
- parsePkgManifestFromFile :: FilePath -> IO PkgManifest
- errorBundlePretty :: (VisualStream s, TraversableStream s, ShowErrorComponent e) => ParseErrorBundle s e -> String
- newtype BuildList = BuildList {}
- prettyBuildList :: BuildList -> Text
Documentation
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).
Instances
Monoid PkgRevDeps Source # | |
Defined in Futhark.Pkg.Types Methods mempty :: PkgRevDeps # mappend :: PkgRevDeps -> PkgRevDeps -> PkgRevDeps # mconcat :: [PkgRevDeps] -> PkgRevDeps # | |
Semigroup PkgRevDeps Source # | |
Defined in Futhark.Pkg.Types Methods (<>) :: PkgRevDeps -> PkgRevDeps -> PkgRevDeps # sconcat :: NonEmpty PkgRevDeps -> PkgRevDeps # stimes :: Integral b => b -> PkgRevDeps -> PkgRevDeps # | |
Show PkgRevDeps Source # | |
Defined in Futhark.Pkg.Types Methods showsPrec :: Int -> PkgRevDeps -> ShowS # show :: PkgRevDeps -> String # showList :: [PkgRevDeps] -> ShowS # |
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
Instances
Data Chunk | |
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 # 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 | |
Read Chunk | |
Show Chunk | |
NFData Chunk | |
Defined in Data.Versions | |
Eq Chunk | |
Hashable Chunk | |
Defined in Data.Versions | |
Lift Chunk | |
type Rep Chunk | |
Defined in Data.Versions type Rep Chunk = D1 ('MetaData "Chunk" "Data.Versions" "versions-6.0.8-5FgnyuLEzNj66GIodBlDHn" 'False) (C1 ('MetaCons "Numeric" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word)) :+: C1 ('MetaCons "Alphanum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) |
Chunk
s have comparison behaviour according to SemVer's rules for preleases.
Instances
Data Release | |
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 | |
Read Release | |
Show Release | |
NFData Release | |
Defined in Data.Versions | |
Eq Release | |
Ord Release | |
Hashable Release | |
Defined in Data.Versions | |
Lift Release | |
type Rep Release | |
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:
- Pre-release versions have lower precedence than normal versions.
- Build metadata does not affect version precedence.
- PREREL and META strings may only contain ASCII alphanumerics and hyphens.
For more information, see http://semver.org
Constructors
SemVer | |
Instances
Data SemVer | |
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 | |
Show SemVer | |
NFData SemVer | |
Defined in Data.Versions | |
Eq SemVer | Two SemVers are equal if all fields except metadata are equal. |
Ord SemVer | Build metadata does not affect version precedence. |
Hashable SemVer | |
Defined in Data.Versions | |
Semantic SemVer | |
Defined in Data.Versions | |
Lift SemVer | |
type Rep SemVer | |
Defined in Data.Versions type Rep SemVer = D1 ('MetaData "SemVer" "Data.Versions" "versions-6.0.8-5FgnyuLEzNj66GIodBlDHn" 'False) (C1 ('MetaCons "SemVer" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_svMajor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word) :*: S1 ('MetaSel ('Just "_svMinor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word)) :*: (S1 ('MetaSel ('Just "_svPatch") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (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).
Constructors
PkgManifest | |
Fields
|
Instances
Show PkgManifest Source # | |
Defined in Futhark.Pkg.Types Methods showsPrec :: Int -> PkgManifest -> ShowS # show :: PkgManifest -> String # showList :: [PkgManifest] -> ShowS # | |
Eq PkgManifest Source # | |
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 #
prettyPkgManifest :: PkgManifest -> Text Source #
Prettyprint a package manifest such that it can be written to a
futhark.pkg
file.
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.
Instances
Foldable Commented Source # | |
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] # length :: Commented a -> Int # elem :: Eq a => a -> Commented a -> Bool # maximum :: Ord a => Commented a -> a # minimum :: Ord a => Commented a -> a # | |
Traversable Commented Source # | |
Defined in Futhark.Pkg.Types | |
Functor Commented Source # | |
Show a => Show (Commented a) Source # | |
Eq a => Eq (Commented a) Source # | |
An entry in the required
section of a futhark.pkg
file.
Constructors
Required | |
Fields
|
Instances
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
.
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 ParseError
s 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
A mapping from package paths to their chosen revisions. This is the result of the version solver.
Constructors
BuildList | |
Fields |
prettyBuildList :: BuildList -> Text Source #
Prettyprint a build list; one package per line and newline-terminated.