[Haskell-cafe] Thinking about an unlistN

2008-08-10 Thread Michael Feathers


I wrote this function the other day, and I was wondering if I'm missing 
something.. whether there is already a function or idiom around to do this.



unlist3 :: (a - a - a - b) - [a] - b
unlist3 f (x:y:z:xs) = f x y z


I was also wondering whether the function can be generalized to N or 
whether this is just one of those edges in the type system that you 
can't abstract over.



Thanks,

Michael



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Thinking about an unlistN

2008-08-10 Thread Michael Feathers



Philip,

Thanks.  It's not quite that, though.  It's more like an adapter for a 
function with a specific arity.


If I have, say, a function f :: a - a - a - a - b it would be nice 
to be able to just:


unlistN 4 f [1..4]


Michael (does look like there's no way to make that fly with the type 
system however)




Philip Neustrom wrote:

I'm no expert, but it looks like the generalization of that would be
some f that took a list:

f :: [a] - b

so what you'd have is a fold, right?

foldr1 :: (a - a - a) - [a] - a

Best,
Philip Neustrom

On Sun, Aug 10, 2008 at 11:47 AM, Michael Feathers
[EMAIL PROTECTED] wrote:

I wrote this function the other day, and I was wondering if I'm missing
something.. whether there is already a function or idiom around to do this.


unlist3 :: (a - a - a - b) - [a] - b
unlist3 f (x:y:z:xs) = f x y z


I was also wondering whether the function can be generalized to N or whether
this is just one of those edges in the type system that you can't abstract
over.


Thanks,

Michael



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe






--
Now Playing: Clammbon - 246
http://youtube.com/watch?v=PO77bN8W1mA


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is there anything manifestly stupid about this code?

2008-07-07 Thread Michael Feathers


Thanks.  Here's a newb question: what does strictness really get me in 
this code?


BTW, I only noticed the Complex type late.  I looked at it and noticed 
that all I'd be using is the constructor and add.  Didn't seem worth the 
 change.


Michael

Derek Elkins wrote:

To answer the question in your subject, yes!  We have a complex type.
Not only does that make the code simpler and more obvious and idiomatic,
but it's also more efficient because for this use you'd really prefer a
strict pair type for Point, and complex is strict in it's components.

On Sun, 2008-07-06 at 21:02 -0400, Michael Feathers wrote:
Decided a while ago to write some code to calculate the Mandelbrot set 
using the escape iterations algorithm.  Discovered after mulling it 
about that I could just built it as an infinite list of infinite lists 
and then extract any rectangle of values that I wanted:


type Point = (Double, Double)



sq :: Double - Double
sq x = x ^ 2

translate :: Point - Point - Point
translate (r0, i0) (r1, i1) =
   (r0 + r1, i0 + i1)

mandel :: Point - Point
mandel (r, i) =
   (sq r + sq i, 2 * r * i)

notEscaped :: Point - Bool
notEscaped (r, i) =
   (sq r + sq i) = 4.0

trajectory :: (Point - Point) - [Point]
trajectory pointFunction =
   takeWhile notEscaped $ iterate pointFunction seed
 where seed = (0.0, 0.0)

escapeIterations :: (Point - Point) - Int
escapeIterations =
   length . tail . take 1024 . trajectory

mandelbrot :: Double - [[Int]]
mandelbrot incrementSize =
   [[ escapeIterations $ translate (x, y) . mandel
 | x - increments]
 | y - increments] where
 increments = [0.0, incrementSize .. ]

window :: (Int, Int) - (Int, Int) - [[a]] - [[a]]
window (x0, y0) (x1, y1) = range x0 x1 . map (range y0 y1) where
   range m n = take (n - m) . drop m


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe






--
Now Playing: Clammbon - 246
http://youtube.com/watch?v=PO77bN8W1mA


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Having trouble with zip12..

2008-07-06 Thread Michael Feathers



I have some code that looks like this and I'm having trouble with it:


zip12 ((tails . nub) flightPaths) wayPoints etopsPackets (hd geoCaches)
  groundSpeeds headings (map windShift headings) (regulations !! 2)
  (foldr (\|/) (tail pathDistances)) [ghy x | x - [1..], full x]
  (nub . nub) arrivalSchedule


The domain is air traffic control and I need to generate 12-tuples for 
aircraft that are within a particular radius of the tower.


When I evaluate that expression with 'take 4' it works fine.  When I 
evaluate it with 'take 6' it works as well.  But, when I evaluate it 
with 'take 5' I get the following runtime error from H# in Visual Studio 
(it runs fine on the command line).  This is particularly odd because 
I'm not using Sql.




