shake-ats-1.6.0.1: Utilities for building ATS projects with shake
Safe HaskellNone
LanguageHaskell2010

Development.Shake.ATS

Synopsis

Shake Rules

cleanATS :: Action () Source #

Clean up after an ATS build.

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.

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 #

Location of patscc

patsopt :: ATSToolConfig -> String Source #

Location of 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

Instances details
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

Hashable 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.6.0.1-m4GnLhaQsq1mYEBTqyyee" '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

Instances details
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

Instances details
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

type Rep ATSToolConfig = D1 ('MetaData "ATSToolConfig" "Development.Shake.ATS.Type" "shake-ats-1.6.0.1-m4GnLhaQsq1mYEBTqyyee" 'False) (C1 ('MetaCons "ATSToolConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_patsHome") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "_patsHomeLocs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :*: (S1 ('MetaSel ('Just "_hasPretty") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "_cc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CCompiler) :*: S1 ('MetaSel ('Just "_linkStatic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))))

data CCompiler #

A data type representing the C compiler to be used.

Bundled Patterns

pattern GHCStd :: CCompiler

Default ghc available

pattern GCCStd :: CCompiler

Default gcc available

Instances

Instances details
Eq CCompiler 
Instance details

Defined in Development.Shake.C

Generic CCompiler Source # 
Instance details

Defined in Development.Shake.ATS.Type

Associated Types

type Rep CCompiler :: Type -> Type #

Binary CCompiler Source # 
Instance details

Defined in Development.Shake.ATS.Type

type Rep CCompiler Source # 
Instance details

Defined in Development.Shake.ATS.Type

type Rep CCompiler = D1 ('MetaData "CCompiler" "Development.Shake.C" "shake-ext-2.11.0.1-9k6S9xexKlZKbY1SIwBb52" 'False) ((C1 ('MetaCons "GCC" 'PrefixI 'True) (S1 ('MetaSel ('Just "_prefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))) :+: C1 ('MetaCons "Clang" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GHC" 'PrefixI 'True) (S1 ('MetaSel ('Just "_prefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Just "_postfix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))) :+: (C1 ('MetaCons "CompCert" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Other" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))

data ArtifactType Source #

Instances

Instances details
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.6.0.1-m4GnLhaQsq1mYEBTqyyee" '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

Instances details
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.6.0.1-m4GnLhaQsq1mYEBTqyyee" '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))))

Lenses