shake-ats-1.10.2.0: 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.

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 :: HsCompiler -> 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

Instances
Eq ForeignCabal Source # 
Instance details

Defined in Development.Shake.ATS.Type

Show ForeignCabal Source # 
Instance details

Defined in Development.Shake.ATS.Type

Generic ForeignCabal Source # 
Instance details

Defined in Development.Shake.ATS.Type

Associated Types

type Rep ForeignCabal :: Type -> Type #

Binary ForeignCabal Source # 
Instance details

Defined in Development.Shake.ATS.Type

type Rep ForeignCabal Source # 
Instance details

Defined in Development.Shake.ATS.Type

type Rep ForeignCabal = D1 (MetaData "ForeignCabal" "Development.Shake.ATS.Type" "shake-ats-1.10.2.0-JL2gBfy1piMBMi2UTYlGKd" False) (C1 (MetaCons "ForeignCabal" PrefixI True) (S1 (MetaSel (Just "projectFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "cabalFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "objectFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))

data ATSTarget Source #

Type for binary and library builds with ATS.

Constructors

ATSTarget 

Fields

Instances
Generic ATSTarget Source # 
Instance details

Defined in Development.Shake.ATS.Type

Associated Types

type Rep ATSTarget :: Type -> Type #

Binary ATSTarget Source # 
Instance details

Defined in Development.Shake.ATS.Type

type Rep ATSTarget Source # 
Instance details

Defined in Development.Shake.ATS.Type

data ATSToolConfig Source #

Information about where to find patscc and patsopt.

Constructors

ATSToolConfig 

Fields

Instances
Generic ATSToolConfig Source # 
Instance details

Defined in Development.Shake.ATS.Type

Associated Types

type Rep ATSToolConfig :: Type -> Type #

Binary ATSToolConfig Source # 
Instance details

Defined in Development.Shake.ATS.Type

type Rep ATSToolConfig Source # 
Instance details

Defined in Development.Shake.ATS.Type

data CCompiler #

A data type representing the C compiler to be used.

Constructors

GCC 

Fields

Clang 
GHC 

Fields

CompCert 
ICC 
Other String 
Instances
Generic CCompiler 
Instance details

Defined in Development.Shake.C

Associated Types

type Rep CCompiler :: Type -> Type #

Binary CCompiler 
Instance details

Defined in Development.Shake.C

type Rep CCompiler 
Instance details

Defined in Development.Shake.C

data ArtifactType Source #

Instances
Generic ArtifactType Source # 
Instance details

Defined in Development.Shake.ATS.Type

Associated Types

type Rep ArtifactType :: Type -> Type #

Binary ArtifactType Source # 
Instance details

Defined in Development.Shake.ATS.Type

type Rep ArtifactType Source # 
Instance details

Defined in Development.Shake.ATS.Type

type Rep ArtifactType = D1 (MetaData "ArtifactType" "Development.Shake.ATS.Type" "shake-ats-1.10.2.0-JL2gBfy1piMBMi2UTYlGKd" False) (C1 (MetaCons "StaticLibrary" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Executable" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SharedLibrary" PrefixI False) (U1 :: Type -> Type)))

data ATSGen Source #

Constructors

ATSGen 

Fields

Instances
Generic ATSGen Source # 
Instance details

Defined in Development.Shake.ATS.Type

Associated Types

type Rep ATSGen :: Type -> Type #

Methods

from :: ATSGen -> Rep ATSGen x #

to :: Rep ATSGen x -> ATSGen #

Binary ATSGen Source # 
Instance details

Defined in Development.Shake.ATS.Type

Methods

put :: ATSGen -> Put #

get :: Get ATSGen #

putList :: [ATSGen] -> Put #

type Rep ATSGen Source # 
Instance details

Defined in Development.Shake.ATS.Type

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

data HATSGen Source #

Constructors

HATSGen 

Fields

Instances
Generic HATSGen Source # 
Instance details

Defined in Development.Shake.ATS.Type

Associated Types

type Rep HATSGen :: Type -> Type #

Methods

from :: HATSGen -> Rep HATSGen x #

to :: Rep HATSGen x -> HATSGen #

Binary HATSGen Source # 
Instance details

Defined in Development.Shake.ATS.Type

Methods

put :: HATSGen -> Put #

get :: Get HATSGen #

putList :: [HATSGen] -> Put #

type Rep HATSGen Source # 
Instance details

Defined in Development.Shake.ATS.Type

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

data Solver Source #

Constructors

PatsSolve 
Z3 
Ignore 
Instances
Generic Solver Source # 
Instance details

Defined in Development.Shake.ATS.Type

Associated Types

type Rep Solver :: Type -> Type #

Methods

from :: Solver -> Rep Solver x #

to :: Rep Solver x -> Solver #

Binary Solver Source # 
Instance details

Defined in Development.Shake.ATS.Type

Methods

put :: Solver -> Put #

get :: Get Solver #

putList :: [Solver] -> Put #

type Rep Solver Source # 
Instance details

Defined in Development.Shake.ATS.Type

type Rep Solver = D1 (MetaData "Solver" "Development.Shake.ATS.Type" "shake-ats-1.10.2.0-JL2gBfy1piMBMi2UTYlGKd" False) (C1 (MetaCons "PatsSolve" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Z3" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ignore" PrefixI False) (U1 :: Type -> Type)))