The type initializer for 'System.Data.SqlClient.SqlConnection' threw an 
exception.
Exception (TypeInitializationException): Source=System.Data; 
Target=null; Tag=null; TypeName=System.Data.SqlClient.SqlConnection;
Message = The type initializer for 
'System.Data.SqlClient.SqlConnection' threw an exception.
InnerException (TypeInitializationException): Source=System.Data; 
Target=null; Tag=null;
Message = The type initializer for 
'System.Data.SqlClient.SqlConnectionFactory' threw an exception.

StackTrace =  at System.Data.SqlClient.SqlConnection..cctor()
InnerException (TypeInitializationException): Source=System.Data; 
Target=null; Tag=null;
Message = The type initializer for 
'System.Data.SqlClient.SqlPerformanceCounters' threw an exception.

StackTrace =
 at System.Data.SqlClient.SqlConnectionFactory..ctor()
at System.Data.SqlClient.SqlConnectionFactory..cctor()
InnerException (ConfigurationErrorsException): 
Source=System.Configuration; Target=null; Tag=null; Line=21;

Message =
The value of the property 'traceOutputOptions' cannot be parsed. The 
error is: The enumeration value must be one of the following: None, 
LogicalOperationStack, DateTime, Timestamp, ProcessId, ThreadId, 
Callstack. (C:\Documents and
Settings\Paey\Desktop\Projects\RPMC\bin\Debug\RPMC.vshost.exe.config 
line 21)

StackTrace =
 at System.Configuration.BaseConfigurationRecord.EvaluateOne(String[] 
keys, SectionInput input, Boolean isTrusted, FactoryRecord 
factoryRecord, SectionRecord sectionRecord, Object parentResult)
at System.Configuration.BaseConfigurationRecord.Evaluate(FactoryRecord 
factoryRecord, SectionRecord sectionRecord, Object parentResult, Boolean 
getLkg, Boolean getRuntimeObject, Object result, Object 
resultRuntimeObject)
at 
System.Configuration.BaseConfigurationRecord.GetSectionRecursive(String 
configKey, Boolean getLkg, Boolean checkPermission, Boolean 
getRuntimeObject, Boolean requestIsHere, Object result, Object 
resultRuntimeObject)
at 
System.Configuration.BaseConfigurationRecord.GetSectionRecursive(String 
configKey, Boolean getLkg, Boolean checkPermission, Boolean 
getRuntimeObject, Boolean requestIsHere, Object result, Object 
resultRuntimeObject)
at 
System.Configuration.BaseConfigurationRecord.GetSectionRecursive(String 
configKey, Boolean getLkg, Boolean ch... (truncated) ...olean 
checkPermission)

at System.Configuration.BaseConfigurationRecord.GetSection(String configKey)
at 
System.Configuration.ClientConfigurationSystem.System.Configuration.Internal.IInternalConfigSystem.GetSection(String 
sectionName)

at System.Configuration.ConfigurationManager.GetSection(String sectionName)
at System.Configuration.PrivilegedConfigurationManager.GetSection(String 
sectionName)

at System.Diagnostics.DiagnosticsConfiguration.GetConfigSection()
at System.Diagnostics.DiagnosticsConfiguration.Initialize()
at System.Diagnostics.Switch.InitializeConfigSettings()
at System.Diagnostics.Switch.InitializeWithStatus()
at System.Diagnostics.Switch.get_SwitchSetting()
at System.Diagnostics.TraceSwitch.get_Level()
at System.Data.ProviderBase.DbConnectionPoolCounters..ctor(String 
categoryName, String categoryHelp)

at System.Data.SqlClient.SqlPerformanceCounters..ctor()
at System.Data.SqlClient.SqlPerformanceCounters..cctor()
BareMessage = The value of the property 'traceOutputOptions' cannot be 
parsed. The error is: The enumeration value must be one of the 
following: None, LogicalOperationStack, DateTime, Timestamp, ProcessId, 
ThreadId, Callstack.
Filename = C:\Documents and 
Settings\Pley\Desktop\Projects\RPMC\bin\Debug\RPMC.vshost.exe.config

Errors (ConfigurationException[]): Length=1; Rank=1; Count=1;
#0 (ConfigurationErrorsException): Source=null; Target=null; Tag=null; 
StackTrace=null; BareMessage=(-BareMessage); Filename=(-Filename); 
Line=21;

Message =
The value of the property 'traceOutputOptions' cannot be parsed. The 
error is: The enumeration value must be one of the following: None, 
LogicalOperationStack, DateTime, Timestamp, ProcessId, ThreadId, 
Callstack. (C:\Documents and
Settings\Pley\Desktop\Projects\RPMC\bin\Debug\RPMC.vshost.exe.config 
line 21)

Errors (ConfigurationException[]): Length=1; Rank=1; Count=1;
#0 (ConfigurationErrorsException): 

Re: [Haskell-cafe] Having trouble with zip12..

