2011-01-19 00:24:11 +01:00
/* sbt -- Simple Build Tool
* Copyright 2011 Mark Harrah
*/
2010-09-08 20:29:00 +02:00
package sbt
2010-12-29 22:07:17 +01:00
import Types._
2010-12-13 03:33:32 +01:00
sealed trait Settings [ Scope ]
{
2011-01-19 00:24:11 +01:00
def data : Map [ Scope , AttributeMap ]
def keys ( scope : Scope ) : Set [ AttributeKey [ _ ] ]
def scopes : Set [ Scope ]
2011-02-06 17:33:56 +01:00
def definingScope ( scope : Scope , key : AttributeKey [ _ ] ) : Option [ Scope ]
2011-01-26 04:19:03 +01:00
def allKeys [ T ] ( f : ( Scope , AttributeKey [ _ ] ) => T ) : Seq [ T ]
2010-12-13 03:33:32 +01:00
def get [ T ] ( scope : Scope , key : AttributeKey [ T ] ) : Option [ T ]
def set [ T ] ( scope : Scope , key : AttributeKey [ T ] , value : T ) : Settings [ Scope ]
}
2010-12-29 22:07:17 +01:00
private final class Settings0 [ Scope ] ( val data : Map [ Scope , AttributeMap ] , val delegates : Scope => Seq [ Scope ] ) extends Settings [ Scope ]
2010-09-08 20:29:00 +02:00
{
2011-01-19 00:24:11 +01:00
def scopes : Set [ Scope ] = data . keySet . toSet
def keys ( scope : Scope ) = data ( scope ) . keys . toSet
2011-01-26 04:19:03 +01:00
def allKeys [ T ] ( f : ( Scope , AttributeKey [ _ ] ) => T ) : Seq [ T ] = data . flatMap { case ( scope , map ) => map . keys . map ( k => f ( scope , k ) ) } toSeq ;
2010-12-29 22:07:17 +01:00
2010-12-13 03:33:32 +01:00
def get [ T ] ( scope : Scope , key : AttributeKey [ T ] ) : Option [ T ] =
2010-12-29 22:07:17 +01:00
delegates ( scope ) . toStream . flatMap ( sc => scopeLocal ( sc , key ) ) . headOption
2011-02-06 17:33:56 +01:00
def definingScope ( scope : Scope , key : AttributeKey [ _ ] ) : Option [ Scope ] =
delegates ( scope ) . toStream . filter ( sc => scopeLocal ( sc , key ) . isDefined ) . headOption
2010-12-13 03:33:32 +01:00
private def scopeLocal [ T ] ( scope : Scope , key : AttributeKey [ T ] ) : Option [ T ] =
( data get scope ) . flatMap ( _ get key )
def set [ T ] ( scope : Scope , key : AttributeKey [ T ] , value : T ) : Settings [ Scope ] =
{
val map = ( data get scope ) getOrElse AttributeMap . empty
val newData = data . updated ( scope , map . put ( key , value ) )
2010-12-29 22:07:17 +01:00
new Settings0 ( newData , delegates )
2010-12-13 03:33:32 +01:00
}
2010-09-08 20:29:00 +02:00
}
2010-12-29 22:07:17 +01:00
// delegates should contain the input Scope as the first entry
2011-01-19 00:24:11 +01:00
// this trait is intended to be mixed into an object
trait Init [ Scope ]
2010-09-08 20:29:00 +02:00
{
2010-12-29 22:07:17 +01:00
final case class ScopedKey [ T ] ( scope : Scope , key : AttributeKey [ T ] )
2010-09-08 20:29:00 +02:00
2010-12-29 22:07:17 +01:00
type SettingSeq [ T ] = Seq [ Setting [ T ] ]
type ScopedMap = IMap [ ScopedKey , SettingSeq ]
type CompiledMap = Map [ ScopedKey [ _ ] , Compiled ]
type MapScoped = ScopedKey ~> ScopedKey
2011-02-12 02:22:17 +01:00
type ScopeLocal = ScopedKey [ _ ] => Seq [ Setting [ _ ] ]
2010-12-13 03:33:32 +01:00
2011-02-12 02:22:17 +01:00
def setting [ T ] ( key : ScopedKey [ T ] , init : Initialize [ T ] ) : Setting [ T ] = new Setting [ T ] ( key , init )
def value [ T ] ( value : => T ) : Initialize [ T ] = new Value ( value _ )
def update [ T ] ( key : ScopedKey [ T ] ) ( f : T => T ) : Setting [ T ] = new Setting [ T ] ( key , app ( key : ^: KNil ) ( hl => f ( hl . head ) ) )
def app [ HL <: HList , T ] ( inputs : KList [ ScopedKey , HL ] ) ( f : HL => T ) : Initialize [ T ] = new Apply ( f , inputs )
def uniform [ S ,T ] ( inputs : Seq [ ScopedKey [ S ] ] ) ( f : Seq [ S ] => T ) : Initialize [ T ] = new Uniform ( f , inputs )
def kapp [ HL <: HList , M [ _ ] , T ] ( inputs : KList [ ( { type l [ t ] = ScopedKey [ M [ t ] ] } ) # l , HL ] ) ( f : KList [ M , HL ] => T ) : Initialize [ T ] = new KApply [ HL , M , T ] ( f , inputs )
2010-12-13 03:33:32 +01:00
2011-01-19 00:24:11 +01:00
// the following is a temporary workaround for the "... cannot be instantiated from ..." bug, which renders 'kapp' above unusable outside this source file
class KApp [ HL <: HList , M [ _ ] , T ] {
type Composed [ S ] = ScopedKey [ M [ S ] ]
2011-02-12 02:22:17 +01:00
def apply ( inputs : KList [ Composed , HL ] ) ( f : KList [ M , HL ] => T ) : Initialize [ T ] = new KApply [ HL , M , T ] ( f , inputs )
2011-01-19 00:24:11 +01:00
}
def empty ( implicit delegates : Scope => Seq [ Scope ] ) : Settings [ Scope ] = new Settings0 ( Map . empty , delegates )
2010-12-29 22:07:17 +01:00
def asTransform ( s : Settings [ Scope ] ) : ScopedKey ~> Id = new ( ScopedKey ~> Id ) {
2011-01-19 00:24:11 +01:00
def apply [ T ] ( k : ScopedKey [ T ] ) : T = getValue ( s , k )
2010-12-13 03:33:32 +01:00
}
2011-01-19 00:24:11 +01:00
def getValue [ T ] ( s : Settings [ Scope ] , k : ScopedKey [ T ] ) = s . get ( k . scope , k . key ) . get
def asFunction [ T ] ( s : Settings [ Scope ] ) : ScopedKey [ T ] => T = k => getValue ( s , k )
2010-12-13 03:33:32 +01:00
2011-02-12 02:22:17 +01:00
def compiled ( init : Seq [ Setting [ _ ] ] ) ( implicit delegates : Scope => Seq [ Scope ] , scopeLocal : ScopeLocal ) : CompiledMap =
2010-12-13 03:33:32 +01:00
{
2011-02-06 17:33:56 +01:00
// prepend per-scope settings
2011-02-06 03:39:34 +01:00
val withLocal = addLocal ( init ) ( scopeLocal )
2010-12-29 22:07:17 +01:00
// group by Scope/Key, dropping dead initializations
2011-02-06 03:39:34 +01:00
val sMap : ScopedMap = grouped ( withLocal )
2010-12-29 22:07:17 +01:00
// delegate references to undefined values according to 'delegates'
2011-01-19 00:24:11 +01:00
val dMap : ScopedMap = delegate ( sMap ) ( delegates )
2010-12-29 22:07:17 +01:00
// merge Seq[Setting[_]] into Compiled
2011-02-06 17:33:56 +01:00
compile ( dMap )
}
2011-02-12 02:22:17 +01:00
def make ( init : Seq [ Setting [ _ ] ] ) ( implicit delegates : Scope => Seq [ Scope ] , scopeLocal : ScopeLocal ) : Settings [ Scope ] =
2011-02-06 17:33:56 +01:00
{
val cMap = compiled ( init ) ( delegates , scopeLocal )
2010-12-29 22:07:17 +01:00
// order the initializations. cyclic references are detected here.
val ordered : Seq [ Compiled ] = sort ( cMap )
// evaluation: apply the initializations.
applyInits ( ordered )
2010-12-13 03:33:32 +01:00
}
2010-12-29 22:07:17 +01:00
def sort ( cMap : CompiledMap ) : Seq [ Compiled ] =
Dag . topologicalSort ( cMap . values ) ( _ . dependencies . map ( cMap ) )
def compile ( sMap : ScopedMap ) : CompiledMap =
sMap . toSeq . map { case ( k , ss ) =>
2011-02-16 00:43:44 +01:00
val deps = ss flatMap { _ . dependsOn } toSet ;
2010-12-29 22:07:17 +01:00
val eval = ( settings : Settings [ Scope ] ) => ( settings /: ss ) ( applySetting )
2011-02-16 00:43:44 +01:00
( k , new Compiled ( k , deps , eval ) )
2010-12-13 03:33:32 +01:00
} toMap ;
2010-12-29 22:07:17 +01:00
def grouped ( init : Seq [ Setting [ _ ] ] ) : ScopedMap =
( ( IMap . empty : ScopedMap ) /: init ) ( ( m , s ) => add ( m , s ) )
def add [ T ] ( m : ScopedMap , s : Setting [ T ] ) : ScopedMap =
m . mapValue [ T ] ( s . key , Nil , ss => append ( ss , s ) )
def append [ T ] ( ss : Seq [ Setting [ T ] ] , s : Setting [ T ] ) : Seq [ Setting [ T ] ] =
if ( s . definitive ) s : : Nil else ss :+ s
2011-02-06 03:39:34 +01:00
2011-02-12 02:22:17 +01:00
def addLocal ( init : Seq [ Setting [ _ ] ] ) ( implicit scopeLocal : ScopeLocal ) : Seq [ Setting [ _ ] ] =
2011-02-06 03:39:34 +01:00
init . flatMap ( _ . dependsOn flatMap scopeLocal ) ++ init
2010-12-29 22:07:17 +01:00
2011-01-19 00:24:11 +01:00
def delegate ( sMap : ScopedMap ) ( implicit delegates : Scope => Seq [ Scope ] ) : ScopedMap =
2010-12-13 03:33:32 +01:00
{
2011-02-16 00:43:44 +01:00
def refMap ( refKey : ScopedKey [ _ ] , isFirst : Boolean ) = new ( ScopedKey ~> ScopedKey ) { def apply [ T ] ( k : ScopedKey [ T ] ) =
delegateForKey ( sMap , k , delegates ( k . scope ) , refKey , isFirst )
2011-01-26 04:14:02 +01:00
}
val f = new ( SettingSeq ~> SettingSeq ) { def apply [ T ] ( ks : Seq [ Setting [ T ] ] ) =
2011-02-16 00:43:44 +01:00
ks . zipWithIndex . map { case ( s , i ) => s mapReferenced refMap ( s . key , i == 0 ) }
2011-01-26 04:14:02 +01:00
}
2010-12-29 22:07:17 +01:00
sMap mapValues f
2010-12-13 03:33:32 +01:00
}
2011-02-16 00:43:44 +01:00
private [ this ] def delegateForKey [ T ] ( sMap : ScopedMap , k : ScopedKey [ T ] , scopes : Seq [ Scope ] , refKey : ScopedKey [ _ ] , isFirst : Boolean ) : ScopedKey [ T ] =
2010-12-29 22:07:17 +01:00
{
val scache = PMap . empty [ ScopedKey , ScopedKey ]
def resolve ( search : Seq [ Scope ] ) : ScopedKey [ T ] =
search match {
2011-02-01 00:16:25 +01:00
case Seq ( ) => throw Uninitialized ( k , refKey )
2010-12-29 22:07:17 +01:00
case Seq ( x , xs @ _ * ) =>
val sk = ScopedKey ( x , k . key )
2011-02-16 00:43:44 +01:00
scache . getOrUpdate ( sk , if ( defines ( sMap , sk , refKey , isFirst ) ) sk else resolve ( xs ) )
2010-12-29 22:07:17 +01:00
}
resolve ( scopes )
2010-12-13 03:33:32 +01:00
}
2011-02-16 00:43:44 +01:00
private [ this ] def defines ( map : ScopedMap , key : ScopedKey [ _ ] , refKey : ScopedKey [ _ ] , isFirst : Boolean ) : Boolean =
( map get key ) match { case Some ( Seq ( x , _ * ) ) => ( refKey != key ) || ! isFirst ; case _ => false }
2010-12-29 22:07:17 +01:00
2011-01-19 00:24:11 +01:00
private [ this ] def applyInits ( ordered : Seq [ Compiled ] ) ( implicit delegates : Scope => Seq [ Scope ] ) : Settings [ Scope ] =
2010-12-29 22:07:17 +01:00
( empty /: ordered ) { ( m , comp ) => comp . eval ( m ) }
2010-12-13 03:33:32 +01:00
2011-01-19 00:24:11 +01:00
private [ this ] def applySetting [ T ] ( map : Settings [ Scope ] , setting : Setting [ T ] ) : Settings [ Scope ] =
{
2011-02-12 02:22:17 +01:00
val value = setting . init . get ( map )
val key = setting . key
map . set ( key . scope , key . key , value )
2011-01-19 00:24:11 +01:00
}
2010-12-13 03:33:32 +01:00
2011-02-01 00:16:25 +01:00
final class Uninitialized ( val key : ScopedKey [ _ ] , val refKey : ScopedKey [ _ ] , msg : String ) extends Exception ( msg )
def Uninitialized ( key : ScopedKey [ _ ] , refKey : ScopedKey [ _ ] ) : Uninitialized =
new Uninitialized ( key , refKey , "Reference to uninitialized setting " + key . key . label + " (in " + key . scope + ") from " + refKey . key . label + " (in " + refKey . scope + ")" )
2011-02-16 00:43:44 +01:00
final class Compiled ( val key : ScopedKey [ _ ] , val dependencies : Iterable [ ScopedKey [ _ ] ] , val eval : Settings [ Scope ] => Settings [ Scope ] )
2010-12-29 22:07:17 +01:00
2011-02-12 02:22:17 +01:00
sealed trait Initialize [ T ]
2010-12-13 03:33:32 +01:00
{
2010-12-29 22:07:17 +01:00
def dependsOn : Seq [ ScopedKey [ _ ] ]
2011-02-12 02:22:17 +01:00
def map [ S ] ( g : T => S ) : Initialize [ S ]
def mapReferenced ( g : MapScoped ) : Initialize [ T ]
def zip [ S ] ( o : Initialize [ S ] ) : Initialize [ ( T ,S ) ] = zipWith ( o ) ( ( x , y ) => ( x , y ) )
def zipWith [ S ,U ] ( o : Initialize [ S ] ) ( f : ( T , S ) => U ) : Initialize [ U ] = new Joined [ T ,S ,U ] ( this , o , f )
def get ( map : Settings [ Scope ] ) : T
}
final class Setting [ T ] ( val key : ScopedKey [ T ] , val init : Initialize [ T ] )
{
def definitive : Boolean = ! init . dependsOn . contains ( key )
def dependsOn : Seq [ ScopedKey [ _ ] ] = remove ( init . dependsOn , key )
def mapReferenced ( g : MapScoped ) : Setting [ T ] = new Setting ( key , init mapReferenced g )
def mapKey ( g : MapScoped ) : Setting [ T ] = new Setting ( g ( key ) , init )
2011-02-16 00:43:44 +01:00
override def toString = "setting(" + key + ")"
2011-02-12 02:22:17 +01:00
}
private [ this ] final class Joined [ S ,T ,U ] ( a : Initialize [ S ] , b : Initialize [ T ] , f : ( S , T ) => U ) extends Initialize [ U ]
{
def dependsOn = a . dependsOn ++ b . dependsOn
def mapReferenced ( g : MapScoped ) = new Joined ( a mapReferenced g , b mapReferenced g , f )
def map [ Z ] ( g : U => Z ) = new Joined [ S ,T ,Z ] ( a , b , ( s , t ) => g ( f ( s , t ) ) )
def get ( map : Settings [ Scope ] ) : U = f ( a get map , b get map )
2010-12-13 03:33:32 +01:00
}
2011-02-12 02:22:17 +01:00
private [ this ] final class Value [ T ] ( value : ( ) => T ) extends Initialize [ T ]
2010-12-13 03:33:32 +01:00
{
2010-12-29 22:07:17 +01:00
def dependsOn = Nil
2011-01-19 00:24:11 +01:00
def mapReferenced ( g : MapScoped ) = this
2011-02-12 02:22:17 +01:00
def map [ S ] ( g : T => S ) = new Value [ S ] ( ( ) => g ( value ( ) ) )
def get ( map : Settings [ Scope ] ) : T = value ( )
2010-09-08 20:29:00 +02:00
}
2011-02-12 02:22:17 +01:00
private [ this ] final class Apply [ HL <: HList , T ] ( val f : HL => T , val inputs : KList [ ScopedKey , HL ] ) extends Initialize [ T ]
2010-12-13 03:33:32 +01:00
{
2011-02-12 02:22:17 +01:00
def dependsOn = inputs . toList
def mapReferenced ( g : MapScoped ) = new Apply ( f , inputs transform g )
def map [ S ] ( g : T => S ) = new Apply ( g compose f , inputs )
def get ( map : Settings [ Scope ] ) = f ( inputs down asTransform ( map ) )
2011-01-19 00:24:11 +01:00
}
2011-02-12 02:22:17 +01:00
private [ this ] final class KApply [ HL <: HList , M [ _ ] , T ] ( val f : KList [ M , HL ] => T , val inputs : KList [ ( { type l [ t ] = ScopedKey [ M [ t ] ] } ) # l , HL ] ) extends Initialize [ T ]
2011-01-19 00:24:11 +01:00
{
2011-02-12 02:22:17 +01:00
def dependsOn = unnest ( inputs . toList )
def mapReferenced ( g : MapScoped ) = new KApply [ HL , M , T ] ( f , inputs . transform [ ( { type l [ t ] = ScopedKey [ M [ t ] ] } ) # l ] ( nestCon ( g ) ) )
def map [ S ] ( g : T => S ) = new KApply [ HL , M , S ] ( g compose f , inputs )
def get ( map : Settings [ Scope ] ) = f ( inputs . transform [ M ] ( nestCon [ ScopedKey , Id , M ] ( asTransform ( map ) ) ) )
2011-01-19 00:24:11 +01:00
private [ this ] def unnest ( l : List [ ScopedKey [ M [ T ] ] forSome { type T } ] ) : List [ ScopedKey [ _ ] ] = l . asInstanceOf [ List [ ScopedKey [ _ ] ] ]
}
2011-02-12 02:22:17 +01:00
private [ this ] final class Uniform [ S , T ] ( val f : Seq [ S ] => T , val inputs : Seq [ ScopedKey [ S ] ] ) extends Initialize [ T ]
2011-01-19 00:24:11 +01:00
{
2011-02-12 02:22:17 +01:00
def dependsOn = inputs
def mapReferenced ( g : MapScoped ) = new Uniform ( f , inputs map g . fn [ S ] )
def map [ S ] ( g : T => S ) = new Uniform ( g compose f , inputs )
def get ( map : Settings [ Scope ] ) = f ( inputs map asFunction ( map ) )
2010-12-13 03:33:32 +01:00
}
2011-01-19 00:24:11 +01:00
private def remove [ T ] ( s : Seq [ T ] , v : T ) = s filterNot ( _ == v )
2010-12-13 03:33:32 +01:00
}