ats-pkg-2.7.1.0: A build tool for ATS

Safe HaskellNone
LanguageHaskell2010

Language.ATS.Package

Contents

Synopsis

Documentation

buildAll :: Maybe String -> Maybe FilePath -> IO () Source #

Build in current directory or indicated directory

mkPkg Source #

Arguments

:: Bool

Force rebuild

-> Bool

Run linter

-> Bool

Print build profiling information

-> [IO ()]

Setup

-> [String]

Targets

-> Maybe String

Target triple

-> Int

Verbosity

-> IO () 

checkPkg Source #

Arguments

:: FilePath

Path to .dhall file defining a package set.

-> Bool

Whether to print detailed error messages.

-> IO ATSPackageSet 

Ecosystem functionality

Functions involving the compiler

packageCompiler :: FilePath -> IO () Source #

Make a tarball from a directory containing the compiler.

Functions for generic packaging

atsInstallDirs :: Hashable a => IO (InstallDirs a) Source #

The default set of install dirs for an ATS package.

Types

newtype Version :: * #

Constructors

Version [Integer] 

Instances

Eq Version 

Methods

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

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

Ord Version 
Show Version 
Generic Version 

Associated Types

type Rep Version :: * -> * #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Binary Version 

Methods

put :: Version -> Put #

get :: Get Version #

putList :: [Version] -> Put #

NFData Version 

Methods

rnf :: Version -> () #

type Rep Version 
type Rep Version = D1 * (MetaData "Version" "Data.Dependency.Type" "dependency-0.1.0.9-4FUJypiVFnz5jpvxtJbYg1" True) (C1 * (MetaCons "Version" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Integer])))

data Pkg Source #

Data type associated with atspkg.dhall file.

Constructors

Pkg 

Fields

Instances

Eq Pkg Source # 

Methods

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

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

Show Pkg Source # 

Methods

showsPrec :: Int -> Pkg -> ShowS #

show :: Pkg -> String #

showList :: [Pkg] -> ShowS #

Generic Pkg Source # 

Associated Types

type Rep Pkg :: * -> * #

Methods

from :: Pkg -> Rep Pkg x #

to :: Rep Pkg x -> Pkg #

Binary Pkg Source # 

Methods

put :: Pkg -> Put #

get :: Get Pkg #

putList :: [Pkg] -> Put #

Hashable Pkg Source # 

Methods

hashWithSalt :: Int -> Pkg -> Int #

hash :: Pkg -> Int #