2008-07-06 Thread Michael Feathers


Sorry guys.  I was just bored on a Sunday afternoon so I thought I'd 
type up a little joke.  I thought to myself Gee, how outrageous can I 
make it?


1) Using and debugging a zip12 function.
2) That fails only on 'take 5' (Brubeck fans take note)
3) Has some absurd arguments like (nub . nub)
4) Is embedded in an air traffic control system
5) Is written in a Microsoft variant of Haskell called H#
6) Silently makes SQL calls when evaluating a pure function
7) Yields an mile long stack trace

Sorry all.  Boredom made me do it,

Michael

Paul Visschers wrote:

You're zipping 12 lists here, so how about testing each list
individually? This will narrow down the problem considerably.

Michael Feathers wrote:


I have some code that looks like this and I'm having trouble with it:


zip12 ((tails . nub) flightPaths) wayPoints etopsPackets (hd geoCaches)
  groundSpeeds headings (map windShift headings) (regulations !! 2)
  (foldr (\|/) (tail pathDistances)) [ghy x | x - [1..], full x]
  (nub . nub) arrivalSchedule


The domain is air traffic control and I need to generate 12-tuples for
aircraft that are within a particular radius of the tower.

When I evaluate that expression with 'take 4' it works fine.  When I
evaluate it with 'take 6' it works as well.  But, when I evaluate it
with 'take 5' I get the following runtime error from H# in Visual Studio
(it runs fine on the command line).  This is particularly odd because
I'm not using Sql.



The type initializer for 'System.Data.SqlClient.SqlConnection' threw an
exception.
Exception (TypeInitializationException): Source=System.Data;
Target=null; Tag=null; TypeName=System.Data.SqlClient.SqlConnection;
Message = The type initializer for
'System.Data.SqlClient.SqlConnection' threw an exception.
InnerException (TypeInitializationException): Source=System.Data;
Target=null; Tag=null;
Message = The type initializer for
'System.Data.SqlClient.SqlConnectionFactory' threw an exception.
StackTrace =  at System.Data.SqlClient.SqlConnection..cctor()
InnerException (TypeInitializationException): Source=System.Data;
Target=null; Tag=null;
Message = The type initializer for
'System.Data.SqlClient.SqlPerformanceCounters' threw an exception.
StackTrace =
 at System.Data.SqlClient.SqlConnectionFactory..ctor()
at System.Data.SqlClient.SqlConnectionFactory..cctor()
InnerException (ConfigurationErrorsException):
Source=System.Configuration; Target=null; Tag=null; Line=21;
Message =
The value of the property 'traceOutputOptions' cannot be parsed. The
error is: The enumeration value must be one of the following: None,
LogicalOperationStack, DateTime, Timestamp, ProcessId, ThreadId,
Callstack. (C:\Documents and
Settings\Paey\Desktop\Projects\RPMC\bin\Debug\RPMC.vshost.exe.config
line 21)
StackTrace =
 at System.Configuration.BaseConfigurationRecord.EvaluateOne(String[]
keys, SectionInput input, Boolean isTrusted, FactoryRecord
factoryRecord, SectionRecord sectionRecord, Object parentResult)
at System.Configuration.BaseConfigurationRecord.Evaluate(FactoryRecord
factoryRecord, SectionRecord sectionRecord, Object parentResult, Boolean
getLkg, Boolean getRuntimeObject, Object result, Object
resultRuntimeObject)
at
System.Configuration.BaseConfigurationRecord.GetSectionRecursive(String
configKey, Boolean getLkg, Boolean checkPermission, Boolean
getRuntimeObject, Boolean requestIsHere, Object result, Object
resultRuntimeObject)
at
System.Configuration.BaseConfigurationRecord.GetSectionRecursive(String
configKey, Boolean getLkg, Boolean checkPermission, Boolean
getRuntimeObject, Boolean requestIsHere, Object result, Object
resultRuntimeObject)
at
System.Configuration.BaseConfigurationRecord.GetSectionRecursive(String
configKey, Boolean getLkg, Boolean ch... (truncated) ...olean
checkPermission)
at System.Configuration.BaseConfigurationRecord.GetSection(String
configKey)
at
System.Configuration.ClientConfigurationSystem.System.Configuration.Internal.IInternalConfigSystem.GetSection(String
sectionName)
at System.Configuration.ConfigurationManager.GetSection(String sectionName)
at System.Configuration.PrivilegedConfigurationManager.GetSection(String
sectionName)
at System.Diagnostics.DiagnosticsConfiguration.GetConfigSection()
at System.Diagnostics.DiagnosticsConfiguration.Initialize()
at System.Diagnostics.Switch.InitializeConfigSettings()
at System.Diagnostics.Switch.InitializeWithStatus()
at System.Diagnostics.Switch.get_SwitchSetting()
at System.Diagnostics.TraceSwitch.get_Level()
at System.Data.ProviderBase.DbConnectionPoolCounters..ctor(String
categoryName, String categoryHelp)
at System.Data.SqlClient.SqlPerformanceCounters..ctor()
at System.Data.SqlClient.SqlPerformanceCounters..cctor()
BareMessage = The value of the property 'traceOutputOptions' cannot be
parsed. The error is: The enumeration value must be one of the
following: None, LogicalOperationStack, DateTime, Timestamp, ProcessId,
ThreadId, Callstack.
Filename = C:\Documents and
Settings\Pley\Desktop\Projects\RPMC\bin\Debug

