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

Safe HaskellNone
LanguageHaskell2010

Development.Shake.ATS

Contents

Synopsis

Shake Rules

cgen Source #

Arguments

:: ATSToolConfig 
-> FilePath

Directory containing ATS source code

-> Rules () 

cgenPretty :: ATSToolConfig -> FilePath -> Rules () Source #

This uses pats-filter to prettify the errors.

atsLex :: FilePattern -> Rules () Source #

Build a .lats file.

Actions

patsHome :: MonadIO m => Version -> m String Source #

The directory that will be PATSHOME.

Helper functions

compatible :: CCompiler -> CCompiler -> Bool Source #

Whether generated libraries are to be considered compatible.

patscc :: MonadIO m => ATSToolConfig -> m String Source #

Location of patscc

patsopt :: MonadIO m => ATSToolConfig -> m String Source #

Location of patsopt

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.5-2Pn2f9bdecr38sTmMu1Pov" True) (C1 * (MetaCons "Version" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Integer])))

data ForeignCabal Source #

Data type containing information about Haskell components of a build.

Constructors

ForeignCabal 

Fields

data BinaryTarget Source #

Type for binary and library builds with ATS.

Constructors

BinaryTarget 

Fields

Instances

Generic BinaryTarget Source # 

Associated Types

type Rep BinaryTarget :: * -> * #

Binary BinaryTarget Source # 
type Rep BinaryTarget Source # 
type Rep BinaryTarget = D1 * (MetaData "BinaryTarget" "Development.Shake.ATS.Type" "shake-ats-1.4.1.0-K5oOYDfwIY3ElslOyarGp2" False) (C1 * (MetaCons "BinaryTarget" 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 * [String]))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "hsLibs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ForeignCabal])) ((:*:) * (S1 * (MetaSel (Just Symbol "genTargets") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(String, String, Bool)])) (S1 * (MetaSel (Just Symbol "binTarget") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))) ((:*:) * (S1 * (MetaSel (Just Symbol "cDeps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String])) ((:*:) * (S1 * (MetaSel (Just Symbol "otherDeps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String])) (S1 * (MetaSel (Just Symbol "tgtType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ArtifactType)))))))

data ATSToolConfig Source #

Information about where to find patscc and patsopt.

Constructors

ATSToolConfig 

Fields

data CCompiler :: * #

Bundled Patterns

pattern GCCStd :: CCompiler 
pattern GHCStd :: CCompiler 

data ArtifactType Source #

Constructors

StaticLibrary 
Executable 

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.4.1.0-K5oOYDfwIY3ElslOyarGp2" False) ((:+:) * (C1 * (MetaCons "StaticLibrary" PrefixI False) (U1 *)) (C1 * (MetaCons "Executable" PrefixI False) (U1 *)))