Interpret Pkg Source # 
type Rep Pkg Source # 
type Rep Pkg = D1 * (MetaData "Pkg" "Language.ATS.Package.Type" "ats-pkg-2.7.1.0-1DFGMY63NGP8bwq9cR0soS" False) (C1 * (MetaCons "Pkg" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "bin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Bin])) ((:*:) * (S1 * (MetaSel (Just Symbol "test") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Bin])) (S1 * (MetaSel (Just Symbol "libraries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Lib])))) ((:*:) * (S1 * (MetaSel (Just Symbol "man") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "completions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "version") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Version))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "compiler") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Version)) ((:*:) * (S1 * (MetaSel (Just Symbol "dependencies") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [LibDep])) (S1 * (MetaSel (Just Symbol "clib") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [LibDep])))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "buildDeps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [LibDep])) (S1 * (MetaSel (Just Symbol "ccompiler") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "cflags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Text])) (S1 * (MetaSel (Just Symbol "atsSource") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Src])))))))

data Bin Source #

Constructors

Bin 

Fields

  • src :: Text

    Source file (should end with .dats)

  • target :: Text

    Binary to be built

  • libs :: [Text]

    Libraries to link against (e.g. [ "pthread" ])

  • hsDeps :: [ForeignCabal]

    Haskell .cabal files associated with the final library we want to make

  • hs2ats :: [TargetPair]

    List of sources and targets for hs2ats

  • gcBin :: Bool

    Whether to use the garbage collector

  • extras :: [Text]

    Extra source files the build depends on

Instances

Eq Bin Source # 

Methods

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

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

Show Bin Source # 

Methods

showsPrec :: Int -> Bin -> ShowS #

show :: Bin -> String #

showList :: [Bin] -> ShowS #

Generic Bin Source # 

Associated Types

type Rep Bin :: * -> * #

Methods

from :: Bin -> Rep Bin x #

to :: Rep Bin x -> Bin #

Binary Bin Source # 

Methods

put :: Bin -> Put #

get :: Get Bin #

putList :: [Bin] -> Put #

Hashable Bin Source # 

Methods

hashWithSalt :: Int -> Bin -> Int #

hash :: Bin -> Int #

Interpret Bin Source # 
type Rep Bin Source # 

data Lib Source #

Constructors

Lib 

Fields

Instances

Eq Lib Source # 

Methods

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

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

Show Lib Source # 

Methods

showsPrec :: Int -> Lib -> ShowS #

show :: Lib -> String #

showList :: [Lib] -> ShowS #

Generic Lib Source # 

Associated Types

type Rep Lib :: * -> * #

Methods

from :: Lib -> Rep Lib x #

to :: Rep Lib x -> Lib #

Binary Lib Source # 

Methods

put :: Lib -> Put #

get :: Get Lib #

putList :: [Lib] -> Put #

Hashable Lib Source # 

Methods

hashWithSalt :: Int -> Lib -> Int #

hash :: Lib -> Int #

Interpret Lib Source # 
type Rep Lib Source # 

data Src Source #

Constructors

Src 

Fields

Instances

Eq Src Source # 

Methods

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

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

Show Src Source # 

Methods

showsPrec :: Int -> Src -> ShowS #

show :: Src -> String #

showList :: [Src] -> ShowS #

Generic Src Source # 

Associated Types

type Rep Src :: * -> * #

Methods

from :: Src -> Rep Src x #

to :: Rep Src x -> Src #

Binary Src Source # 

Methods

put :: Src -> Put #

get :: Get Src #

putList :: [Src] -> Put #

Hashable Src Source # 

Methods

hashWithSalt :: Int -> Src -> Int #

hash :: Src -> Int #

Interpret Src Source # 
type Rep Src Source # 

data ATSDependency Source #

Type for a dependency

Constructors

ATSDependency 

Fields

Instances

Eq ATSDependency Source # 
Show ATSDependency Source # 
Generic ATSDependency Source # 

Associated Types

type Rep ATSDependency :: * -> * #

Binary ATSDependency Source # 
Hashable ATSDependency Source # 
Interpret ATSDependency Source # 
type Rep ATSDependency Source # 

data TargetPair Source #

This is just a tuple, except I can figure out how to use it with Dhall.

Constructors

TargetPair 

Fields

data ForeignCabal :: * #

Data type containing information about Haskell components of a build. Any functions exposed in the object file will be callable in C or ATS code.

Constructors

ForeignCabal 

Fields

Generic Packaging

newtype Package a b Source #

The package monad provides information about the package to be installed, in particular, the directory for installation and the directories for dependencies.

Constructors

Package 

Fields

Instances

Monad (Package a) Source # 

Methods

(>>=) :: Package a a -> (a -> Package a b) -> Package a b #

(>>) :: Package a a -> Package a b -> Package a b #

return :: a -> Package a a #

fail :: String -> Package a a #

Functor (Package a) Source # 

Methods

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

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

Applicative (Package a) Source # 

Methods

pure :: a -> Package a a #

(<*>) :: Package a (a -> b) -> Package a a -> Package a b #

liftA2 :: (a -> b -> c) -> Package a a -> Package a b -> Package a c #

(*>) :: Package a a -> Package a b -> Package a b #

(<*) :: Package a a -> Package a b -> Package a a #

data InstallDirs a Source #

Functions containing installation information about a particular type.

Constructors

InstallDirs 

Fields

Typeclasses

class Hashable a => GenericPackage a where Source #

Any type implementing GenericPackage can be depended on by other packages.

Minimal complete definition

binRules, libRules, includeRules

Methods

binRules :: a -> Package a () Source #

libRules :: a -> Package a () Source #

includeRules :: a -> Package a () Source #

Lenses