Re: [Haskell-cafe] Having trouble with zip12..

2008-07-06 Thread Michael Feathers

Don Stewart wrote:

I win, almost ...

13:13:18 dons dolio: yeah, it was ... almost ... an April 1 style post 


:)

And yes, this was truly shocking on a number of levels. However, we have
people doing a lot of weird things with Haskell these days, so its not
as absurd that someone would be hacking up a zip12 for an air traffic
control system on some MS platform, with SQL in the backend, as it might
have been a few years ago :)


:-)

Was that IRC?  Oh boy, now I have a reputation.

Michael



mfeathers:
Sorry guys.  I was just bored on a Sunday afternoon so I thought I'd 
type up a little joke.  I thought to myself Gee, how outrageous can I 
make it?


1) Using and debugging a zip12 function.
2) That fails only on 'take 5' (Brubeck fans take note)
3) Has some absurd arguments like (nub . nub)
4) Is embedded in an air traffic control system
5) Is written in a Microsoft variant of Haskell called H#
6) Silently makes SQL calls when evaluating a pure function
7) Yields an mile long stack trace

Sorry all.  Boredom made me do it,

Michael

Paul Visschers wrote:

You're zipping 12 lists here, so how about testing each list
individually? This will narrow down the problem considerably.

Michael Feathers wrote:

I have some code that looks like this and I'm having trouble with it:


zip12 ((tails . nub) flightPaths) wayPoints etopsPackets (hd geoCaches)
 groundSpeeds headings (map windShift headings) (regulations !! 2)
 (foldr (\|/) (tail pathDistances)) [ghy x | x - [1..], full x]
 (nub . nub) arrivalSchedule


The domain is air traffic control and I need to generate 12-tuples for
aircraft that are within a particular radius of the tower.

When I evaluate that expression with 'take 4' it works fine.  When I
evaluate it with 'take 6' it works as well.  But, when I evaluate it
with 'take 5' I get the following runtime error from H# in Visual Studio
(it runs fine on the command line).  This is particularly odd because
I'm not using Sql.



The type initializer for 'System.Data.SqlClient.SqlConnection' threw an
exception.
Exception (TypeInitializationException): Source=System.Data;
Target=null; Tag=null; TypeName=System.Data.SqlClient.SqlConnection;
Message = The type initializer for
'System.Data.SqlClient.SqlConnection' threw an exception.
InnerException (TypeInitializationException): Source=System.Data;
Target=null; Tag=null;
Message = The type initializer for
'System.Data.SqlClient.SqlConnectionFactory' threw an exception.
StackTrace =  at System.Data.SqlClient.SqlConnection..cctor()
InnerException (TypeInitializationException): Source=System.Data;
Target=null; Tag=null;
Message = The type initializer for
'System.Data.SqlClient.SqlPerformanceCounters' threw an exception.
StackTrace =
 at System.Data.SqlClient.SqlConnectionFactory..ctor()
at System.Data.SqlClient.SqlConnectionFactory..cctor()
InnerException (ConfigurationErrorsException):
Source=System.Configuration; Target=null; Tag=null; Line=21;
Message =
The value of the property 'traceOutputOptions' cannot be parsed. The
error is: The enumeration value must be one of the following: None,
LogicalOperationStack, DateTime, Timestamp, ProcessId, ThreadId,
Callstack. (C:\Documents and
Settings\Paey\Desktop\Projects\RPMC\bin\Debug\RPMC.vshost.exe.config
line 21)
StackTrace =
 at System.Configuration.BaseConfigurationRecord.EvaluateOne(String[]
keys, SectionInput input, Boolean isTrusted, FactoryRecord
factoryRecord, SectionRecord sectionRecord, Object parentResult)
at System.Configuration.BaseConfigurationRecord.Evaluate(FactoryRecord
factoryRecord, SectionRecord sectionRecord, Object parentResult, Boolean
getLkg, Boolean getRuntimeObject, Object result, Object
resultRuntimeObject)
at
System.Configuration.BaseConfigurationRecord.GetSectionRecursive(String
configKey, Boolean getLkg, Boolean checkPermission, Boolean
getRuntimeObject, Boolean requestIsHere, Object result, Object
resultRuntimeObject)
at
System.Configuration.BaseConfigurationRecord.GetSectionRecursive(String
configKey, Boolean getLkg, Boolean checkPermission, Boolean
getRuntimeObject, Boolean requestIsHere, Object result, Object
resultRuntimeObject)
at
System.Configuration.BaseConfigurationRecord.GetSectionRecursive(String
configKey, Boolean getLkg, Boolean ch... (truncated) ...olean
checkPermission)
at System.Configuration.BaseConfigurationRecord.GetSection(String
configKey)
at
System.Configuration.ClientConfigurationSystem.System.Configuration.Internal.IInternalConfigSystem.GetSection(String
sectionName)
at System.Configuration.ConfigurationManager.GetSection(String 
sectionName)

