Re: [Haskell-cafe] Interpreter with Cont

2011-11-20 Thread David Menendez
On Sat, Nov 19, 2011 at 3:29 PM, Felipe Almeida Lessa
 wrote:
> On Sat, Nov 19, 2011 at 6:08 PM, Tim Baumgartner
>  wrote:
>> I have not yet gained a good understanding of the continuation monad, but I
>> wonder if it could be used here. What would a clean solution look like?
>> Perhaps there are other things that need to be changed as well?
>
> Your 'Interaction' data type is actually an instance of the more
> general "operational monad" (as named by Heinrich Apfelmus) or "prompt
> monad" (as named by Ryan Ingram).

Both of which are just disguised free monads. For reference:


data Free f a = Val a | Wrap (f (Free f a))

foldFree :: Functor f => (a -> b) -> (f b -> b) -> Free f a -> b
foldFree v w (Val a)  = v a
foldFree v w (Wrap t) = w $ fmap (foldFree v w) t

instance Functor f => Monad (Free f) where
return  = Val
m >>= f = foldFree f Wrap m



To use Free, just find the signature functor for Interaction by
replacing the recursive instances with a new type variable,

data InteractionF a b x = ExitF b
| OutputF b x
| InputF (a -> x)

instance Functor (InteractionF a b) where
fmap f (ExitF b) = ExitF b
fmap f (OutputF b x) = OutputF b (f x)
fmap f (InputF g)= InputF (f . g)

roll :: InteractionF a b (Interaction a b) -> Interaction a b
roll (ExitF b) = Exit b
roll (OutputF b x) = Output b x
roll (InputF g)= Input g


type InteractionM a b = Free (InteractionF a b)

runM :: InteractionM a b b -> Interaction a b
runM = foldFree Exit roll

exit :: b -> InteractionM a b c
exit b = Wrap (ExitF b)

output :: b -> InteractionM a b ()
output b = Wrap (OutputF b (Val ()))

input :: InteractionM a b a
input = Wrap (InputF Val)

-- 
Dave Menendez 


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


Re: [Haskell-cafe] Lifted Spine View

2011-11-20 Thread Antoine Latter
2011/11/20 bob zhang :
> Hi, all
>    I tried to follow the program of the paper "Scrap your boilerpolate"
> Revolutions. Unfortunately,
> I found the program in the section lifted spine view does not compile in my
> GHC, could anybody
>  point out where I am wrong? Many Thanks
>
> My code is posted here http://hpaste.org/54357
>

Hello!

What error do you get? Which version of GHC are you using?

Thanks,
Antoine

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


[Haskell-cafe] Lifted Spine View

2011-11-20 Thread bob zhang
Hi, all
I tried to follow the program of the paper "Scrap your boilerpolate"
Revolutions. Unfortunately,
I found the program in the section lifted spine view does not compile in
my GHC, could anybody
point out where I am wrong? Many Thanks

My code is posted herehttp://hpaste.org/54357

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


[Haskell-cafe] thread blocked indefinitely in an STM transaction

2011-11-20 Thread Eric Wong
Hi everyone,

I'm writing an API server using the snap framework with the new snaplet 
infrastructure. In order to connect with the database, I'm using snaplet-hdbc, 
HDBC, HDBC-mysql.  (I'm using InnoDB for storage engine so it can process 
transaction).  Every query is wrapped in the function withTransaction' so I 
don't have to commit or rollback by hand. If there's a SqlError raised, I will 
catch it, log the error and return an error message to the client side.  But 
when running the program, if there's a DB error, the process will be blocked 
and there's an error message: " thread blocked indefinitely in an STM 
transaction". There's no STM related code in my code. Do you have any idea on 
this error and how to process this?
Thanks.

Eric.

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


Re: [Haskell-cafe] os.path.expanduser analogue

2011-11-20 Thread Ben Gamari
On Sun, 20 Nov 2011 21:02:30 -0500, Brandon Allbery  wrote:
> On Sun, Nov 20, 2011 at 20:36, Ben Gamari  wrote:
[Snip]
> 
> Although arguably there should be some error checking.
> 
Thanks for the improved implementation. I should have re-read my code
before sending as it wasn't even close to correct.

Cheers,

- Ben


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


Re: [Haskell-cafe] os.path.expanduser analogue

2011-11-20 Thread Brandon Allbery
On Sun, Nov 20, 2011 at 20:36, Ben Gamari  wrote:

> expandUser :: FilePath -> IO FilePath
> expandUser p = if "~/" `isPrefixOf` p
>  then do u <- getLoginName
>  return $ u ++ drop 2 p
>  else return p
>

expandUser "~" = fmap homeDirectory getLoginName
expandUser ('~':'/':p) = getLoginName >>=
 fmap ((++ p) . homeDirectory)
  getUserEntryForName
