2011-01-19 00:24:11 +01:00
/* sbt -- Simple Build Tool
* Copyright 2011 Mark Harrah
*/
package sbt
/* * An abstraction on top of Settings for build configuration and task definition. */
import Types._
2011-04-12 04:12:03 +02:00
import std.TaskExtra. { task => mktask , _ }
2011-01-19 00:24:11 +01:00
import Task._
2011-02-12 02:22:17 +01:00
import Project. { Initialize , ScopedKey , Setting , setting }
2011-01-22 20:01:59 +01:00
import complete.Parser
2011-01-19 00:24:11 +01:00
import java.io.File
import java.net.URI
2011-04-14 13:32:42 +02:00
import Path._
2011-01-19 00:24:11 +01:00
2011-04-05 01:10:35 +02:00
sealed trait InputTask [ T ] {
def mapTask [ S ] ( f : Task [ T ] => Task [ S ] ) : InputTask [ S ]
}
private final class InputStatic [ T ] ( val parser : State => Parser [ Task [ T ] ] ) extends InputTask [ T ] {
def mapTask [ S ] ( f : Task [ T ] => Task [ S ] ) = new InputStatic ( s => parser ( s ) map f )
}
2011-02-12 02:22:17 +01:00
private sealed trait InputDynamic [ T ] extends InputTask [ T ]
2011-04-05 01:10:35 +02:00
{ outer =>
2011-02-12 02:22:17 +01:00
type Result
def parser : State => Parser [ Result ]
def task : Task [ T ]
2011-04-05 01:10:35 +02:00
def mapTask [ S ] ( f : Task [ T ] => Task [ S ] ) = new InputDynamic [ S ] {
type Result = outer . Result
def parser = outer . parser
def task = f ( outer . task )
}
2011-01-19 00:24:11 +01:00
}
2011-02-12 02:22:17 +01:00
object InputTask
{
def static [ T ] ( p : Parser [ Task [ T ] ] ) : InputTask [ T ] = free ( _ => p )
def static [ I ,T ] ( p : Parser [ I ] ) ( c : I => Task [ T ] ) : InputTask [ T ] = static ( p map c )
def free [ T ] ( p : State => Parser [ Task [ T ] ] ) : InputTask [ T ] = new InputStatic [ T ] ( p )
def free [ I ,T ] ( p : State => Parser [ I ] ) ( c : I => Task [ T ] ) : InputTask [ T ] = free ( s => p ( s ) map c )
def separate [ I ,T ] ( p : State => Parser [ I ] ) ( action : Initialize [ I => Task [ T ] ] ) : Initialize [ InputTask [ T ] ] =
separate ( Project value p ) ( action )
def separate [ I ,T ] ( p : Initialize [ State => Parser [ I ] ] ) ( action : Initialize [ I => Task [ T ] ] ) : Initialize [ InputTask [ T ] ] =
p . zipWith ( action ) ( ( parser , act ) => free ( parser ) ( act ) )
// This interface allows the Parser to be constructed using other Settings, but not Tasks (which is desired).
// The action can be constructed using Settings and Tasks and with the parse result injected into a Task.
// This is the ugly part, requiring hooks in injectStreams and Act to handle the dummy task for the parse result.
2011-04-07 03:00:48 +02:00
// However, this is results in a minimal interface to the full capabilities of an InputTask for users
2011-02-12 02:22:17 +01:00
def apply [ I ,T ] ( p : Initialize [ State => Parser [ I ] ] ) ( action : TaskKey [ I ] => Initialize [ Task [ T ] ] ) : Initialize [ InputTask [ T ] ] =
{
2011-04-07 03:00:48 +02:00
val key = Keys . parseResult . asInstanceOf [ TaskKey [ I ] ]
2011-02-12 02:22:17 +01:00
p . zipWith ( action ( key ) ) { ( parserF , act ) =>
new InputDynamic [ T ]
{
type Result = I
def parser = parserF
def task = act
}
}
}
def apply [ I ,T ] ( p : State => Parser [ I ] ) ( action : TaskKey [ I ] => Initialize [ Task [ T ] ] ) : Initialize [ InputTask [ T ] ] =
apply ( Project . value ( p ) ) ( action )
2011-01-19 00:24:11 +01:00
}
2011-02-12 02:22:17 +01:00
sealed trait Scoped { def scope : Scope ; def key : AttributeKey [ _ ] }
2011-01-29 03:15:39 +01:00
sealed trait ScopedTaskable [ T ] extends Scoped
sealed trait ScopedSetting [ T ] extends ScopedTaskable [ T ] { def key : AttributeKey [ T ] }
sealed trait ScopedTask [ T ] extends ScopedTaskable [ T ] { def key : AttributeKey [ Task [ T ] ] }
2011-02-12 02:22:17 +01:00
sealed trait ScopedInput [ T ] extends Scoped { def key : AttributeKey [ InputTask [ T ] ] }
2011-01-19 00:24:11 +01:00
sealed trait Key [ T ] extends Scoped { final def scope : Scope = Scope ( This , This , This , This ) }
2011-02-12 02:22:17 +01:00
final class SettingKey [ T ] private ( val key : AttributeKey [ T ] ) extends Key [ T ] with ScopedSetting [ T ]
final class TaskKey [ T ] private ( val key : AttributeKey [ Task [ T ] ] ) extends Key [ T ] with ScopedTask [ T ]
2011-01-19 00:24:11 +01:00
final class InputKey [ T ] private ( val key : AttributeKey [ InputTask [ T ] ] ) extends Key [ InputTask [ T ] ] with ScopedInput [ T ]
object Scoped
{
2011-02-12 02:22:17 +01:00
implicit def richSettingScoped [ T ] ( s : ScopedSetting [ T ] ) : RichSettingScoped [ T ] = new RichSettingScoped [ T ] ( s . scope , s . key )
implicit def richTaskScoped [ T ] ( s : ScopedTask [ T ] ) : RichTaskScoped [ T ] = new RichTaskScoped [ T ] ( s . scope , s . key )
2011-01-19 00:24:11 +01:00
implicit def richInputScoped [ T ] ( s : ScopedInput [ T ] ) : RichInputScoped [ T ] = new RichInputScoped [ T ] ( s . scope , s . key )
2011-02-12 02:22:17 +01:00
implicit def richSettingListScoped [ T ] ( s : ScopedSetting [ Seq [ T ] ] ) : RichSettingList [ T ] = new RichSettingList [ T ] ( s . scope , s . key )
implicit def richListTaskScoped [ T ] ( s : ScopedTask [ Seq [ T ] ] ) : RichListTask [ T ] = new RichListTask [ T ] ( s . scope , s . key )
2011-01-19 00:24:11 +01:00
2011-04-05 13:10:28 +02:00
implicit def taskScopedToKey [ T ] ( s : ScopedTask [ T ] ) : ScopedKey [ Task [ T ] ] = ScopedKey ( s . scope , s . key )
implicit def inputScopedToKey [ T ] ( s : ScopedInput [ T ] ) : ScopedKey [ InputTask [ T ] ] = ScopedKey ( s . scope , s . key )
2011-03-01 14:48:14 +01:00
implicit def scopedSettingScoping [ T ] ( s : ScopedSetting [ T ] ) : ScopingSetting [ ScopedSetting [ T ] ] =
new ScopingSetting ( scope => scopedSetting ( Scope . replaceThis ( s . scope ) ( scope ) , s . key ) )
2011-01-29 03:15:39 +01:00
2011-03-01 14:48:14 +01:00
implicit def scopedTaskScoping [ T ] ( s : ScopedTask [ T ] ) : ScopingSetting [ ScopedTask [ T ] ] =
new ScopingSetting ( scope => scopedTask ( Scope . replaceThis ( s . scope ) ( scope ) , s . key ) )
2011-01-29 03:15:39 +01:00
2011-03-01 14:48:14 +01:00
implicit def scopedInputScoping [ T ] ( s : ScopedInput [ T ] ) : ScopingSetting [ ScopedInput [ T ] ] =
new ScopingSetting ( scope => scopedInput ( Scope . replaceThis ( s . scope ) ( scope ) , s . key ) )
2011-02-06 17:33:29 +01:00
2011-03-01 14:48:14 +01:00
implicit def settingScoping [ T ] ( s : SettingKey [ T ] ) : ScopingSetting [ ScopedSetting [ T ] ] =
new ScopingSetting ( scope => scopedSetting ( scope , s . key ) )
implicit def inputScoping [ T ] ( s : InputKey [ T ] ) : ScopingSetting [ ScopedInput [ T ] ] =
new ScopingSetting ( scope => scopedInput ( scope , s . key ) )
implicit def taskScoping [ T ] ( s : TaskKey [ T ] ) : ScopingSetting [ ScopedTask [ T ] ] =
new ScopingSetting ( scope => scopedTask ( scope , s . key ) )
final class ScopingSetting [ Result ] ( app0 : Scope => Result )
2011-01-19 00:24:11 +01:00
{
2011-02-05 04:02:39 +01:00
def in ( s : Scope ) : Result = app0 ( s )
2011-03-03 12:44:19 +01:00
def in ( p : Reference ) : Result = in ( Select ( p ) , This , This )
2011-02-10 14:16:07 +01:00
def in ( t : Scoped ) : Result = in ( This , This , Select ( t . key ) )
2011-02-05 04:02:39 +01:00
def in ( c : ConfigKey ) : Result = in ( This , Select ( c ) , This )
2011-02-10 14:16:07 +01:00
def in ( c : ConfigKey , t : Scoped ) : Result = in ( This , Select ( c ) , Select ( t . key ) )
2011-03-03 12:44:19 +01:00
def in ( p : Reference , c : ConfigKey ) : Result = in ( Select ( p ) , Select ( c ) , This )
def in ( p : Reference , t : Scoped ) : Result = in ( Select ( p ) , This , Select ( t . key ) )
def in ( p : Reference , c : ConfigKey , t : Scoped ) : Result = in ( Select ( p ) , Select ( c ) , Select ( t . key ) )
def in ( p : ScopeAxis [ Reference ] , c : ScopeAxis [ ConfigKey ] , t : ScopeAxis [ AttributeKey [ _ ] ] ) : Result = in ( Scope ( p , c , t , This ) )
2011-01-19 00:24:11 +01:00
}
2011-01-29 03:15:39 +01:00
2011-02-12 02:22:17 +01:00
private [ this ] def scopedSetting [ T ] ( s : Scope , k : AttributeKey [ T ] ) : ScopedSetting [ T ] = new ScopedSetting [ T ] { val scope = s ; val key = k }
2011-01-29 03:15:39 +01:00
private [ this ] def scopedInput [ T ] ( s : Scope , k : AttributeKey [ InputTask [ T ] ] ) : ScopedInput [ T ] = new ScopedInput [ T ] { val scope = s ; val key = k }
2011-02-12 02:22:17 +01:00
private [ this ] def scopedTask [ T ] ( s : Scope , k : AttributeKey [ Task [ T ] ] ) : ScopedTask [ T ] = new ScopedTask [ T ] { val scope = s ; val key = k }
2011-01-19 00:24:11 +01:00
2011-05-13 04:33:45 +02:00
sealed abstract class RichXList [ S , M [ _ ] ]
2011-02-05 04:02:39 +01:00
{
2011-05-13 04:33:45 +02:00
protected [ this ] def make [ T ] ( other : Initialize [ M [ T ] ] ) ( f : ( Seq [ S ] , T ) => Seq [ S ] ) : Setting [ M [ Seq [ S ] ] ]
protected [ this ] def update ( f : Seq [ S ] => Seq [ S ] ) : Setting [ M [ Seq [ S ] ] ]
def <+= ( value : Initialize [ M [ S ] ] ) : Setting [ M [ Seq [ S ] ] ] = make ( value ) { _ : + _ }
def <++= ( values : Initialize [ M [ Seq [ S ] ] ] ) : Setting [ M [ Seq [ S ] ] ] = make ( values ) { _ ++ _ }
def += ( value : => S ) : Setting [ M [ Seq [ S ] ] ] = update ( _ : + value )
def ++= ( values : => Seq [ S ] ) : Setting [ M [ Seq [ S ] ] ] = update ( _ ++ values )
2011-02-05 04:02:39 +01:00
}
2011-05-13 04:33:45 +02:00
final class RichSettingList [ S ] ( scope : Scope , key : AttributeKey [ Seq [ S ] ] ) extends RichXList [ S , Id ]
2011-02-05 04:02:39 +01:00
{
2011-05-13 04:33:45 +02:00
private [ this ] val base = new RichSettingScoped ( scope , key )
protected [ this ] def make [ T ] ( other : Initialize [ T ] ) ( f : ( Seq [ S ] , T ) => Seq [ S ] ) : Setting [ Seq [ S ] ] = base <<= ( base . identity zipWith other ) ( f )
protected [ this ] def update ( f : Seq [ S ] => Seq [ S ] ) : Setting [ Seq [ S ] ] = base ~= f
}
final class RichListTask [ S ] ( scope : Scope , key : AttributeKey [ Task [ Seq [ S ] ] ] ) extends RichXList [ S , Task ]
{
private [ this ] val base = new RichTaskScoped ( scope , key )
protected [ this ] def make [ T ] ( other : Initialize [ Task [ T ] ] ) ( f : ( Seq [ S ] , T ) => Seq [ S ] ) : Setting [ Task [ Seq [ S ] ] ] = base <<= ( base . identity zipWith other ) { ( a , b ) => ( a , b ) map f }
protected [ this ] def update ( f : Seq [ S ] => Seq [ S ] ) : Setting [ Task [ Seq [ S ] ] ] = base ~= f
2011-02-05 04:02:39 +01:00
}
2011-01-19 00:24:11 +01:00
sealed abstract class RichBaseScoped [ S ]
{
def scope : Scope
def key : AttributeKey [ S ]
2011-04-21 05:33:53 +02:00
final val scoped = ScopedKey ( scope , key )
2011-01-19 00:24:11 +01:00
final def : = = ( value : S ) : Setting [ S ] = : = ( value )
2011-02-12 02:22:17 +01:00
final def : = ( value : => S ) : Setting [ S ] = setting ( scoped , Project . value ( value ) )
2011-02-05 04:02:39 +01:00
final def ~= ( f : S => S ) : Setting [ S ] = Project . update ( scoped ) ( f )
2011-02-12 02:22:17 +01:00
final def <<= ( app : Initialize [ S ] ) : Setting [ S ] = setting ( scoped , app )
2011-01-19 00:24:11 +01:00
2011-02-12 02:22:17 +01:00
final def apply [ T ] ( f : S => T ) : Initialize [ T ] = Apply . single ( scoped ) ( f )
2011-05-08 04:02:06 +02:00
final def identity : Initialize [ S ] = apply ( idFun )
final def ? : Initialize [ Option [ S ] ] = Project . optional ( scoped ) ( idFun )
final def ?? [ T >: S ] ( or : => T ) : Initialize [ T ] = Project . optional ( scoped ) ( _ getOrElse or )
2011-01-19 00:24:11 +01:00
2011-01-29 03:15:39 +01:00
final def get ( settings : Settings [ Scope ] ) : Option [ S ] = settings . get ( scope , key )
2011-01-19 00:24:11 +01:00
}
2011-02-12 02:22:17 +01:00
final class RichInputScoped [ T ] ( val scope : Scope , val key : AttributeKey [ InputTask [ T ] ] ) extends RichBaseScoped [ InputTask [ T ] ]
final class RichSettingScoped [ S ] ( val scope : Scope , val key : AttributeKey [ S ] ) extends RichBaseScoped [ S ]
2011-01-19 00:24:11 +01:00
{
2011-04-12 04:12:03 +02:00
def map [ T ] ( f : S => T ) : Initialize [ Task [ T ] ] = flatMap ( s => mktask ( f ( s ) ) )
2011-02-12 02:22:17 +01:00
def flatMap [ T ] ( f : S => Task [ T ] ) : Initialize [ Task [ T ] ] = Apply . single ( scoped ) ( f )
2011-01-19 00:24:11 +01:00
}
2011-02-12 02:22:17 +01:00
final class RichTaskScoped [ S ] ( scope : Scope , key : AttributeKey [ Task [ S ] ] )
2011-01-19 00:24:11 +01:00
{
type ScS = Setting [ Task [ S ] ]
def : = = ( value : S ) : ScS = : = ( value )
2011-02-12 02:22:17 +01:00
def : := ( value : Task [ S ] ) : ScS = Project . setting ( scoped , Project . value ( value ) )
2011-04-12 04:12:03 +02:00
def : = ( value : => S ) : ScS = : := ( mktask ( value ) )
2011-04-05 01:10:35 +02:00
def : = = ( v : ScopedSetting [ S ] ) : ScS = <<= ( v ( const ) )
2011-02-05 04:02:39 +01:00
def ~= ( f : S => S ) : ScS = Project . update ( scoped ) ( _ map f )
2011-01-19 00:24:11 +01:00
2011-02-12 02:22:17 +01:00
def <<= ( app : App [ S ] ) : ScS = Project . setting ( scoped , app )
2011-01-19 00:24:11 +01:00
2011-04-12 04:12:03 +02:00
def task : ScopedSetting [ Task [ S ] ] = scopedSetting ( scope , key )
2011-01-19 00:24:11 +01:00
def get ( settings : Settings [ Scope ] ) : Option [ Task [ S ] ] = settings . get ( scope , key )
2011-02-12 02:22:17 +01:00
type App [ T ] = Initialize [ Task [ T ] ]
2011-04-21 05:33:53 +02:00
def scoped = ScopedKey ( scope , key )
2011-02-12 02:22:17 +01:00
private [ this ] def mk [ T ] ( onTask : Task [ S ] => Task [ T ] ) : App [ T ] = Apply . single ( scoped ) ( onTask )
2011-01-19 00:24:11 +01:00
def flatMapR [ T ] ( f : Result [ S ] => Task [ T ] ) : App [ T ] = mk ( _ flatMapR f )
2011-01-29 03:15:39 +01:00
def flatMap [ T ] ( f : S => Task [ T ] ) : App [ T ] = flatMapR ( f compose successM )
def map [ T ] ( f : S => T ) : App [ T ] = mapR ( f compose successM )
2011-01-19 00:24:11 +01:00
def mapR [ T ] ( f : Result [ S ] => T ) : App [ T ] = mk ( _ mapR f )
2011-01-29 03:15:39 +01:00
def flatFailure [ T ] ( f : Incomplete => Task [ T ] ) : App [ T ] = flatMapR ( f compose failM )
def mapFailure [ T ] ( f : Incomplete => T ) : App [ T ] = mapR ( f compose failM )
2011-01-19 00:24:11 +01:00
def andFinally ( fin : => Unit ) : App [ S ] = mk ( _ andFinally fin )
def doFinally ( t : Task [ Unit ] ) : App [ S ] = mk ( _ doFinally t )
2011-04-16 17:24:58 +02:00
def identity : App [ S ] = mk ( idFun )
2011-05-08 04:02:06 +02:00
def ? : Initialize [ Task [ Option [ S ] ] ] = Project . optional ( scoped ) { case None => mktask { None } ; case Some ( t ) => t map some . fn }
def ?? [ T >: S ] ( or : => T ) : Initialize [ Task [ T ] ] = Project . optional ( scoped ) ( _ getOrElse mktask ( or ) )
2011-01-19 00:24:11 +01:00
def || [ T >: S ] ( alt : Task [ T ] ) : App [ T ] = mk ( _ || alt )
def && [ T ] ( alt : Task [ T ] ) : App [ T ] = mk ( _ && alt )
def dependsOn ( tasks : ScopedTask [ _ ] * ) : App [ S ] =
{
2011-02-12 02:22:17 +01:00
val in = KCons ( scopedTask ( scope , key ) , KList . fromList ( tasks ) )
2011-01-29 03:15:39 +01:00
Apply . tasks ( in ) { kl =>
val KCons ( h , t ) = KList . kcons ( kl )
h . dependsOn ( t . toList : _ * )
}
2011-01-19 00:24:11 +01:00
}
}
2011-03-01 14:48:14 +01:00
implicit def richSettingSeq [ T ] ( in : Seq [ ScopedSetting [ T ] ] ) : RichSettingSeq [ T ] = new RichSettingSeq ( in )
final class RichSettingSeq [ T ] ( keys : Seq [ ScopedSetting [ T ] ] )
{
2011-04-16 17:24:58 +02:00
def join : Initialize [ Seq [ T ] ] = joinWith ( idFun )
2011-03-01 14:48:14 +01:00
def joinWith [ S ] ( f : Seq [ T ] => S ) : Initialize [ S ] = Apply . uniform ( keys ) ( f )
}
implicit def richTaskSeq [ T ] ( in : Seq [ ScopedTask [ T ] ] ) : RichTaskSeq [ T ] = new RichTaskSeq ( in )
final class RichTaskSeq [ T ] ( keys : Seq [ ScopedTask [ T ] ] )
{
def join : Initialize [ Task [ Seq [ T ] ] ] = Apply . uniformTasks ( keys )
}
implicit def richAnyTaskSeq ( in : Seq [ ScopedTask [ _ ] ] ) : RichAnyTaskSeq = new RichAnyTaskSeq ( in )
final class RichAnyTaskSeq ( keys : Seq [ ScopedTask [ _ ] ] )
2011-02-10 14:16:07 +01:00
{
2011-02-12 02:22:17 +01:00
def dependOn : Initialize [ Task [ Unit ] ] = Apply . tasks ( KList . fromList ( keys ) ) { kl => nop . dependsOn ( kl . toList : _ * ) }
2011-02-10 14:16:07 +01:00
}
2011-04-23 17:49:58 +02:00
final class RichInitializeTask [ T ] ( init : Initialize [ Task [ T ] ] )
{
def triggeredBy ( tasks : ScopedTask [ _ ] * ) : Initialize [ Task [ T ] ] = nonLocal ( tasks , Keys . triggeredBy )
def runBefore ( tasks : ScopedTask [ _ ] * ) : Initialize [ Task [ T ] ] = nonLocal ( tasks , Keys . runBefore )
private [ this ] def nonLocal ( tasks : Seq [ ScopedTask [ _ ] ] , key : AttributeKey [ Seq [ Task [ _ ] ] ] ) : Initialize [ Task [ T ] ] =
{
val getTasks = Apply . tasks ( KList . fromList ( tasks ) ) ( idFun )
( getTasks zipWith init ) { ( tasks , i ) =>
i . copy ( info = i . info . set ( key , tasks . toList ) )
}
}
}
2011-04-14 13:32:42 +02:00
implicit def richFileSetting ( s : ScopedSetting [ File ] ) : RichFileSetting = new RichFileSetting ( s )
implicit def richFilesSetting ( s : ScopedSetting [ Seq [ File ] ] ) : RichFilesSetting = new RichFilesSetting ( s )
final class RichFileSetting ( s : ScopedSetting [ File ] ) extends RichFileBase
{
def / ( c : String ) : Initialize [ File ] = s { _ / c }
protected [ this ] def map0 ( f : PathFinder => PathFinder ) = s ( file => finder ( f ) ( file : : Nil ) )
}
final class RichFilesSetting ( s : ScopedSetting [ Seq [ File ] ] ) extends RichFileBase
{
def / ( s : String ) : Initialize [ Seq [ File ] ] = map0 { _ / s }
protected [ this ] def map0 ( f : PathFinder => PathFinder ) = s ( finder ( f ) )
}
sealed abstract class RichFileBase
{
def * ( filter : FileFilter ) : Initialize [ Seq [ File ] ] = map0 { _ * filter }
def ** ( filter : FileFilter ) : Initialize [ Seq [ File ] ] = map0 { _ ** filter }
protected [ this ] def map0 ( f : PathFinder => PathFinder ) : Initialize [ Seq [ File ] ]
protected [ this ] def finder ( f : PathFinder => PathFinder ) : Seq [ File ] => Seq [ File ] =
in => f ( in ) . getFiles
}
2011-01-29 03:15:39 +01:00
/*
* Reduced and combine provide support for mixed Setting / Task flatMap / map .
* The general idea is to take a KList of ScopedTaskables , which are either ScopedSettings or ScopedTasks ,
* and uniformly provide multi - flatMap / map for constructing a new Task .
* For example : { { { ( SettingKeyA , TaskKeyB ) flatMap { ( a , b ) => . . . } } } }
*/
trait Reduced [ HLs <: HList , HLt <: HList , HLv <: HList ]
{ o =>
def settings : KList [ ScopedSetting , HLs ] // SS[A] :^: SS[Task[B]] :^: ...
def tasks ( hls : HLs ) : KList [ Task , HLt ] // takes setting values from previous line to Task[B] :^: ...
def expand ( hls : HLs , hlt : Results [ HLt ] ) : Results [ HLv ] // takes Result[B] :+: ... to Value[A] :+: Result[B] :+: ...
def prependTask [ H ] ( key : ScopedSetting [ Task [ H ] ] ) =
new Reduced [ Task [ H ] :+: HLs , H :+: HLt , H :+: HLv ]
{
val settings = KCons ( key , o . settings )
def tasks ( hls : Task [ H ] : +: HLs ) = KCons ( hls . head , o . tasks ( hls . tail ) )
def expand ( hls : Task [ H ] : +: HLs , hlt : Results [ H :+: HLt ] ) = KCons ( hlt . head , o . expand ( hls . tail , hlt . tail ) )
}
def prependSetting [ H ] ( key : ScopedSetting [ H ] ) =
new Reduced [ H :+: HLs , HLt , H :+: HLv ]
{
val settings = KCons ( key , o . settings )
def tasks ( hls : H :+: HLs ) = o . tasks ( hls . tail )
def expand ( hls : H :+: HLs , hlt : Results [ HLt ] ) = KCons ( Value ( hls . head ) , o . expand ( hls . tail , hlt ) )
}
def prependTaskable [ H ] ( key : ScopedTaskable [ H ] ) : Reduced [ _ ,_ ,H :+: HLv ] =
key match
{
case ss : ScopedSetting [ H ] => prependSetting ( ss )
2011-02-12 02:22:17 +01:00
case st : ScopedTask [ H ] => prependTask ( scopedSetting ( st . scope , st . key ) )
2011-01-29 03:15:39 +01:00
}
2011-02-12 02:22:17 +01:00
def combine [ D [ _ ] ,S ] ( c : Combine [ D ] , f : Results [ HLv ] => D [ S ] ) : Initialize [ Task [ S ] ] =
2011-01-29 03:15:39 +01:00
Apply ( settings ) ( hls => c ( tasks ( hls ) ) ( hlt => f ( expand ( hls , hlt ) ) ) )
}
type RedHL [ HL <: HList ] = Reduced [ _ ,_ ,HL ]
def reduced [ HL <: HList ] ( settings : KList [ ScopedTaskable , HL ] ) : Reduced [ _ ,_ ,HL ] =
settings . foldr { new KFold [ ScopedTaskable , RedHL ] {
def knil = emptyReduced
def kcons [ H ,T <: HList ] ( h : ScopedTaskable [ H ] , acc : Reduced [ _ ,_ ,T ] ) : Reduced [ _ ,_ ,H :+: T ] =
acc prependTaskable h
} }
def emptyReduced : Reduced [ HNil ,HNil ,HNil ] = new Reduced [ HNil ,HNil ,HNil ] {
def settings = KNil
def tasks ( h : HNil ) = KNil
def expand ( a : HNil , k : Results [ HNil ] ) = KNil
}
trait Combine [ D [ _ ] ] {
def apply [ HL <: HList ,S ] ( tasks : KList [ Task , HL ] ) ( f : Results [ HL ] => D [ S ] ) : Task [ S ]
}
object Combine
2011-01-19 00:24:11 +01:00
{
2011-01-29 03:15:39 +01:00
val mapR : Combine [ Id ] = new Combine [ Id ] {
def apply [ HL <: HList ,S ] ( tasks : KList [ Task , HL ] ) ( f : Results [ HL ] => S ) : Task [ S ] =
tasks mapR f
}
val flatMapR : Combine [ Task ] = new Combine [ Task ] {
def apply [ HL <: HList ,S ] ( tasks : KList [ Task , HL ] ) ( f : Results [ HL ] => Task [ S ] ) : Task [ S ] =
tasks flatMapR f
}
2011-01-19 00:24:11 +01:00
}
2011-01-31 05:19:28 +01:00
// this is the least painful arrangement I came up with
implicit def t2ToTable2 [ A ,B ] ( t2 : ( ScopedTaskable [ A ] , ScopedTaskable [ B ] ) ) : RichTaskable2 [ A ,B ] = new RichTaskable2 ( t2 )
implicit def t3ToTable3 [ A ,B ,C ] ( t3 : ( ScopedTaskable [ A ] , ScopedTaskable [ B ] , ScopedTaskable [ C ] ) ) : RichTaskable3 [ A ,B ,C ] = new RichTaskable3 ( t3 )
implicit def t4ToTable4 [ A ,B ,C ,D ] ( t4 : ( ScopedTaskable [ A ] , ScopedTaskable [ B ] , ScopedTaskable [ C ] , ScopedTaskable [ D ] ) ) : RichTaskable4 [ A ,B ,C ,D ] = new RichTaskable4 ( t4 )
implicit def t5ToTable5 [ A ,B ,C ,D ,E ] ( t5 : ( ScopedTaskable [ A ] , ScopedTaskable [ B ] , ScopedTaskable [ C ] , ScopedTaskable [ D ] , ScopedTaskable [ E ] ) ) : RichTaskable5 [ A ,B ,C ,D ,E ] = new RichTaskable5 ( t5 )
implicit def t6ToTable6 [ A ,B ,C ,D ,E ,F ] ( t6 : ( ScopedTaskable [ A ] , ScopedTaskable [ B ] , ScopedTaskable [ C ] , ScopedTaskable [ D ] , ScopedTaskable [ E ] , ScopedTaskable [ F ] ) ) : RichTaskable6 [ A ,B ,C ,D ,E ,F ] = new RichTaskable6 ( t6 )
implicit def t7ToTable7 [ A ,B ,C ,D ,E ,F ,G ] ( t7 : ( ScopedTaskable [ A ] , ScopedTaskable [ B ] , ScopedTaskable [ C ] , ScopedTaskable [ D ] , ScopedTaskable [ E ] , ScopedTaskable [ F ] , ScopedTaskable [ G ] ) ) : RichTaskable7 [ A ,B ,C ,D ,E ,F ,G ] = new RichTaskable7 ( t7 )
implicit def t8ToTable8 [ A ,B ,C ,D ,E ,F ,G ,H ] ( t8 : ( ScopedTaskable [ A ] , ScopedTaskable [ B ] , ScopedTaskable [ C ] , ScopedTaskable [ D ] , ScopedTaskable [ E ] , ScopedTaskable [ F ] , ScopedTaskable [ G ] , ScopedTaskable [ H ] ) ) : RichTaskable8 [ A ,B ,C ,D ,E ,F ,G ,H ] = new RichTaskable8 ( t8 )
implicit def t9ToTable9 [ A ,B ,C ,D ,E ,F ,G ,H ,I ] ( t9 : ( ScopedTaskable [ A ] , ScopedTaskable [ B ] , ScopedTaskable [ C ] , ScopedTaskable [ D ] , ScopedTaskable [ E ] , ScopedTaskable [ F ] , ScopedTaskable [ G ] , ScopedTaskable [ H ] , ScopedTaskable [ I ] ) ) : RichTaskable9 [ A ,B ,C ,D ,E ,F ,G ,H ,I ] = new RichTaskable9 ( t9 )
sealed abstract class RichTaskables [ In <: HList ] ( keys : KList [ ScopedTaskable , In ] )
{
2011-02-12 02:22:17 +01:00
type App [ T ] = Initialize [ Task [ T ] ]
2011-01-31 05:19:28 +01:00
type Fun [ M [ _ ] ,Ret ]
protected def convertH [ Ret ] ( f : Fun [ Id ,Ret ] ) : In => Ret
protected def convertK [ M [ _ ] ,Ret ] ( f : Fun [ M ,Ret ] ) : KList [ M ,In ] => Ret
private [ this ] val red = reduced ( keys )
2011-04-16 17:24:58 +02:00
2011-01-31 05:19:28 +01:00
def flatMap [ T ] ( f : Fun [ Id ,Task [ T ] ] ) : App [ T ] = red . combine ( Combine . flatMapR , convertH ( f ) compose allM )
def flatMapR [ T ] ( f : Fun [ Result ,Task [ T ] ] ) : App [ T ] = red . combine ( Combine . flatMapR , convertK ( f ) )
def map [ T ] ( f : Fun [ Id , T ] ) : App [ T ] = red . combine [ Id ,T ] ( Combine . mapR , convertH ( f ) compose allM )
def mapR [ T ] ( f : Fun [ Result ,T ] ) : App [ T ] = red . combine [ Id ,T ] ( Combine . mapR , convertK ( f ) )
def flatFailure [ T ] ( f : Seq [ Incomplete ] => Task [ T ] ) : App [ T ] = red . combine ( Combine . flatMapR , f compose anyFailM )
def mapFailure [ T ] ( f : Seq [ Incomplete ] => T ) : App [ T ] = red . combine [ Id ,T ] ( Combine . mapR , f compose anyFailM )
}
2011-04-16 18:05:42 +02:00
final class RichTaskable2 [ A ,B ] ( t2 : ( ScopedTaskable [ A ] , ScopedTaskable [ B ] ) ) extends RichTaskables ( k2 ( t2 ) )
2011-01-31 05:19:28 +01:00
{
type Fun [ M [ _ ] ,Ret ] = ( M [ A ] , M [ B ] ) => Ret
2011-04-16 18:05:42 +02:00
def identityMap = map ( mkTuple2 )
protected def convertH [ R ] ( z : ( A , B ) => R ) = hf2 ( z )
2011-01-31 05:19:28 +01:00
protected def convertK [ M [ _ ] ,R ] ( f : ( M [ A ] , M [ B ] ) => R ) = { case a : ^: b :^: KNil => f ( a , b ) }
}
2011-04-16 18:05:42 +02:00
final class RichTaskable3 [ A ,B ,C ] ( t3 : ( ScopedTaskable [ A ] , ScopedTaskable [ B ] , ScopedTaskable [ C ] ) ) extends RichTaskables ( k3 ( t3 ) )
2011-01-31 05:19:28 +01:00
{
type Fun [ M [ _ ] ,Ret ] = ( M [ A ] , M [ B ] , M [ C ] ) => Ret
2011-04-16 18:05:42 +02:00
def identityMap = map ( mkTuple3 )
protected def convertH [ R ] ( z : Fun [ Id ,R ] ) = hf3 ( z )
2011-01-31 05:19:28 +01:00
protected def convertK [ M [ _ ] ,R ] ( f : Fun [ M ,R ] ) = { case a : ^: b :^: c :^: KNil => f ( a , b , c ) }
}
2011-04-16 18:05:42 +02:00
final class RichTaskable4 [ A ,B ,C ,D ] ( t4 : ( ScopedTaskable [ A ] , ScopedTaskable [ B ] , ScopedTaskable [ C ] , ScopedTaskable [ D ] ) ) extends RichTaskables ( k4 ( t4 ) )
2011-01-31 05:19:28 +01:00
{
type Fun [ M [ _ ] ,Ret ] = ( M [ A ] , M [ B ] , M [ C ] , M [ D ] ) => Ret
2011-04-16 18:05:42 +02:00
def identityMap = map ( mkTuple4 )
protected def convertH [ R ] ( z : Fun [ Id ,R ] ) = hf4 ( z )
2011-01-31 05:19:28 +01:00
protected def convertK [ M [ _ ] ,R ] ( f : Fun [ M ,R ] ) = { case a : ^: b :^: c :^: d :^: KNil => f ( a , b , c , d ) }
}
2011-04-16 18:05:42 +02:00
final class RichTaskable5 [ A ,B ,C ,D ,E ] ( t5 : ( ScopedTaskable [ A ] , ScopedTaskable [ B ] , ScopedTaskable [ C ] , ScopedTaskable [ D ] , ScopedTaskable [ E ] ) ) extends RichTaskables ( k5 ( t5 ) )
2011-01-31 05:19:28 +01:00
{
type Fun [ M [ _ ] ,Ret ] = ( M [ A ] , M [ B ] , M [ C ] , M [ D ] , M [ E ] ) => Ret
2011-04-16 18:05:42 +02:00
def identityMap = map ( mkTuple5 )
protected def convertH [ R ] ( z : Fun [ Id ,R ] ) = hf5 ( z )
2011-01-31 05:19:28 +01:00
protected def convertK [ M [ _ ] ,R ] ( f : Fun [ M ,R ] ) = { case a : ^: b :^: c :^: d :^: e :^: KNil => f ( a , b , c , d , e ) }
}
2011-04-16 18:05:42 +02:00
final class RichTaskable6 [ A ,B ,C ,D ,E ,F ] ( t6 : ( ScopedTaskable [ A ] , ScopedTaskable [ B ] , ScopedTaskable [ C ] , ScopedTaskable [ D ] , ScopedTaskable [ E ] , ScopedTaskable [ F ] ) ) extends RichTaskables ( k6 ( t6 ) )
2011-01-31 05:19:28 +01:00
{
type Fun [ M [ _ ] ,Ret ] = ( M [ A ] , M [ B ] , M [ C ] , M [ D ] , M [ E ] , M [ F ] ) => Ret
2011-04-16 18:05:42 +02:00
def identityMap = map ( mkTuple6 )
protected def convertH [ R ] ( z : Fun [ Id ,R ] ) = hf6 ( z )
2011-01-31 05:19:28 +01:00
protected def convertK [ M [ _ ] ,R ] ( z : Fun [ M ,R ] ) = { case a : ^: b :^: c :^: d :^: e :^: f :^: KNil => z ( a , b , c , d , e , f ) }
}
2011-04-16 18:05:42 +02:00
final class RichTaskable7 [ A ,B ,C ,D ,E ,F ,G ] ( t7 : ( ScopedTaskable [ A ] , ScopedTaskable [ B ] , ScopedTaskable [ C ] , ScopedTaskable [ D ] , ScopedTaskable [ E ] , ScopedTaskable [ F ] , ScopedTaskable [ G ] ) ) extends RichTaskables ( k7 ( t7 ) )
2011-01-31 05:19:28 +01:00
{
type Fun [ M [ _ ] ,Ret ] = ( M [ A ] , M [ B ] , M [ C ] , M [ D ] , M [ E ] , M [ F ] , M [ G ] ) => Ret
2011-04-16 18:05:42 +02:00
def identityMap = map ( mkTuple7 )
protected def convertH [ R ] ( z : Fun [ Id ,R ] ) = hf7 ( z )
2011-01-31 05:19:28 +01:00
protected def convertK [ M [ _ ] ,R ] ( z : Fun [ M ,R ] ) = { case a : ^: b :^: c :^: d :^: e :^: f :^: g :^: KNil => z ( a , b , c , d , e , f , g ) }
}
2011-04-16 18:05:42 +02:00
final class RichTaskable8 [ A ,B ,C ,D ,E ,F ,G ,H ] ( t8 : ( ScopedTaskable [ A ] , ScopedTaskable [ B ] , ScopedTaskable [ C ] , ScopedTaskable [ D ] , ScopedTaskable [ E ] , ScopedTaskable [ F ] , ScopedTaskable [ G ] , ScopedTaskable [ H ] ) ) extends RichTaskables ( k8 ( t8 ) )
2011-01-31 05:19:28 +01:00
{
type Fun [ M [ _ ] ,Ret ] = ( M [ A ] , M [ B ] , M [ C ] , M [ D ] , M [ E ] , M [ F ] , M [ G ] , M [ H ] ) => Ret
2011-04-16 18:05:42 +02:00
def identityMap = map ( mkTuple8 )
protected def convertH [ R ] ( z : Fun [ Id ,R ] ) = hf8 ( z )
2011-01-31 05:19:28 +01:00
protected def convertK [ M [ _ ] ,R ] ( z : Fun [ M ,R ] ) = { case a : ^: b :^: c :^: d :^: e :^: f :^: g :^: h :^: KNil => z ( a , b , c , d , e , f , g , h ) }
}
2011-04-16 18:05:42 +02:00
final class RichTaskable9 [ A ,B ,C ,D ,E ,F ,G ,H ,I ] ( t9 : ( ScopedTaskable [ A ] , ScopedTaskable [ B ] , ScopedTaskable [ C ] , ScopedTaskable [ D ] , ScopedTaskable [ E ] , ScopedTaskable [ F ] , ScopedTaskable [ G ] , ScopedTaskable [ H ] , ScopedTaskable [ I ] ) ) extends RichTaskables ( k9 ( t9 ) )
2011-01-31 05:19:28 +01:00
{
type Fun [ M [ _ ] ,Ret ] = ( M [ A ] , M [ B ] , M [ C ] , M [ D ] , M [ E ] , M [ F ] , M [ G ] , M [ H ] , M [ I ] ) => Ret
2011-04-16 18:05:42 +02:00
def identityMap = map ( mkTuple9 )
protected def convertH [ R ] ( z : Fun [ Id ,R ] ) = hf9 ( z )
2011-01-31 05:19:28 +01:00
protected def convertK [ M [ _ ] ,R ] ( z : Fun [ M ,R ] ) = { case a : ^: b :^: c :^: d :^: e :^: f :^: g :^: h :^: i :^: KNil => z ( a , b , c , d , e , f , g , h , i ) }
}
2011-01-29 03:15:39 +01:00
2011-01-31 05:19:28 +01:00
// this doesn't actually work for mixed KLists because the compiler crashes trying to infer the bound when constructing the KList
2011-01-29 03:15:39 +01:00
implicit def richTaskableKeys [ HL <: HList ] ( in : KList [ ScopedTaskable , HL ] ) : RichTaskableKeys [ HL ] = new RichTaskableKeys ( in )
final class RichTaskableKeys [ In <: HList ] ( keys : KList [ ScopedTaskable , In ] )
2011-01-19 00:24:11 +01:00
{
2011-02-12 02:22:17 +01:00
type App [ T ] = Initialize [ Task [ T ] ]
2011-01-29 03:15:39 +01:00
private [ this ] val red = reduced ( keys )
2011-04-16 17:24:58 +02:00
def identity : App [ In ] = map ( idFun )
2011-01-29 03:15:39 +01:00
def flatMap [ T ] ( f : In => Task [ T ] ) : App [ T ] = flatMapR ( f compose allM )
def flatMapR [ T ] ( f : Results [ In ] => Task [ T ] ) : App [ T ] = red . combine ( Combine . flatMapR , f )
def map [ T ] ( f : In => T ) : App [ T ] = mapR ( f compose allM )
def mapR [ T ] ( f : Results [ In ] => T ) : App [ T ] = red . combine [ Id ,T ] ( Combine . mapR , f )
def flatFailure [ T ] ( f : Seq [ Incomplete ] => Task [ T ] ) : App [ T ] = flatMapR ( f compose anyFailM )
def mapFailure [ T ] ( f : Seq [ Incomplete ] => T ) : App [ T ] = mapR ( f compose anyFailM )
2011-01-19 00:24:11 +01:00
}
implicit def t2ToApp2 [ A ,B ] ( t2 : ( ScopedSetting [ A ] , ScopedSetting [ B ] ) ) : Apply2 [ A ,B ] = new Apply2 ( t2 )
implicit def t3ToApp3 [ A ,B ,C ] ( t3 : ( ScopedSetting [ A ] , ScopedSetting [ B ] , ScopedSetting [ C ] ) ) : Apply3 [ A ,B ,C ] = new Apply3 ( t3 )
2011-01-29 17:22:59 +01:00
implicit def t4ToApp4 [ A ,B ,C ,D ] ( t4 : ( ScopedSetting [ A ] , ScopedSetting [ B ] , ScopedSetting [ C ] , ScopedSetting [ D ] ) ) : Apply4 [ A ,B ,C ,D ] = new Apply4 ( t4 )
2011-02-06 19:01:50 +01:00
implicit def t5ToApp5 [ A ,B ,C ,D ,E ] ( t5 : ( ScopedSetting [ A ] , ScopedSetting [ B ] , ScopedSetting [ C ] , ScopedSetting [ D ] , ScopedSetting [ E ] ) ) : Apply5 [ A ,B ,C ,D ,E ] = new Apply5 ( t5 )
2011-02-12 02:22:17 +01:00
implicit def t6ToApp6 [ A ,B ,C ,D ,E ,F ] ( t6 : ( ScopedSetting [ A ] , ScopedSetting [ B ] , ScopedSetting [ C ] , ScopedSetting [ D ] , ScopedSetting [ E ] , ScopedSetting [ F ] ) ) : Apply6 [ A ,B ,C ,D ,E ,F ] = new Apply6 ( t6 )
implicit def t7ToApp7 [ A ,B ,C ,D ,E ,F ,G ] ( t7 : ( ScopedSetting [ A ] , ScopedSetting [ B ] , ScopedSetting [ C ] , ScopedSetting [ D ] , ScopedSetting [ E ] , ScopedSetting [ F ] , ScopedSetting [ G ] ) ) : Apply7 [ A ,B ,C ,D ,E ,F ,G ] = new Apply7 ( t7 )
2011-04-16 18:05:42 +02:00
implicit def t8ToApp8 [ A ,B ,C ,D ,E ,F ,G ,H ] ( t8 : ( ScopedSetting [ A ] , ScopedSetting [ B ] , ScopedSetting [ C ] , ScopedSetting [ D ] , ScopedSetting [ E ] , ScopedSetting [ F ] , ScopedSetting [ G ] , ScopedSetting [ H ] ) ) : Apply8 [ A ,B ,C ,D ,E ,F ,G ,H ] = new Apply8 ( t8 )
implicit def t9ToApp9 [ A ,B ,C ,D ,E ,F ,G ,H ,I ] ( t9 : ( ScopedSetting [ A ] , ScopedSetting [ B ] , ScopedSetting [ C ] , ScopedSetting [ D ] , ScopedSetting [ E ] , ScopedSetting [ F ] , ScopedSetting [ G ] , ScopedSetting [ H ] , ScopedSetting [ I ] ) ) : Apply9 [ A ,B ,C ,D ,E ,F ,G ,H ,I ] = new Apply9 ( t9 )
2011-01-19 00:24:11 +01:00
object Apply
{
2011-02-12 02:22:17 +01:00
def single [ I ,T ] ( in : ScopedKey [ I ] ) ( f : I => T ) : Initialize [ T ] =
Project . app ( in : ^: KNil ) ( hl => f ( hl . head ) )
def apply [ HL <: HList , T ] ( in : KList [ ScopedSetting , HL ] ) ( f : HL => T ) : Initialize [ T ] =
Project . app ( in transform ssToSK ) ( f )
2011-03-01 14:48:14 +01:00
def uniformTasks [ S ] ( inputs : Seq [ ScopedTask [ S ] ] ) : Initialize [ Task [ Seq [ S ] ] ] =
Project . uniform ( inputs map stToSK . fn ) ( _ join )
def uniform [ S ,T ] ( inputs : Seq [ ScopedSetting [ S ] ] ) ( f : Seq [ S ] => T ) : Initialize [ T ] =
Project . uniform ( inputs map ssToSK . fn ) ( f )
2011-02-12 02:22:17 +01:00
def tasks [ HL <: HList , T ] ( in : KList [ ScopedTask , HL ] ) ( f : KList [ Task , HL ] => T ) : Initialize [ T ] =
2011-01-19 00:24:11 +01:00
{
val kapp = new Project . KApp [ HL , Task , T ]
2011-02-12 02:22:17 +01:00
kapp ( in transform stToSK ) ( f )
2011-01-19 00:24:11 +01:00
}
2011-02-12 02:22:17 +01:00
private val ssToSK = new ( ScopedSetting ~> ScopedKey ) { def apply [ T ] ( sk : ScopedSetting [ T ] ) = new ScopedKey ( sk . scope , sk . key ) }
private val stToSK = new ( ScopedTask ~> ScopedTaskKey ) { def apply [ T ] ( st : ScopedTask [ T ] ) = new ScopedKey ( st . scope , st . key ) }
2011-03-04 11:25:40 +01:00
type ScopedTaskKey [ T ] = ScopedKey [ Task [ T ] ]
2011-01-19 00:24:11 +01:00
}
2011-04-16 18:05:42 +02:00
def mkTuple2 [ A ,B ] = ( a : A , b : B ) => ( a , b )
def mkTuple3 [ A ,B ,C ] = ( a : A , b : B , c : C ) => ( a , b , c )
def mkTuple4 [ A ,B ,C ,D ] = ( a : A , b : B , c : C , d : D ) => ( a , b , c , d )
def mkTuple5 [ A ,B ,C ,D ,E ] = ( a : A , b : B , c : C , d : D , e : E ) => ( a , b , c , d , e )
def mkTuple6 [ A ,B ,C ,D ,E ,F ] = ( a : A , b : B , c : C , d : D , e : E , f : F ) => ( a , b , c , d , e , f )
def mkTuple7 [ A ,B ,C ,D ,E ,F ,G ] = ( a : A , b : B , c : C , d : D , e : E , f : F , g : G ) => ( a , b , c , d , e , f , g )
def mkTuple8 [ A ,B ,C ,D ,E ,F ,G ,H ] = ( a : A , b : B , c : C , d : D , e : E , f : F , g : G , h : H ) => ( a , b , c , d , e , f , g , h )
def mkTuple9 [ A ,B ,C ,D ,E ,F ,G ,H ,I ] = ( a : A , b : B , c : C , d : D , e : E , f : F , g : G , h : H , i : I ) => ( a , b , c , d , e , f , g , h , i )
2011-01-19 00:24:11 +01:00
final class Apply2 [ A ,B ] ( t2 : ( ScopedSetting [ A ] , ScopedSetting [ B ] ) ) {
2011-04-16 18:05:42 +02:00
def apply [ T ] ( z : ( A , B ) => T ) = Apply ( k2 ( t2 ) ) ( hf2 ( z ) )
def identity = apply ( mkTuple2 )
2011-01-19 00:24:11 +01:00
}
final class Apply3 [ A ,B ,C ] ( t3 : ( ScopedSetting [ A ] , ScopedSetting [ B ] , ScopedSetting [ C ] ) ) {
2011-04-16 18:05:42 +02:00
def apply [ T ] ( z : ( A , B , C ) => T ) = Apply ( k3 ( t3 ) ) ( hf3 ( z ) )
def identity = apply ( mkTuple3 )
2011-01-19 00:24:11 +01:00
}
2011-01-29 17:22:59 +01:00
final class Apply4 [ A ,B ,C ,D ] ( t4 : ( ScopedSetting [ A ] , ScopedSetting [ B ] , ScopedSetting [ C ] , ScopedSetting [ D ] ) ) {
2011-04-16 18:05:42 +02:00
def apply [ T ] ( z : ( A , B , C , D ) => T ) = Apply ( k4 ( t4 ) ) ( hf4 ( z ) )
def identity = apply ( mkTuple4 )
2011-01-29 17:22:59 +01:00
}
2011-02-06 19:01:50 +01:00
final class Apply5 [ A ,B ,C ,D ,E ] ( t5 : ( ScopedSetting [ A ] , ScopedSetting [ B ] , ScopedSetting [ C ] , ScopedSetting [ D ] , ScopedSetting [ E ] ) ) {
2011-04-16 18:05:42 +02:00
def apply [ T ] ( z : ( A , B , C , D , E ) => T ) = Apply ( k5 ( t5 ) ) ( hf5 ( z ) )
def identity = apply ( mkTuple5 )
2011-02-06 19:01:50 +01:00
}
2011-02-12 02:22:17 +01:00
final class Apply6 [ A ,B ,C ,D ,E ,F ] ( t6 : ( ScopedSetting [ A ] , ScopedSetting [ B ] , ScopedSetting [ C ] , ScopedSetting [ D ] , ScopedSetting [ E ] , ScopedSetting [ F ] ) ) {
2011-04-16 18:05:42 +02:00
def apply [ T ] ( z : ( A , B , C , D , E , F ) => T ) = Apply ( k6 ( t6 ) ) ( hf6 ( z ) )
def identity = apply ( mkTuple6 )
2011-02-12 02:22:17 +01:00
}
final class Apply7 [ A ,B ,C ,D ,E ,F ,G ] ( t7 : ( ScopedSetting [ A ] , ScopedSetting [ B ] , ScopedSetting [ C ] , ScopedSetting [ D ] , ScopedSetting [ E ] , ScopedSetting [ F ] , ScopedSetting [ G ] ) ) {
2011-04-16 18:05:42 +02:00
def apply [ T ] ( z : ( A , B , C , D , E , F , G ) => T ) = Apply ( k7 ( t7 ) ) ( hf7 ( z ) )
def identity = apply ( mkTuple7 )
}
final class Apply8 [ A ,B ,C ,D ,E ,F ,G ,H ] ( t8 : ( ScopedSetting [ A ] , ScopedSetting [ B ] , ScopedSetting [ C ] , ScopedSetting [ D ] , ScopedSetting [ E ] , ScopedSetting [ F ] , ScopedSetting [ G ] , ScopedSetting [ H ] ) ) {
def apply [ T ] ( z : ( A , B , C , D , E , F , G , H ) => T ) = Apply ( k8 ( t8 ) ) ( hf8 ( z ) )
def identity = apply ( mkTuple8 )
}
final class Apply9 [ A ,B ,C ,D ,E ,F ,G ,H ,I ] ( t9 : ( ScopedSetting [ A ] , ScopedSetting [ B ] , ScopedSetting [ C ] , ScopedSetting [ D ] , ScopedSetting [ E ] , ScopedSetting [ F ] , ScopedSetting [ G ] , ScopedSetting [ H ] , ScopedSetting [ I ] ) ) {
def apply [ T ] ( z : ( A , B , C , D , E , F , G , H , I ) => T ) = Apply ( k9 ( t9 ) ) ( hf9 ( z ) )
def identity = apply ( mkTuple9 )
}
def hf2 [ A , B , T ] ( z : ( A , B ) => T ) : A :+: B :+: HNil => T = { case a : +: b :+: HNil => z ( a , b ) }
def hf3 [ A , B , C , T ] ( z : ( A , B , C ) => T ) : A :+: B :+: C :+: HNil => T = { case a : +: b :+: c :+: HNil => z ( a , b , c ) }
def hf4 [ A , B , C , D , T ] ( z : ( A , B , C , D ) => T ) : A :+: B :+: C :+: D :+: HNil => T = { case a : +: b :+: c :+: d :+: HNil => z ( a , b , c , d ) }
def hf5 [ A , B , C , D , E , T ] ( z : ( A , B , C , D , E ) => T ) : A :+: B :+: C :+: D :+: E :+: HNil => T = { case a : +: b :+: c :+: d :+: e :+: HNil => z ( a , b , c , d , e ) }
def hf6 [ A , B , C , D , E , F , T ] ( z : ( A , B , C , D , E , F ) => T ) : A :+: B :+: C :+: D :+: E :+: F :+: HNil => T = { case a : +: b :+: c :+: d :+: e :+: f :+: HNil => z ( a , b , c , d , e , f ) }
def hf7 [ A , B , C , D , E , F , G , T ] ( z : ( A , B , C , D , E , F , G ) => T ) : A :+: B :+: C :+: D :+: E :+: F :+: G :+: HNil => T = { case a : +: b :+: c :+: d :+: e :+: f :+: g :+: HNil => z ( a , b , c , d , e , f , g ) }
def hf8 [ A , B , C , D , E , F , G , H , T ] ( z : ( A , B , C , D , E , F , G , H ) => T ) : A :+: B :+: C :+: D :+: E :+: F :+: G :+: H :+: HNil => T = { case a : +: b :+: c :+: d :+: e :+: f :+: g :+: h :+: HNil => z ( a , b , c , d , e , f , g , h ) }
def hf9 [ A , B , C , D , E , F , G , H , I , T ] ( z : ( A , B , C , D , E , F , G , H , I ) => T ) : A :+: B :+: C :+: D :+: E :+: F :+: G :+: H :+: I :+: HNil => T = { case a : +: b :+: c :+: d :+: e :+: f :+: g :+: h :+: i :+: HNil => z ( a , b , c , d , e , f , g , h , i ) }
def k2 [ M [ _ ] , A , B ] ( t2 : ( M [ A ] , M [ B ] ) ) = t2 . _1 : ^: t2 . _ 2 :^: KNil
def k3 [ M [ _ ] , A , B , C ] ( t3 : ( M [ A ] , M [ B ] , M [ C ] ) ) = t3 . _1 : ^: t3 . _ 2 :^: t3 . _ 3 :^: KNil
def k4 [ M [ _ ] , A , B , C , D ] ( t4 : ( M [ A ] , M [ B ] , M [ C ] , M [ D ] ) ) = t4 . _1 : ^: t4 . _ 2 :^: t4 . _ 3 :^: t4 . _ 4 :^: KNil
def k5 [ M [ _ ] , A , B , C , D , E ] ( t5 : ( M [ A ] , M [ B ] , M [ C ] , M [ D ] , M [ E ] ) ) = t5 . _1 : ^: t5 . _ 2 :^: t5 . _ 3 :^: t5 . _ 4 :^: t5 . _ 5 :^: KNil
def k6 [ M [ _ ] , A , B , C , D , E , F ] ( t6 : ( M [ A ] , M [ B ] , M [ C ] , M [ D ] , M [ E ] , M [ F ] ) ) = t6 . _1 : ^: t6 . _ 2 :^: t6 . _ 3 :^: t6 . _ 4 :^: t6 . _ 5 :^: t6 . _ 6 :^: KNil
def k7 [ M [ _ ] , A , B , C , D , E , F , G ] ( t7 : ( M [ A ] , M [ B ] , M [ C ] , M [ D ] , M [ E ] , M [ F ] , M [ G ] ) ) = t7 . _1 : ^: t7 . _ 2 :^: t7 . _ 3 :^: t7 . _ 4 :^: t7 . _ 5 :^: t7 . _ 6 :^: t7 . _ 7 :^: KNil
def k8 [ M [ _ ] , A , B , C , D , E , F , G , H ] ( t8 : ( M [ A ] , M [ B ] , M [ C ] , M [ D ] , M [ E ] , M [ F ] , M [ G ] , M [ H ] ) ) = t8 . _1 : ^: t8 . _ 2 :^: t8 . _ 3 :^: t8 . _ 4 :^: t8 . _ 5 :^: t8 . _ 6 :^: t8 . _ 7 :^: t8 . _ 8 :^: KNil
def k9 [ M [ _ ] , A , B , C , D , E , F , G , H , I ] ( t9 : ( M [ A ] , M [ B ] , M [ C ] , M [ D ] , M [ E ] , M [ F ] , M [ G ] , M [ H ] , M [ I ] ) ) = t9 . _1 : ^: t9 . _ 2 :^: t9 . _ 3 :^: t9 . _ 4 :^: t9 . _ 5 :^: t9 . _ 6 :^: t9 . _ 7 :^: t9 . _ 8 :^: t9 . _ 9 :^: KNil
2011-01-19 00:24:11 +01:00
}
2011-01-26 04:20:05 +01:00
object InputKey
{
2011-04-21 02:18:58 +02:00
def apply [ T ] ( label : String , description : String = "" ) : InputKey [ T ] =
apply ( AttributeKey [ InputTask [ T ] ] ( label , description ) )
2011-01-26 04:20:05 +01:00
def apply [ T ] ( akey : AttributeKey [ InputTask [ T ] ] ) : InputKey [ T ] =
new InputKey [ T ] ( akey )
}
2011-01-19 00:24:11 +01:00
object TaskKey
{
2011-04-21 02:18:58 +02:00
def apply [ T ] ( label : String , description : String = "" ) : TaskKey [ T ] =
apply ( AttributeKey [ Task [ T ] ] ( label , description ) )
2011-01-19 00:24:11 +01:00
2011-02-12 02:22:17 +01:00
def apply [ T ] ( akey : AttributeKey [ Task [ T ] ] ) : TaskKey [ T ] =
new TaskKey [ T ] ( akey )
2011-01-19 00:24:11 +01:00
}
object SettingKey
{
2011-04-21 02:18:58 +02:00
def apply [ T ] ( label : String , description : String = "" ) : SettingKey [ T ] =
apply ( AttributeKey [ T ] ( label , description ) )
2011-01-19 00:24:11 +01:00
2011-02-12 02:22:17 +01:00
def apply [ T ] ( akey : AttributeKey [ T ] ) : SettingKey [ T ] =
new SettingKey [ T ] ( akey )
2011-01-19 00:24:11 +01:00
}