at System.Configuration.PrivilegedConfigurationManager.GetSection(String
sectionName)
at System.Diagnostics.DiagnosticsConfiguration.GetConfigSection()
at System.Diagnostics.DiagnosticsConfiguration.Initialize()
at System.Diagnostics.Switch.InitializeConfigSettings()
at System.Diagnostics.Switch.InitializeWithStatus()
at System.Diagnostics.Switch.get_SwitchSetting()
at System.Diagnostics.TraceSwitch.get_Level

Re: [Haskell-cafe] Having trouble with zip12..

2008-07-06 Thread Michael Feathers

Andrew Wagner wrote:

Wow. Where did you come up with the stack trace? That's...impressive.


Pulled it from a blog.  I was actually looking for a creepy VB4 or VB5 
stack trace I saw years ago that ripped through their dynamic type 
resolution layer. Now that would've been funny. :-)


Michael



On Sun, Jul 6, 2008 at 5:07 PM, Don Stewart [EMAIL PROTECTED] wrote:

I win, almost ...

   13:13:18 dons dolio: yeah, it was ... almost ... an April 1 style post

:)

And yes, this was truly shocking on a number of levels. However, we have
people doing a lot of weird things with Haskell these days, so its not
as absurd that someone would be hacking up a zip12 for an air traffic
control system on some MS platform, with SQL in the backend, as it might
have been a few years ago :)

mfeathers:

Sorry guys.  I was just bored on a Sunday afternoon so I thought I'd
type up a little joke.  I thought to myself Gee, how outrageous can I
make it?

1) Using and debugging a zip12 function.
2) That fails only on 'take 5' (Brubeck fans take note)
3) Has some absurd arguments like (nub . nub)
4) Is embedded in an air traffic control system
5) Is written in a Microsoft variant of Haskell called H#
6) Silently makes SQL calls when evaluating a pure function
7) Yields an mile long stack trace

Sorry all.  Boredom made me do it,

Michael

Paul Visschers wrote:

You're zipping 12 lists here, so how about testing each list
individually? This will narrow down the problem considerably.

Michael Feathers wrote:

I have some code that looks like this and I'm having trouble with it:


zip12 ((tails . nub) flightPaths) wayPoints etopsPackets (hd geoCaches)
 groundSpeeds headings (map windShift headings) (regulations !! 2)
 (foldr (\|/) (tail pathDistances)) [ghy x | x - [1..], full x]
 (nub . nub) arrivalSchedule


The domain is air traffic control and I need to generate 12-tuples for
aircraft that are within a particular radius of the tower.

When I evaluate that expression with 'take 4' it works fine.  When I
evaluate it with 'take 6' it works as well.  But, when I evaluate it
with 'take 5' I get the following runtime error from H# in Visual Studio
(it runs fine on the command line).  This is particularly odd because
I'm not using Sql.



The type initializer for 'System.Data.SqlClient.SqlConnection' threw an
exception.
Exception (TypeInitializationException): Source=System.Data;
Target=null; Tag=null; TypeName=System.Data.SqlClient.SqlConnection;
Message = The type initializer for
'System.Data.SqlClient.SqlConnection' threw an exception.
InnerException (TypeInitializationException): Source=System.Data;
Target=null; Tag=null;
Message = The type initializer for
'System.Data.SqlClient.SqlConnectionFactory' threw an exception.
StackTrace =  at System.Data.SqlClient.SqlConnection..cctor()
InnerException (TypeInitializationException): Source=System.Data;
Target=null; Tag=null;
Message = The type initializer for
'System.Data.SqlClient.SqlPerformanceCounters' threw an exception.
StackTrace =
 at System.Data.SqlClient.SqlConnectionFactory..ctor()