expandUser ('~':up)= let (u,p) = break (== '/') up
  in fmap ((++ (drop 1 p)) . homeDirectory
  (getUserEntryForName u)
expandUser p   = p

Although arguably there should be some error checking.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] os.path.expanduser analogue

2011-11-20 Thread Ben Gamari
On the whole, the filepath package does an excellent job of providing
basic path manipulation tools, one weakness is the inability to resolve
"~/..." style POSIX paths. Python implements this with
os.path.expanduser. Perhaps a similar function might be helpful in
filepath?

Cheers,

- Ben

Possible (but untested) implementation
expandUser :: FilePath -> IO FilePath
expandUser p = if "~/" `isPrefixOf` p
  then do u <- getLoginName
  return $ u ++ drop 2 p
  else return p

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


Re: [Haskell-cafe] Decision procedure for foldr/foldl/foldl'?

2011-11-20 Thread wren ng thornton

On 11/20/11 11:58 AM, Daniel Fischer wrote:

On Sunday 20 November 2011, 17:28:43, David Fox wrote:

Does anyone have a quick way to decide which of the fold functions to
use in a given situation?  There are times when I would like to find
out which to use in the quickest way possible, rather than reading a
long explanation of why each one behaves the way it does.



- foldl: In the rare cases where you need this, you'll probably know (I'm
not aware of any real-world case where foldl is the correct choice)


If your folding function is a constructor, then the result will already 
be in WHNF, therefore foldl' is doing extra work (checking for WHNF) 
that it doesn't need to.


If your folding function is (.), the foldl variant is superior to foldl' 
because it avoids making a bunch of unnecessary intermediate 
functions/closures.


Those are the only notable real-world examples I can recall.

--
Live well,
~wren

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


Re: [Haskell-cafe] Superset of Haddock and Markdown

2011-11-20 Thread Ivan Lazar Miljenovic
On 21 November 2011 03:19, David Fox  wrote:
> On Fri, Nov 18, 2011 at 1:10 AM, Ertugrul Soeylemez  wrote:
>> Ivan Lazar Miljenovic  wrote:
>>
>>> Wasn't there talk at one stage of integrating pandoc into haddock?
>>
>> I wouldn't mind Haddock depending on Pandoc, at least optionally
>> (-fmarkdown-comments).  Taking this to its conclusion you could easily
>> have syntax-highlighted code examples in Haddock documentations and
>> allow alternative output formats.
>
> I'm not sure the pandoc license (GPL) is compatible with the GHC license.

Do you mean because GHC ships with a Haddock binary?

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] Decision procedure for foldr/foldl/foldl'?

2011-11-20 Thread Daniel Fischer
On Sunday 20 November 2011, 17:28:43, David Fox wrote:
> Does anyone have a quick way to decide which of the fold functions to
> use in a given situation?  There are times when I would like to find
> out which to use in the quickest way possible, rather than reading a
> long explanation of why each one behaves the way it does.
> 

- foldl: In the rare cases where you need this, you'll probably know (I'm 
not aware of any real-world case where foldl is the correct choice)

Rule of thumb:

Can the result be determined/constructed (at least partially) before the 
end of the list has been reached?[*]
Then foldr.
Otherwise foldl'.

Exceptions to the rule may exist.

[*] That typically means the folded function is lazy in its second 
argument, like (:), (++), (&&), (||) ...

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


[Haskell-cafe] Decision procedure for foldr/foldl/foldl'?

2011-11-20 Thread David Fox
Does anyone have a quick way to decide which of the fold functions to
use in a given situation?  There are times when I would like to find
out which to use in the quickest way possible, rather than reading a
long explanation of why each one behaves the way it does.

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


Re: [Haskell-cafe] Superset of Haddock and Markdown

2011-11-20 Thread David Fox
On Fri, Nov 18, 2011 at 1:10 AM, Ertugrul Soeylemez  wrote:
> Ivan Lazar Miljenovic  wrote:
>
>> Wasn't there talk at one stage of integrating pandoc into haddock?
>
> I wouldn't mind Haddock depending on Pandoc, at least optionally
> (-fmarkdown-comments).  Taking this to its conclusion you could easily
> have syntax-highlighted code examples in Haddock documentations and
> allow alternative output formats.

I'm not sure the pandoc license (GPL) is compatible with the GHC license.

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


Re: [Haskell-cafe] Visi.Pro -- My Next Thing

2011-11-20 Thread Simon Clarkstone
On Fri, Nov 18, 2011 at 5:04 PM, David Pollak
 wrote:
> I've launch a new, Haskell powered, adventure: Visi.Pro, Cloud Computing for
> the Rest of Us.  Visi.Pro will offer a HyperCard-like development
> environment that will empower normal people to build and run beautiful,
> interactive apps on their iPad and seamlessly integrate the Cloud including
> real-time data feeds and destinations.

I think there are some lists of commercial users of Haskell around
that you could add this venture to.  The IHG comes to mind, but is
more expensive than I remembered it being.

http://industry.haskell.org/

-- 
src/

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