shake-ats-1.8.0.6: Utilities for building ATS projects with shake

Safe HaskellNone
LanguageHaskell2010

Development.Shake.ATS

Contents

Synopsis

Shake Rules

atsBin :: ATSTarget -> Rules () Source #

Rules for generating binaries or libraries from ATS code. This is very general; use defaultATSTarget for sensible defaults that can be modified with the provided lenses.

cgen Source #

Arguments

:: ATSToolConfig 
-> [FilePath]

Extra files to track

-> [FilePath]

ATS source that may be generated.

-> FilePath

ATS source

-> FilePattern

Pattern for C file to be generated

-> Rules () 

Generate C code from ATS code.

genATS Source #

Arguments

:: FilePath

Haskell source

-> FilePattern

.sats file to generate

-> Bool

Whether to call cpphs preprocessor

-> Rules () 

Given a plain Haskell source file, generate a .sats file containing the equivalent types.

atsLex Source #

Arguments

:: FilePath

Filepath of .lats file

-> FilePattern

File pattern for generated output

-> Rules () 

Build a .lats file using atslex.

cabalForeign :: CCompiler -> ForeignCabal -> Rules () Source #

These rules take a .cabal file and the .o file to be produced from them, building the .o file.

Shake actions

cleanATS :: Action () Source #

Clean up after an ATS build.

Helper functions

getSubdirs :: FilePath -> IO [FilePath] Source #

Get subdirectories recursively.

ccToDir :: CCompiler -> String Source #

Given a C compiler, return the appropriate directory for its globally installed artifacts. This is used to keep libraries built for different platforms separate.

withPF Source #

Filter any generated errors with pats-filter.

Environment/configuration

patscc :: ATSToolConfig -> String Source #

Absolute path to patscc

patsopt :: ATSToolConfig -> String Source #

Absolute path to patsopt

Types

data ForeignCabal Source #

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

data ATSTarget Source #

Type for binary and library builds with ATS.

Constructors

ATSTarget 

Fields

Instances

Generic ATSTarget Source # 

Associated Types

type Rep ATSTarget :: * -> * #

Binary ATSTarget Source # 
type Rep ATSTarget Source # 
type Rep ATSTarget = D1 * (MetaData "ATSTarget" "Development.Shake.ATS.Type" "shake-ats-1.8.0.6-LTDifr6ALor3XEeHxppcuU" False) (C1 * (MetaCons "ATSTarget" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String])) ((:*:) * (S1 * (MetaSel (Just Symbol "_toolConfig") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ATSToolConfig)) (S1 * (MetaSel (Just Symbol "_gc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_libs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String])) ((:*:) * (S1 * (MetaSel (Just Symbol "_src") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FilePath])) (S1 * (MetaSel (Just Symbol "_hsLibs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ForeignCabal]))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_genTargets") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ATSGen])) ((:*:) * (S1 * (MetaSel (Just Symbol "_linkTargets") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [HATSGen])) (S1 * (MetaSel (Just Symbol "_binTarget") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FilePath)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_otherDeps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FilePath])) ((:*:) * (S1 * (MetaSel (Just Symbol "_tgtType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ArtifactType)) (S1 * (MetaSel (Just Symbol "_strip") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))))))

data ATSToolConfig Source #

Information about where to find patscc and patsopt.

Constructors

ATSToolConfig 

Fields

data CCompiler :: * #

A data type representing the C compiler to be used.

Bundled Patterns

pattern GCCStd :: CCompiler

Default gcc available

pattern GHCStd :: CCompiler

Default ghc available

Instances

Eq CCompiler 
Show CCompiler 
Generic CCompiler 

Associated Types

type Rep CCompiler :: * -> * #

NFData CCompiler 

Methods

rnf :: CCompiler -> () #

Binary CCompiler 
Hashable CCompiler 
type Rep CCompiler 

data ArtifactType Source #

Instances

Generic ArtifactType Source # 

Associated Types

type Rep ArtifactType :: * -> * #

Binary ArtifactType Source # 
type Rep ArtifactType Source # 
type Rep ArtifactType = D1 * (MetaData "ArtifactType" "Development.Shake.ATS.Type" "shake-ats-1.8.0.6-LTDifr6ALor3XEeHxppcuU" False) ((:+:) * (C1 * (MetaCons "StaticLibrary" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Executable" PrefixI False) (U1 *)) (C1 * (MetaCons "SharedLibrary" PrefixI False) (U1 *))))

data ATSGen Source #

Constructors

ATSGen 

Fields

Instances

Generic ATSGen Source # 

Associated Types

type Rep ATSGen :: * -> * #

Methods

from :: ATSGen -> Rep ATSGen x #

to :: Rep ATSGen x -> ATSGen #

Binary ATSGen Source # 

Methods

put :: ATSGen -> Put #

get :: Get ATSGen #

putList :: [ATSGen] -> Put #

type Rep ATSGen Source # 
type Rep ATSGen = D1 * (MetaData "ATSGen" "Development.Shake.ATS.Type" "shake-ats-1.8.0.6-LTDifr6ALor3XEeHxppcuU" False) (C1 * (MetaCons "ATSGen" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_hsFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FilePath)) ((:*:) * (S1 * (MetaSel (Just Symbol "_atsTarget") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FilePath)) (S1 * (MetaSel (Just Symbol "_cpphs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))))

data HATSGen Source #

Constructors

HATSGen 

Fields

Instances

Generic HATSGen Source # 

Associated Types

type Rep HATSGen :: * -> * #

Methods

from :: HATSGen -> Rep HATSGen x #

to :: Rep HATSGen x -> HATSGen #

Binary HATSGen Source # 

Methods

put :: HATSGen -> Put #

get :: Get HATSGen #

putList :: [HATSGen] -> Put #

type Rep HATSGen Source # 
type Rep HATSGen = D1 * (MetaData "HATSGen" "Development.Shake.ATS.Type" "shake-ats-1.8.0.6-LTDifr6ALor3XEeHxppcuU" False) (C1 * (MetaCons "HATSGen" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "satsFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FilePath)) (S1 * (MetaSel (Just Symbol "hatsFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FilePath))))

data Solver Source #

Constructors

PatsSolve 
Z3 
Ignore 

Instances

Generic Solver Source # 

Associated Types

type Rep Solver :: * -> * #

Methods

from :: Solver -> Rep Solver x #

to :: Rep Solver x -> Solver #

Binary Solver Source # 

Methods

put :: Solver -> Put #

get :: Get Solver #

putList :: [Solver] -> Put #

type Rep Solver Source # 
type Rep Solver = D1 * (MetaData "Solver" "Development.Shake.ATS.Type" "shake-ats-1.8.0.6-LTDifr6ALor3XEeHxppcuU" False) ((:+:) * (C1 * (MetaCons "PatsSolve" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Z3" PrefixI False) (U1 *)) (C1 * (MetaCons "Ignore" PrefixI False) (U1 *))))

Lenses