at System.Data.SqlClient.SqlConnectionFactory..cctor()
InnerException (ConfigurationErrorsException):
Source=System.Configuration; Target=null; Tag=null; Line=21;
Message =
The value of the property 'traceOutputOptions' cannot be parsed. The
error is: The enumeration value must be one of the following: None,
LogicalOperationStack, DateTime, Timestamp, ProcessId, ThreadId,
Callstack. (C:\Documents and
Settings\Paey\Desktop\Projects\RPMC\bin\Debug\RPMC.vshost.exe.config
line 21)
StackTrace =
 at System.Configuration.BaseConfigurationRecord.EvaluateOne(String[]
keys, SectionInput input, Boolean isTrusted, FactoryRecord
factoryRecord, SectionRecord sectionRecord, Object parentResult)
at System.Configuration.BaseConfigurationRecord.Evaluate(FactoryRecord
factoryRecord, SectionRecord sectionRecord, Object parentResult, Boolean
getLkg, Boolean getRuntimeObject, Object result, Object
resultRuntimeObject)
at
System.Configuration.BaseConfigurationRecord.GetSectionRecursive(String
configKey, Boolean getLkg, Boolean checkPermission, Boolean
getRuntimeObject, Boolean requestIsHere, Object result, Object
resultRuntimeObject)
at
System.Configuration.BaseConfigurationRecord.GetSectionRecursive(String
configKey, Boolean getLkg, Boolean checkPermission, Boolean
getRuntimeObject, Boolean requestIsHere, Object result, Object
resultRuntimeObject)
at
System.Configuration.BaseConfigurationRecord.GetSectionRecursive(String
configKey, Boolean getLkg, Boolean ch... (truncated) ...olean
checkPermission)
at System.Configuration.BaseConfigurationRecord.GetSection(String
configKey)
at
System.Configuration.ClientConfigurationSystem.System.Configuration.Internal.IInternalConfigSystem.GetSection(String
sectionName)
at System.Configuration.ConfigurationManager.GetSection(String
sectionName)
at System.Configuration.PrivilegedConfigurationManager.GetSection(String
sectionName

[Haskell-cafe] Is there a nicer way to do this?

2008-07-06 Thread Michael Feathers



segment :: Int - [a] - [[a]]
segment 0 _ = []
segment _ [] = []
segment n x = (take n x) : segment n (drop n x)


I did a version of this which used splitAt but I wasn't sure whether it 
was going to buy me anything re performance that would justify its ugliness.



Michael






___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Is there anything manifestly stupid about this code?

2008-07-06 Thread Michael Feathers


Decided a while ago to write some code to calculate the Mandelbrot set 
using the escape iterations algorithm.  Discovered after mulling it 
about that I could just built it as an infinite list of infinite lists 
and then extract any rectangle of values that I wanted:


type Point = (Double, Double)

sq :: Double - Double
sq x = x ^ 2

translate :: Point - Point - Point
translate (r0, i0) (r1, i1) =
  (r0 + r1, i0 + i1)

mandel :: Point - Point
mandel (r, i) =
  (sq r + sq i, 2 * r * i)

notEscaped :: Point - Bool
notEscaped (r, i) =
  (sq r + sq i) = 4.0

trajectory :: (Point - Point) - [Point]
trajectory pointFunction =
  takeWhile notEscaped $ iterate pointFunction seed
where seed = (0.0, 0.0)

escapeIterations :: (Point - Point) - Int
escapeIterations =
  length . tail . take 1024 . trajectory

mandelbrot :: Double - [[Int]]
mandelbrot incrementSize =
  [[ escapeIterations $ translate (x, y) . mandel
| x - increments]
| y - increments] where
increments = [0.0, incrementSize .. ]

window :: (Int, Int) - (Int, Int) - [[a]] - [[a]]
window (x0, y0) (x1, y1) = range x0 x1 . map (range y0 y1) where
  range m n = take (n - m) . drop m


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] An ugly zip3 problem..

2008-03-22 Thread Michael Feathers


Thanks!  I learned a lot from that.


Michael

Tillmann Rendel wrote:

Michael Feathers wrote:
  I'm working on something and it's looking rather ugly. essentially,
  it's an application of a low pass filer to a dataset.

I would not consider your code ugly. it can be made shorter, though.

  type Dataset = [Double]
  type FilterWindow3 = (Double,Double,Double)
 
  internalList :: [a] - [a]
  internalList = tail . init
 
  lowPass3 :: FilterWindow3 - Double
  lowPass3 (i, j, k) = (i + 2 * j + k) / 4.0
 
  filter3 :: (FilterWindow3 - Double) - Dataset - Dataset
  filter3 f3 ds = [(f3 x) | x - formWindows ds]

I would prefer this version to the list comprehension:

  filter3 f3 = map f3 . formWindows

I tend to assume list comprehensions are doing something magical I have 
to figure out while reading a program, so a comprehension for a simple 
map looks wrong to me. read ahead for more magical list comprehensions.


  iterFilter :: (Dataset - Dataset) - Int - Dataset - Dataset
  iterFilter f n ds
| n  0 = iterFilter f (n - 1) (f ds)
| otherwise = ds

You can use iterate and list indexing to iterate a function a specified 
number of times.


  iterFilter f n = (!! n) . iterate f

Probably

  iterateN :: (a - a) - Int - a

is a better type and name for this function.

  formWindows :: Dataset - [FilterWindow3]
  formWindows ds =
internalList $ zip3 x y z
  where c0 = [head ds]
cn = [last ds]
x  = ds ++ cn ++ cn
y  = c0 ++ ds ++ cn
z  = c0 ++ c0 ++ ds

internalList will delete the first and last element, so why create it at 
all? there is no problem with different list lengths, the result will be 
as long as the shortest list.


  formWindows ds = zip3 x y z where
x = tail ds ++ [last ds]
y = ds
z = head ds : ds

if you want to make clear what elements of the lists are used, you can use

  z = head ds : init ds

instead. Note that definition for y clearly states that the middle 
element is the original list. I would consider swapping x and z to help 
me imagine a window moving over the dataset. as it is now, i have to 
imagine a window with an integrated mirror to make it fit.


I don't like the definition of x, because I fear that the (last ds) 
thunk will hang around and hold the whole list ds in memory, which is 
unecessary because it's value only depends on the last element of said 
list. I would therefore consider a different implementation using tails.


  formWindows ds = [(f y z, y, x) | (x : y : z) - tails (head ds : ds)]
where f x [] = x
  f _ (x : _) = x

the head corner case is taken care of by duplicating the head of ds. the 
last corner case is taken care of by the call to f, which uses y as 
default value if z doesn't contain another one. the list comprehension 
is used here to do three different things:


  * convert lists to tuples
  * apply f
  * throw away the last element of tails' result (pattern match
failure means ignore this element in list comprehensions)

Maybe

  headDefault :: a - [a] - a

is a sensible name for f.

  smooth :: Int - Dataset - Dataset
  smooth = iterFilter $ filter3 lowPass3

by inlining the definition above, this can be given as a four-liner now:

  smooth n = (!! n) . iterate f where
f ds = [(g y z + 2 * y + x) / 4.0 | x:y:z - tails (head ds : ds)]
g x []= x
g _ (x:_) = x

:-)

  Tillmann




--
Now Playing: http://www.youtube.com/watch?v=SsnDdq4V8zg

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] An ugly zip3 problem..

2008-03-22 Thread Michael Feathers



One thing that gets me about this solution.. as I was structuring mine I 
noticed that I was ending up with types like FilterWindow3 and functions 
like lowPass3.  Inlining does eliminate them, but I wonder whether there 
is a good way to structure the computation generically so that it can be 
performed with windows of 5 as well as 3.  The cons pattern matching 
here would get in the way, and in my original solution, the fact that I 
was using tuples got in the way also.


Would Haskell's type system allow you to pass a function of arbitrary 
arity, discern its arity, use that information to construct the 
appropriate structure for iteration, and then apply it?



Michael

Tillmann Rendel wrote:



by inlining the definition above, this can be given as a four-liner now:

  smooth n = (!! n) . iterate f where
f ds = [(g y z + 2 * y + x) / 4.0 | x:y:z - tails (head ds : ds)]
g x []= x
g _ (x:_) = x

:-)

  Tillmann




--
Now Playing: http://www.youtube.com/watch?v=SsnDdq4V8zg

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] An ugly zip3 problem..

2008-03-20 Thread Michael Feathers
I'm working on something and it's looking rather ugly.. essentially, it 
it's an application of a low pass filer to a dataset.



type Dataset = [Double]
type FilterWindow3 = (Double,Double,Double)

internalList :: [a] - [a]
internalList = tail . init

lowPass3 :: FilterWindow3 - Double
lowPass3 (i, j, k) = (i + 2 * j + k) / 4.0

filter3 :: (FilterWindow3 - Double) - Dataset - Dataset
filter3 f3 ds = [(f3 x) | x - formWindows ds]

iterFilter :: (Dataset - Dataset) - Int - Dataset - Dataset
iterFilter f n ds
  | n  0 = iterFilter f (n - 1) (f ds)
  | otherwise = ds

smooth :: Int - Dataset - Dataset
smooth = iterFilter $ filter3 lowPass3

formWindows :: Dataset - [FilterWindow3]
formWindows ds =
  internalList $ zip3 x y z
where c0 = [head ds]
  cn = [last ds]
  x  = ds ++ cn ++ cn
  y  = c0 ++ ds ++ cn
  z  = c0 ++ c0 ++ ds


The key idea is that I can take care of edge conditions with that last 
function.  It lets me build a list of 3-tuples, each of which is reduced 
to a single point in the next rewrite of the dataset.  I used zip3 to 
build up that list, and I take care to keep the lists the same length by 
 duplicating the head and last elements as necessary.  Has anyone done 
this sort of thing before?


Any and all style advice welcome.

Thanks,

Michael Feathers


--
Now Playing: http://www.youtube.com/watch?v=SsnDdq4V8zg

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] An ugly zip3 problem..

2008-03-20 Thread Michael Feathers


Thanks.  That's interesting (but a little beyond me).  Seems like he's 
assuming that values beyond his range are zero whereas I'm trying to use 
the values at the edges of the range.


Is there anything I can do before I understand comonads? ;-)

Michael

Dan Weston wrote:

There's an interesting blog post by Dan Piponi on the subject:

http://sigfpe.blogspot.com/2007/01/monads-hidden-behind-every-zipper.html

Summary: convolution is comonadic

Dan

Michael Feathers wrote:
I'm working on something and it's looking rather ugly.. essentially, 
it it's an application of a low pass filer to a dataset.



type Dataset = [Double]
type FilterWindow3 = (Double,Double,Double)

internalList :: [a] - [a]
internalList = tail . init

lowPass3 :: FilterWindow3 - Double
lowPass3 (i, j, k) = (i + 2 * j + k) / 4.0

filter3 :: (FilterWindow3 - Double) - Dataset - Dataset
filter3 f3 ds = [(f3 x) | x - formWindows ds]

iterFilter :: (Dataset - Dataset) - Int - Dataset - Dataset
iterFilter f n ds
  | n  0 = iterFilter f (n - 1) (f ds)
  | otherwise = ds

smooth :: Int - Dataset - Dataset
smooth = iterFilter $ filter3 lowPass3

formWindows :: Dataset - [FilterWindow3]
formWindows ds =
  internalList $ zip3 x y z
where c0 = [head ds]
  cn = [last ds]
  x  = ds ++ cn ++ cn
  y  = c0 ++ ds ++ cn
  z  = c0 ++ c0 ++ ds


The key idea is that I can take care of edge conditions with that last 
function.  It lets me build a list of 3-tuples, each of which is 
reduced to a single point in the next rewrite of the dataset.  I used 
zip3 to build up that list, and I take care to keep the lists the same 
length by  duplicating the head and last elements as necessary.  Has 
anyone done this sort of thing before?


Any and all style advice welcome.

Thanks,

Michael Feathers









--
Now Playing: http://www.youtube.com/watch?v=SsnDdq4V8zg

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Embedded Functions in Algebraic Data Types?

2008-02-10 Thread Michael Feathers

On a lark, I loaded this into Hugs this morning, and it didn't complain:


data Thing = Thing (Integer - Integer)



But, I've never seen that sort of construct in an example.  Do people 
ever embed functions in ADTs?



Michael

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Embedded Functions in Algebraic Data Types?

2008-02-10 Thread Michael Feathers


Great. Thanks to everyone!

Michael

Luke Palmer wrote:

Quite frequently.

Here are a few examples from my own code:

For functional references (representing a bidirectional function
from a data type to a part of itself (for example the first element of
a pair)).

  

data Accessor s a
= Accessor { get :: s - a
   , set :: a - s - s
   }



My quantum computation arrow (really in the realm of concrete, useful
things, huh? :-)

  

data Operator b c
= Op (forall d. QStateVec (b,d) - IO (QStateVec (c,d)))
| ...



The ubiquitous FRP Behavior, comprising a current value and a function
which takes a timestep and returns the next value.

  

data Behavior a
   = Behavior a (Double - Behavior a)



The suspend monad, representing a computation which can either
finish now with a value of type a, or suspends to request a value of
type v before continuing.

  

data Suspend v a
= Return a
| Suspend (v - Suspend v a)



It seems that most frequently, functions in ADTs are used when
implementing monads or arrows, but that doens't need to be the case.
A lot of times a function is the best way to represent a particular
part of a data structure :-)

Luke

On Feb 10, 2008 1:34 PM, Michael Feathers [EMAIL PROTECTED] wrote:
  

On a lark, I loaded this into Hugs this morning, and it didn't complain:


data Thing = Thing (Integer - Integer)



But, I've never seen that sort of construct in an example.  Do people
ever embed functions in ADTs?


Michael

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe




  


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] nub vs. find + (:) Is this abysmal code?

2008-02-10 Thread Michael Feathers


How bad is this:

addProduct :: [Product] - Product - [Product]
addProduct inventory product = nub (product : inventory)


compared to this:

addProduct :: [Product] - Product - [Product]
addProduct inventory p
   | isNothing (find (==p) inventory)= p : inventory
   | otherwise= inventory


My guess is that the latter is more efficient, but then when I think 
about laziness, I wonder whether the first is a fair trade.


Michael
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe