Re: [Haskell-cafe] indentation with let and do

2013-10-03 Thread David McBride
Imagine if bar was a toplevel function

bar = case foo of
True -> " Foo";
False -> "Bar";

Keep in mind that indentation level starts at the function name, not at the
let keyword.


On Thu, Oct 3, 2013 at 2:31 PM, Corentin Dupont
wrote:

> Hi the list,
> why do this function doesn't compile (parse error):
>
> test :: Bool -> IO ()
> test foo = do
>let bar = case foo of
>True ->  "Foo";
>False -> "Bar"
>return ()
>
> while this one does (just adding one space in front of True and False):
>
> test :: Bool -> IO ()
> test foo = do
>let bar = case foo of
> True ->  "Foo";
> False -> "Bar"
>return ()
>
>
> Thanks!!
> Corentin
>
> ___
> 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


Re: [Haskell-cafe] Importing more modules by default

2013-08-08 Thread David McBride
I've started using BasicPrelude with -XNoImplicitPrelude in all of my
code.  It imports all of those and some other stuff as well (text related
functions).  Cuts down on my imports by a little over half.  Kind of wish
it could be made the default.


On Wed, Aug 7, 2013 at 10:23 PM, aditya bhargava
wrote:

> Hi there,
> It seems like every Haskell program I write imports the following modules:
>
> Control.Monad
> Control.Applicative
> Data.Maybe
> Data.List
>
> Is there a good reason why these modules aren't imported by default? When
> I write a simple script usually a 1/4th of the script is just imports, and
> my code just looks uglier.
>
> Adit
>
> ___
> 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


Re: [Haskell-cafe] How can I use ghci more wisely?

2013-07-24 Thread David McBride
You might like to know about this option for ghci -interactive-print

I tested it with data-pprint though and it didn't work because it
returns an IO Doc instead of IO () (I assume).  But if you wrote a
function that used that, returned the right type, cabal installed it
and put it in your .ghci, you would have your pprinting by default
whenever you use ghci.

On Wed, Jul 24, 2013 at 7:33 AM, Jun Inoue  wrote:
> The data-pprint package's pprint function might give you a quick fix.
> For example:
>
> Prelude> :m Data.PPrint
> Prelude Data.PPrint> pprint [1..]
> [1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19,
>  20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36,
>  37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49, 50, 51, 52, 53,
>  54, 55, 56, 57, 58, 59, 60, 61, 62, 63, 64, 65, 66, 67, 68, 69, 70,
>  71, 72, 73, 74, 75, 76, 77, 78, 79, 80, 81, 82, 83, 84, 85, 86, 87,
>  88, 89, 90, 91, 92, 93, 94, 95, 96, 97, 98, 99, 100, 101, 102, 103,
>  104, 105, 106, 107, 108, 109, 110, 111, 112, 113, 114, 115, 116,
>  117, 118, 119, 120, 121, 122, 123, 124, 125, 126, 127, 128, 129,
>  130, 131, 132, 133, 134, 135, …, ……]
> Prelude Data.PPrint> let long_computation = long_computation
> Prelude Data.PPrint> pprint [1, long_computation, 3]
> [1, ⊥₁, 3]
>   ⊥₁: timeout at 0%
>
> It's a bit of a hassle to have to type "pprint" all the time though,
> and it doesn't give you a way to show the data without printing to the
> terminal in the IO monad.
>
> On Wed, Jul 24, 2013 at 4:30 AM, yi lu  wrote:
>> I am wondering how can I ask ghci to show an infinite list wisely.
>> When I type
>>
>> fst ([1..],[1..10])
>>
>> The result is what as you may guess
>>
>> 1,2,3,4,...(continues to show, cut now)
>>
>> How could I may ghci show
>>
>> [1..]
>>
>> this wise way not the long long long list itself?
>>
>> Yi
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
>
> --
> Jun Inoue
>
> ___
> 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


Re: [Haskell-cafe] Parsec error message not making any sense

2013-07-10 Thread David McBride
First, I want to say you'd have a lot better luck with these questions
by posting to stackoverflow.  This really isn't the right place for
it.

As for why your parser is not working, you need to realize that parsec
does not backtrack by default.  It does this to conserve memory (so it
doesn't have to save its location at every possible branch point).

When you go many1 (interval name), it will parse the five intervals
[n] lines, and then try to parse a 6th one.  Well it turns out the
next atom begins with an 'i' character.  When it hits the t afterword,
that was wrong, it was expecting "intervals [", not an i followed by a
t.  That error message is exactly right.  At that point it fails,
which is fine, it is supposed to fail, but it unfortunately does not
move its place in the text stream back up to the i, it stays at the
't' character, then tries to parse more item blocks starting there.

The fix is to change interval to: "interval tierName = try $ do".
That means if it fails anywhere in the interval block, it will move
the parser back to where it was when the try was hit and then try to
parse it in some other manner.

I think that the rest of your code is pretty good, but you will have
to fix a few more things to completely parse your file.

On Tue, Jul 9, 2013 at 4:23 PM, Fredrik Karlsson  wrote:
> Hi,
>
> Sorry, that was a careless extraction of code - I should have made sure that
> it was complete.
> Please, have a look again. When downloading and running the gist
> (https://gist.github.com/dargosch/5955045) , I still get the error:
>
> Main> let testFile =
> "/Users/frkkan96/Documents/src/ume/umecore/testing/testdata/testdata.TextGrid"
> *Main> parseFromFile textgridfile testFile
> Left
> "/Users/frkkan96/Documents/src/ume/umecore/testing/testdata/testdata.TextGrid"
> (line 35, column 5):
> unexpected "t"
> expecting "intervals ["
>
> on the attached testfile. The "tier" parser works once, but then I get an
> error that I cant understand, given the input.
> How come the parser finds the "unexpected "t"" when the expected thing is
> what is in the input at that point?
>
> Thankful for any help I can get on this.
>
>
> On Tue, Jul 9, 2013 at 10:22 PM, Fredrik Karlsson 
> wrote:
>>
>> Hi,
>>
>> Sorry, that was a careless extraction of code - I should have made sure
>> that it was complete.
>> Please, have a look again. When downloading and running the gist, I still
>> get the error:
>>
>> Main> let testFile =
>> "/Users/frkkan96/Documents/src/ume/umecore/testing/testdata/testdata.TextGrid"
>> *Main> parseFromFile textgridfile testFile
>> Left
>> "/Users/frkkan96/Documents/src/ume/umecore/testing/testdata/testdata.TextGrid"
>> (line 35, column 5):
>> unexpected "t"
>> expecting "intervals ["
>>
>> on the attached testfile. The "tier" parser works once, but then I get an
>> error that I cant understand, given the input.
>> How come the parser finds the "unexpected "t"" when the expected thing is
>> what is in the input at that point?
>>
>> Thankful for any help I can get on this.
>>
>>
>> /Fredrik
>>
>>
>> On Tue, Jul 9, 2013 at 9:37 AM, Roman Cheplyaka  wrote:
>>>
>>> Please check your code.
>>>
>>> I had two problems with it: mixed tabs and spaces, and undefined
>>> 'quotedChar'. After defining quotedChar = anyChar, I get a different
>>> error message from yours:
>>>
>>>   *Main> parseFromFile textgridfile "testdata.TextGrid"
>>>   Left "testdata.TextGrid" (line 137, column 1):
>>>   unexpected end of input
>>>   expecting quote at end of cell
>>>
>>> Roman
>>>
>>> * Fredrik Karlsson  [2013-07-09 08:07:24+0200]
>>> > Hi Roman,
>>> >
>>> > I'm using parsec-3.1.3
>>> >
>>> > I put the code in a gist here - sorry about that.
>>> >
>>> > https://gist.github.com/dargosch/5955045
>>> >
>>> > Fredrik
>>> >
>>> >
>>> >
>>> >
>>> > On Tue, Jul 9, 2013 at 12:08 AM, Roman Cheplyaka 
>>> > wrote:
>>> >
>>> > > Hi Fredrik,
>>> > >
>>> > > First, do you use the latest parsec version (3.1.3)? If not, can you
>>> > > try
>>> > > the same with 3.1.3?
>>> > >
>>> > > Second, please upload your code to hpaste.org or a similar service
>>> > > and
>>> > > give us the link. It's not much fun to extract code from an html
>>> > > email.
>>> > >
>>> > > Roman
>>> > >
>>> > > * Fredrik Karlsson  [2013-07-08 23:54:17+0200]
>>> > > > Dear list,
>>> > > >
>>> > > > I have a Parsec parser that fails and gives the following error
>>> > > > message:
>>> > > >
>>> > > > *Main> parseFromFile textgridfile testFile
>>> > > > Left
>>> > > >
>>> > >
>>> > > "/Users/frkkan96/Documents/src/ume/umecore/testing/testdata/testdata.TextGrid"
>>> > > > (line 35, column 5):
>>> > > > unexpected "t"
>>> > > > expecting "intervals ["
>>> > > >
>>> > > > Now, this is perfectly understandable, but line 35, col 5 in the
>>> > > > file
>>> > > being
>>> > > > parsed looks like the supplies image - there is no 't' there.
>>> > > >
>>> > > > Any ideas on what is going on?
>>> > > >
>>> > > > The parser I am using is:
>>> > > >
>>> > > > data VariableLine = 

Re: [Haskell-cafe] same function's type accepted in top level, but rejected in where clause

2013-07-05 Thread David McBride
If you remove the type signature from f in the where clause it will
work.  The reason is because the type signature listed there, the a is
a different a than in the top level signature.  If you change it from
a to x, it says it should be the a that you can't seem to specify.

If you add the pragma ScopedTypeVariables to your file, it works the
way you would assume.  However you will have to change the toplevel
signature to iterateListF :: forall a. (a -> a) -> a -> Fix (ListF a)
in order to make it work (added the forall a.).

On Fri, Jul 5, 2013 at 4:35 PM, Ömer Sinan Ağacan  wrote:
> Hi all,
>
> I came across an interesting type checker error, a function is
> accepted in top level, but rejected by type checker when moved to
> `where ...` clause.
>
> I moved required code to a new module for demonstration purposes:
>
>
> module Bug where
>
> fix :: (a -> a) -> a
> fix f = let x = f x in x
>
> data Fix f = Fix (f (Fix f))
>
> unFix :: Fix f -> f (Fix f)
> unFix (Fix a) = a
>
> data ListF a l = NilF | ConsF a l
>
> instance Functor (ListF a) where
> fmap _ NilF= NilF
> fmap f (ConsF a l) = ConsF a (f l)
>
> fold :: Functor f => (f a -> a) -> Fix f -> a
> fold f a = f (fmap (fold f) (unFix a {- f (Fix f) -}))
>
> unfold :: Functor f => (a -> f a) -> a -> Fix f
> unfold f a = Fix (fmap (unfold f) (f a))
>
>
> Now, after this code, type checker accept this function:
>
>
> iterateListF :: (a -> a) -> a -> Fix (ListF a)
> iterateListF fn e = unfold (foldFn fn) e
>
> foldFn :: (a -> a) -> a -> ListF a a
> foldFn fn a = ConsF a (fn a)
>
>
> But rejects this:
>
>
> iterateListF :: (a -> a) -> a -> Fix (ListF a)
> iterateListF fn e = unfold f e
>   where
> f :: a -> ListF a a
> f a = ConsF a (fn a)
>
>
> With error:
>
>
> bug.hs:27:20:
> Couldn't match expected type `a1' with actual type `a'
>   `a1' is a rigid type variable bound by
>the type signature for f :: a1 -> ListF a1 a1 at bug.hs:26:10
>   `a' is a rigid type variable bound by
>   the type signature for
> iterateListF :: (a -> a) -> a -> Fix (ListF a)
>   at bug.hs:23:17
> In the return type of a call of `fn'
> In the second argument of `ConsF', namely `(fn a)'
> In the expression: ConsF a (fn a)
>
>
> Changing type variables in type of `f` to `x` fails with this error:
>
>
> bug.hs:28:20:
> Couldn't match expected type `x' with actual type `a'
>   `x' is a rigid type variable bound by
>   the type signature for f :: x -> ListF x x at bug.hs:27:10
>   `a' is a rigid type variable bound by
>   the type signature for
> iterateListF :: (a -> a) -> a -> Fix (ListF a)
>   at bug.hs:24:17
> In the return type of a call of `fn'
> In the second argument of `ConsF', namely `(fn a)'
> In the expression: ConsF a (fn a)
> Failed, modules loaded: none.
>
>
> .. and this is strange because error message describes function as it
> is before changing `a` to `x`.
>
>
> Any ideas why this definition rejected? Is this a bug in GHC?
>
>
> ---
> Ömer Sinan Ağacan
> http://osa1.net
>
> ___
> 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


Re: [Haskell-cafe] Basic Parsec float & integer parsing question

2013-07-05 Thread David McBride
Token parsers are specific to different languages.  Afterall, haskell
parses floats differently than C, which is different from java
(probably).  In order to use it in your code you have to tell it that,
like so:

haskelldef = makeTokenParser haskellDef

header :: Parser LabelFile
header = do
  string headTS1
  start <- fmap double2Float $ float haskelldef
  string "\nxmax = "
  end <- fmap double2Float $ float haskelldef
  string "\ntiers? \nsize = "
  integer haskelldef
  char '\n'
  return $ LabelFile start end

You'll need to import GHC.Float (double2Float) to get those parsed
values as floats.

On Fri, Jul 5, 2013 at 12:42 PM, Fredrik Karlsson  wrote:
> Dear list,
>
> Sorry for asking a simple parsec question, but both Parsec and Haskell is
> new to me, so please be gentle :-)
>
> I have this code:
>
> 
> import Text.ParserCombinators.Parsec
> import Text.Parsec.Token
> import Text.ParserCombinators.Parsec.Char
>
>
> data VariableLine = VariableLine String String deriving Show
> data TierType = IntervalTier | PointTier deriving Show
>
> data Tier = Tier TierType String Float Float Integer
> data Label = Interval Float Float String
> data LabelFile = LabelFile Float Float
>
> symbol :: Parser Char
> symbol = oneOf "!#$%&|*+-/:<=>?@^_~"
>
> testString = "intervals [1]:\nxmin = 0 \nxmax = 0.028192
> \ntext = \"\""
> headTS1 = "File type = \"ooTextFile\"\nObject class = \"TextGrid\"\n\nxmin
> ="
>
> header :: Parser LabelFile
> header = do
> headTS1
> start <- float
> string "\nxmax = "
> end <- float
> string "\ntiers? \nsize = "
> integer
> char '\n'
> return $ LabelFile start end
>
> 
>
> Loading it into ghci I get :
>
> Prelude> :l parsectest.hs
> [1 of 1] Compiling Main ( parsectest.hs, interpreted )
>
> parsectest.hs:21:9:
> Couldn't match type `[]'
>   with `Text.Parsec.Prim.ParsecT
>   String () Data.Functor.Identity.Identity'
> Expected type: Text.Parsec.Prim.ParsecT
>  String () Data.Functor.Identity.Identity Char
>   Actual type: [Char]
> In a stmt of a 'do' block: headTS1
> In the expression:
>   do { headTS1;
>start <- float;
>string
>  "\
>  \xmax = ";
>end <- float;
> }
> In an equation for `header':
> header
>   = do { headTS1;
>  start <- float;
>  string
>"\
>\xmax = ";
>   }
>
> parsectest.hs:22:18:
> Couldn't match expected type `Text.Parsec.Prim.ParsecT
> String () Data.Functor.Identity.Identity
> Float'
> with actual type `GenTokenParser s0 u0 m0
>   -> Text.Parsec.Prim.ParsecT s0 u0 m0
> Double'
> In a stmt of a 'do' block: start <- float
> In the expression:
>   do { headTS1;
>start <- float;
>string
>  "\
>  \xmax = ";
>end <- float;
> }
> In an equation for `header':
> header
>   = do { headTS1;
>  start <- float;
>  string
>"\
>\xmax = ";
>   }
>
> parsectest.hs:24:16:
> Couldn't match expected type `Text.Parsec.Prim.ParsecT
> String () Data.Functor.Identity.Identity
> Float'
> with actual type `GenTokenParser s1 u1 m1
>   -> Text.Parsec.Prim.ParsecT s1 u1 m1
> Double'
> In a stmt of a 'do' block: end <- float
> In the expression:
>   do { headTS1;
>start <- float;
>string
>  "\
>  \xmax = ";
>end <- float;
> }
> In an equation for `header':
> header
>   = do { headTS1;
>  start <- float;
>  string
>"\
>\xmax = ";
>   }
>
> parsectest.hs:26:9:
> Couldn't match expected type `Text.Parsec.Prim.ParsecT
> String () Data.Functor.Identity.Identity
> a0'
> with actual type `GenTokenParser s2 u2 m2
>   -> Text.Parsec.Prim.ParsecT s2 u2 m2
> Integer'
> In a stmt of a 'do' block: integer
> In the expression:
>   do { headTS1;
>start <- float;
>string
>  "\
>  \xmax = ";
>end <- float;
> }
> In an equation for `header':
> header
>   = do { headTS1;
>  start <- float;
>  string
>"\
> 

Re: [Haskell-cafe] "Casting" newtype to base type?

2013-07-02 Thread David McBride
You could always just put it into your newtype:

newtype IOS = IOS {
  unIOS :: IO String
}

On Tue, Jul 2, 2013 at 9:31 AM, Vlatko Basic  wrote:
>
>
>  Original Message  
> Subject: Re: [Haskell-cafe] "Casting" newtype to base type?
> From: Tom Ellis 
> To: haskell-cafe@haskell.org
> Date: 02.07.2013 15:25
>
>> On Tue, Jul 02, 2013 at 03:03:08PM +0200, Vlatko Basic wrote:
>>>
>>> Is there a nicer way to extract the 'IO String' from 'IOS',
>>> without 'case' or without pattern matching the whole 'P'?
>>>
>>> newtype IOS = IOS (IO String)
>>> data P = P {
>>>getA :: String,
>>>getB :: String,
>>>getC :: IOS
>>>} deriving (Show, Eq)
>>>
>>>
>>> getC_IO :: P -> IO String
>>> getC_IO p =
>>>case getC p of
>>>  IOS a -> a
>>> getC_IO (P _ _ (IOS a)) = a
>>
>>
>> How about
>>
>>  unIOS :: IOS -> IO String
>>  unIOS (IOS a) = a
>>
>>  getC_IO :: P -> IO String
>>  getC_IO = unIOS . getC
>>
> Thanks for your answer.
> I had those two funcs, but thought there might be a shorter/prettier
> one-func one-liner. :-)
>
>
>> Tom
>>
>> ___
>> 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] (+) on two lists ?

2013-02-14 Thread David McBride
sum' [] = []  -- returns a list of something the way you intended
sum' (x:xs) = x + xum' xs -- you intended it not to return a list but it
could if you think about it.

The compiler says I think returns a list based on what I see so far, well
if you can add these together then the only way you could get a list from
that is if you were adding two lists together ie (+ l1 l2) :: [a] -> [a] ->
[a].  That works if we assume that sum' must have accepted [[a]] and
returned [a].

But in order for that to be the case [a] must be an instance of Num,
otherwise they couldn't be added together like that, so tack on a Num [a]
requirement on.

But having a typeclass of the form [a] that requires an extension,
FlexibleContexts, which you can read about here:
http://www.haskell.org/ghc/docs/7.0.2/html/users_guide/other-type-extensions.html#flexible-contexts

On Fri, Feb 15, 2013 at 2:33 AM, sheng chen  wrote:

> Hi,
>
> I was puzzled by the following little program.
>
> sum' [] = []
> sum' (x:xs) = x + sum' xs
>
> I thought the GHC type checker will report a type error. However, the type
> checker accepts this program and gives the type
>
> Num [a] => [[a]] -> [a]
>
> When I add type annotation to the program
>
> sum' :: Num [a] => [[a]] -> [a]
> sum' [] = []
> sum' (x:xs) = x + sum' xs
>
> The GHC asks me to add FlexibleContexts language extension.
>
> I would appreciate explanation on this issue.
>
> Thanks,
> Sheng
>
> ___
> 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


Re: [Haskell-cafe] Teaching Haskell @ MOOCs like Coursera or Udacity

2012-10-24 Thread David McBride
I'm taking it primarily because it is taught by the guy who made the
language.  I mean how cool is that?  He is very smart and certainly blows
any other lecturer I've ever had out of the water.  If SPJ were doing a
haskell course I'd sign up for that too in a heart beat.

There's also a slim possibility that coursera will become something
industry people can look at to find people with skills they need.  A nice
perk if it works out, for something I'm doing for fun anyways.

On Wed, Oct 24, 2012 at 4:06 PM, Eric Rasmussen wrote:

> I can see that the required effort would be prohibitive, but after
> thinking about this some more I do think there are a couple of nice
> advantages:
>
> 1) Quizzes and graded assignments offer some structure to self study, and
> having some form of feedback/validation when you first get started is
> helpful. I learned a lot of Haskell by making up my own assignments, but
> not everyone is willing to put that kind of time into it.
>
> 2) I know several developers with great engineering skills who are taking
> the Scala course because it gives them a structured way to get into it and
> have something to show for the time on their resume. They're busy
> professionals whose skills and expertise in large projects could really
> benefit the Haskell community, but I've had no luck convincing them that
> it's worth the time spent researching and learning on their own.
>
> Scala already has some appeal for them if they have to work with java code
> or have spent years with object oriented programming, so I think the more
> the Haskell community can do to bring them here, the better.
>
> Whether or not it's feasible to create the course is another issue. I
> don't have an academic background or any academic affiliations to get the
> ball rolling, but if anyone wants to make a course I'll volunteer to help
> proof materials, test quizzes and assignments, and work on utilities to
> submit and grade assignments.
>
>
> On Tue, Oct 23, 2012 at 7:02 AM, Brent Yorgey wrote:
>
>> On Thu, Oct 18, 2012 at 11:49:08PM +0530, niket wrote:
>> > I am a novice in Haskell but I would love to see the gurus out here
>> > teaching Haskell on MOOCs like Coursera or Udacity.
>> >
>> > Dr Martin Odersky is doing it for Scala here:
>> > https://www.coursera.org/course/progfun
>> >
>> > I would love to see Haskell growing on such new platforms!
>>
>> Just as a counterpoint, putting together a MOOC is a *ton* of work,
>> with (in my opinion) not much benefit for a topic like Haskell where
>> it is already possible to access lots of quality instructional
>> materials online.  I would rather see Haskell gurus put their time and
>> effort into producing more awesome code (or into curating existing
>> instructional materials).
>>
>> Just my 2c.
>>
>> -Brent
>>
>> ___
>> 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Yesod a href render issue

2012-08-31 Thread David McBride
Hamlet is whitespace sensitive like haskell and python.  If you put a tag
after text, it is treated as text.

Write the  wrote:

> I'm following Yesod tutorial that gives this as the first example for
> "type-safe URLs":
>
> | getHomeR  = defaultLayout [whamlet|Go to page 1!|]
>
> Worked fine, the "a href" generated looks perfect.
> Then I tried this:
>
> | getHomeR  = defaultLayout [whamlet|Hello!Go to page
> 1!|]
>
> And got a "a href" referecing a URL without quotes and with no end tag
> for "a", something like this:
>
> | HelloGo to
> page 1!
>
> I tried in many different ways, and the only way to get it working
> properly was to set the "a" tag in a line by itself:
>
> | getHomeR  = defaultLayout [whamlet|Hello!
> | Go to page 1!
> | |]
>
> Is this a failure of Yesod quasiquotation or am I missing something?
> I know Yesod clearly states that the best approach is to use external
> files instead of quasiquotes, but as I'm making my first steps into
> Yesod, I would like to use the practical embedded quasiquotes.
>
> ___
> 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


Re: [Haskell-cafe] hGetContents Illegal byte sequence / ghc-pkg

2012-08-11 Thread David McBride
I had this same problem a couple weeks ago when trying to install
virthualenv and I don't really understand it got into a bad state, but the
way I solved it was by fixing the locale settings on my gentoo machine so
that I'm using UTF8.  That just involved a few changes in /etc and then the
problem went away.

On Sat, Aug 11, 2012 at 7:13 AM, Benjamin Edwards wrote:

> Hello café,
>
> I have a program that is crashing, and I have no idea why:
>
> module Main
>   where
>
> import System.Process (readProcessWithExitCode)
>
>
> main :: IO ()
> main = do _ <- readProcessWithExitCode "ghc-pkg" ["describe", "hoopl"] ""
>   putStrLn "Should never get here"
>
> this is using the process package from hackage. The program crashes with
>
> minimal-test: fd:5: hGetContents: invalid argument (invalid byte sequence)
> minimal-test: thread blocked indefinitely in an MVar operation
>
> inspecting the source of readProcessWithExitCode yields an obvious
> explanation to the MVar problem, but I don't understand why hGetContents is
> so offended.
>
> For the lazy it is defined as follows:
>
> readProcessWithExitCode
> :: FilePath -- ^ command to run
> -> [String] -- ^ any arguments
> -> String   -- ^ standard input
> -> IO (ExitCode,String,String) -- ^ exitcode, stdout, stderr
> readProcessWithExitCode cmd args input = do
> (Just inh, Just outh, Just errh, pid) <-
> createProcess (proc cmd args){ std_in  = CreatePipe,
>std_out = CreatePipe,
>std_err = CreatePipe }
>
> outMVar <- newEmptyMVar
>
> -- fork off a thread to start consuming stdout
> out  <- hGetContents outh
> _ <- forkIO $ C.evaluate (length out) >> putMVar outMVar ()
>
> -- fork off a thread to start consuming stderr
> err  <- hGetContents errh
> _ <- forkIO $ C.evaluate (length err) >> putMVar outMVar ()
>
> -- now write and flush any input
> when (not (null input)) $ do hPutStr inh input; hFlush inh
> hClose inh -- done with stdin
>
> -- wait on the output
> takeMVar outMVar
> takeMVar outMVar
> hClose outh
> hClose errh
>
> -- wait on the process
> ex <- waitForProcess pid
>
> return (ex, out, err)
>
> Now having looked at the source of ghc-pkg it is dumping it's output using
> putStr and friends, so that should be using my local encoding on the
> system, right? and so should hGetContents in my program..?
>
> Now, for the curious: the reason I care is that this problem has
> effectively prevented me from using virthualenv. Sadness and woe.
>
> ___
> 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


Re: [Haskell-cafe] IO() and other datatypes

2012-03-04 Thread David McBride
Just use this rule of thumb.  If it is a monad (like IO Int, IO
String) use do <- notation.  If it isn't a monad (like Int, String),
just use let syntax, same as you did with the first list.

main = do
  let ttime = [8,20,10,15]
  a = dauer ttime  (OPTIONAL let a = dauer ttime)
  putStrLn a

On Sun, Mar 4, 2012 at 1:41 PM, Kevin Clees  wrote:
> Dear Haskell programmers,
>
> I'm very confused, because I really don't know how to handle with IO's and
> other datatypes, such as Int or String.
> If I want to build a haskell program can I only use IO() method outputs ?
> How can I "give" a Int result from a different method back to the main?
> Would this mean that I have to create only IO() outputs? Is this correct?
>
> For example:
>
> -- A User has to choose something, so I need a IO() datatype
> main :: IO()
> main = do
> [...]
> let listtournementTime = [8,20,10,15]
>
> -- This is wrong: Couldn't match expected type `IO t0' with actual type
> `Int'
> -- The results of the method dauer is a Int. Do I have to transform the
> method to an IO() Output
>
> a <- Dauer listtournementTime
>
>
> [...]
>
>
> -- the methods
>
> dauer:: [Int] -> Int
> dauer (x:xs)
>     | laenge(x:xs) == 1 = 0
>     | mod (laenge (x:xs)) 2 == 0 = (tmp x xs) + dauer xs
>     | mod (laenge (x:xs)) 2 /= 0 = dauer xs
>     | otherwise = 99 -- failure
>
> tmp:: Int -> [Int] -> Int
> tmp y (x:xs) = x-y
>
> laenge        :: [a] -> Integer
> laenge []     =  0
> laenge (x:xs) =  1 + laenge xs
>
> The last three methods are working correct, if I directly put some data into
> the methods, like:
> dauer [10,15]
> ===Result===> 5
>
>
> Thank you for any help
>
> Best greetings from Namibia
>
> ___
> 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


Re: [Haskell-cafe] Will changing associativity of enumerator's ($=) affect anyone? (also: enumerator mailing list)

2011-10-15 Thread David McBride
This would be a big boon to newbies.  When I first started using the
library I would get big errors using $= that were because I didn't
have parenthesis I needed, but didn't realize I needed, despite the
fact that the types seemed to line up.

On Sat, Oct 15, 2011 at 12:40 PM, Michael Snoyman  wrote:
> On Sat, Oct 15, 2011 at 4:59 PM, John Millikin  wrote:
>> A user recently suggested changing the associativity of ($=) from [[
>> infixr 0 ]] to [[ infixl 1 ]]. This allows the following expressions
>> to be equivalent:
>>
>>   run $ enumerator $$ enumeratee =$ enumeratee =$ iteratee
>>   run $ enumerator $= enumeratee $$ enumeratee =$ iteratee
>>   run $ enumerator $= enumeratee $= enumeratee $$ iteratee
>>
>> Although this is technically a backward-incompatible change, I feel
>> it's small enough that it could go in a minor release *if nobody
>> depends on the current behavior*.
>>
>> So, if anybody using 'enumerator' will have code broken by this
>> change, please speak up. If I don't hear anything in a week or so,
>> I'll assume it's all clear and will cut the new release.
>>
>> -
>>
>> Second, I was asked whether there's a mailing list for enumerator
>> stuff. To my knowledge there isn't, so I started one on librelist. To
>> subscribe and/or post, send an email to
>> haskell.enumera...@librelist.com . Archives are available at
>> http://librelist.com/browser/haskell.enumerator/ . I plan to make
>> release announcements there (for releases not important enough for
>> haskell-cafe), and it might be useful for general discussion.
>>
>
> I'm strongly in favor of this change, the current associativity has
> caused me to litter some code with a few too many parentheses.
>
> 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


Re: [Haskell-cafe] Binding of an integer variable

2011-07-28 Thread David McBride
It hasn't been evaluated yet.  It is just a thunk.

>let x = 23
>:show bindings
x :: Integer = _
>x
23
>:show bindings
x :: Integer = 23



On Thu, Jul 28, 2011 at 2:43 PM, Paul Reiners  wrote:
> I have a question about the following GHCi interaction:
>
> Prelude> let x = 23
> Prelude> :show bindings
> x :: Integer = _
>
> What is the meaning of the underscore in the third line?  Why doesn't it say
> this, instead?
>
> x :: Integer = 23
>
>
> ___
> 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


Re: [Haskell-cafe] file splitter with enumerator package

2011-07-25 Thread David McBride
I feel like there is a little bit better way to code this by splitting
the file outputting part from the part that counts and checks for
newlines like so:

run_ $ (EB.enumFile "file.txt" $= toChunksnl 4096) $$ toFiles filelist

toFiles [] = error "expected infinite file list"
toFiles (f:fs) = do
  next <- EL.head
  case next of
Nothing -> return ()
Just next' -> do
  liftIO $ L.writeFile f next'
  toFiles fs

toChunksnl n = EL.concatMapAccum (somefunc n) L.empty
  where
somefunc :: Int -> L.ByteString -> B.ByteString -> (L.ByteString,
[L.ByteString])
somefunc = undefined

Where it has an accumulator that starts empty, gets a new bytestring,
then parses the concatenation of those two that into as many full
chunks that end with a newline as it can and stores that in the second
part of the pair and then whatever remains unterminated ends up as the
first part.  I tried to write it myself, but I can't seem to hit all
the edge cases necessary, but it seems like it should be doable for
someone who wants to.  It would be trivial with strings, but with
bytestrings it requires a little elbow grease.

However as to your question on whether you should use iteratees inside
other iteratees, yes of course.  It is all composeable.

On Mon, Jul 25, 2011 at 1:38 PM, Eric Rasmussen  wrote:
> I just found another solution that seems to work, although I don't
> fully understand why. In my original function where I used EB.take to
> strictly read in a Lazy ByteString and then L.hPut to write it out to
> a handle, I now use this instead (full code in the annotation here:
> http://hpaste.org/49366):
>
> EB.isolate bytes =$ EB.iterHandle handle
>
> It now runs at the same speed but in constant memory, which is exactly
> what I was looking for. Is it recommended to nest iteratees within
> iteratees like this? I'm surprised that it worked, but I can't see a
> cleaner way to do it because of the other parts of the program that
> complicate matters. At this point I've achieved my original goals,
> unusual as they are, but since this has been an interesting learning
> experience I don't want it to stop there if there are more idiomatic
> ways to write code with the enumerator package.
>
> On Mon, Jul 25, 2011 at 4:06 AM, David McBride  wrote:
>> Well I was going to say:
>>
>> import Data.Text.IO as T
>> import Data.Enumerator.List as EL
>> import Data.Enumerator.Text as ET
>>
>> run_ $ (ET.enumHandle fp $= ET.lines) $$ EL.mapM_ T.putStrLn
>>
>> for example.  But it turns out this actually concatenates the lines
>> together and prints one single string at the end.  The reason is
>> because it turns out that ET.enumHandle already gets lines one by one
>> without you asking and it doesn't add newlines to the end, so ET.lines
>> looks at each chunk and never sees any newlines so it returns the
>> entire thing concatenated together figuring that was an entire line.
>> I'm kind of surprised that enumHandle fetches linewise rather than to
>> let you handle it.
>>
>> But if you were to make your own enumHandle that wasn't linewise that
>> would work.
>>
>> On Mon, Jul 25, 2011 at 6:26 AM, Yves Parès  wrote:
>>> Okay, so there, the chunks (xs) will be lines of Text, and not just random
>>> blocks.
>>> Isn't there a primitive like printChunks in the enumerator library, or are
>>> we forced to handle Chunks and EOF by hand?
>>>
>>> 2011/7/25 David McBride 
>>>>
>>>> blah = do
>>>>  fp <- openFile "file" ReadMode
>>>>  run_ $ (ET.enumHandle fp $= ET.lines) $$ printChunks True
>>>>
>>>> printChunks is super duper simple:
>>>>
>>>> printChunks printEmpty = continue loop where
>>>>        loop (Chunks xs) = do
>>>>                let hide = null xs && not printEmpty
>>>>                CM.unless hide (liftIO (print xs))
>>>>                continue loop
>>>>
>>>>        loop EOF = do
>>>>                liftIO (putStrLn "EOF")
>>>>                yield () EOF
>>>>
>>>> Just replace print with whatever IO action you wanted to perform.
>>>>
>>>> On Mon, Jul 25, 2011 at 4:31 AM, Yves Parès  wrote:
>>>> > Sorry, I'm only beginning to understand iteratees, but then how do you
>>>> > access each line of text output by the enumeratee "lines" within an
>>>> > iteratee?
>>>> >
>>>> > 2011/7/24 Felipe Almeida Lessa 
>>>> >>
>>>&g

Re: [Haskell-cafe] file splitter with enumerator package

2011-07-25 Thread David McBride
Well I was going to say:

import Data.Text.IO as T
import Data.Enumerator.List as EL
import Data.Enumerator.Text as ET

run_ $ (ET.enumHandle fp $= ET.lines) $$ EL.mapM_ T.putStrLn

for example.  But it turns out this actually concatenates the lines
together and prints one single string at the end.  The reason is
because it turns out that ET.enumHandle already gets lines one by one
without you asking and it doesn't add newlines to the end, so ET.lines
looks at each chunk and never sees any newlines so it returns the
entire thing concatenated together figuring that was an entire line.
I'm kind of surprised that enumHandle fetches linewise rather than to
let you handle it.

But if you were to make your own enumHandle that wasn't linewise that
would work.

On Mon, Jul 25, 2011 at 6:26 AM, Yves Parès  wrote:
> Okay, so there, the chunks (xs) will be lines of Text, and not just random
> blocks.
> Isn't there a primitive like printChunks in the enumerator library, or are
> we forced to handle Chunks and EOF by hand?
>
> 2011/7/25 David McBride 
>>
>> blah = do
>>  fp <- openFile "file" ReadMode
>>  run_ $ (ET.enumHandle fp $= ET.lines) $$ printChunks True
>>
>> printChunks is super duper simple:
>>
>> printChunks printEmpty = continue loop where
>>        loop (Chunks xs) = do
>>                let hide = null xs && not printEmpty
>>                CM.unless hide (liftIO (print xs))
>>                continue loop
>>
>>        loop EOF = do
>>                liftIO (putStrLn "EOF")
>>                yield () EOF
>>
>> Just replace print with whatever IO action you wanted to perform.
>>
>> On Mon, Jul 25, 2011 at 4:31 AM, Yves Parès  wrote:
>> > Sorry, I'm only beginning to understand iteratees, but then how do you
>> > access each line of text output by the enumeratee "lines" within an
>> > iteratee?
>> >
>> > 2011/7/24 Felipe Almeida Lessa 
>> >>
>> >> On Sun, Jul 24, 2011 at 12:28 PM, Yves Parès 
>> >> wrote:
>> >> > If you used Data.Enumerator.Text, you would maybe benefit the "lines"
>> >> > function:
>> >> >
>> >> > lines :: Monad m => Enumeratee Text Text m b
>> >>
>> >> It gets arbitrary blocks of text and outputs lines of text.
>> >>
>> >> > But there is something I don't get with that signature:
>> >> > why isn't it:
>> >> > lines :: Monad m => Enumeratee Text [Text] m b
>> >> > ??
>> >>
>> >> Lists of lines of text?
>> >>
>> >> Cheers, =)
>> >>
>> >> --
>> >> Felipe.
>> >
>> >
>> > ___
>> > 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


Re: [Haskell-cafe] file splitter with enumerator package

2011-07-25 Thread David McBride
blah = do
  fp <- openFile "file" ReadMode
  run_ $ (ET.enumHandle fp $= ET.lines) $$ printChunks True

printChunks is super duper simple:

printChunks printEmpty = continue loop where
loop (Chunks xs) = do
let hide = null xs && not printEmpty
CM.unless hide (liftIO (print xs))
continue loop

loop EOF = do
liftIO (putStrLn "EOF")
yield () EOF

Just replace print with whatever IO action you wanted to perform.

On Mon, Jul 25, 2011 at 4:31 AM, Yves Parès  wrote:
> Sorry, I'm only beginning to understand iteratees, but then how do you
> access each line of text output by the enumeratee "lines" within an
> iteratee?
>
> 2011/7/24 Felipe Almeida Lessa 
>>
>> On Sun, Jul 24, 2011 at 12:28 PM, Yves Parès  wrote:
>> > If you used Data.Enumerator.Text, you would maybe benefit the "lines"
>> > function:
>> >
>> > lines :: Monad m => Enumeratee Text Text m b
>>
>> It gets arbitrary blocks of text and outputs lines of text.
>>
>> > But there is something I don't get with that signature:
>> > why isn't it:
>> > lines :: Monad m => Enumeratee Text [Text] m b
>> > ??
>>
>> Lists of lines of text?
>>
>> Cheers, =)
>>
>> --
>> Felipe.
>
>
> ___
> 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


Re: [Haskell-cafe] Vi mode in ghci?

2011-06-10 Thread David McBride
I do remember reading this page way back when.  Thank you very much!

On Fri, Jun 10, 2011 at 4:41 PM, Evan Laforge  wrote:
> On Fri, Jun 10, 2011 at 1:25 PM, David McBride  wrote:
>> Somehow in the distant past I managed to get vi editing mode working
>> for ghci on ghc 6, but when I upgraded to ghc 7, I can't seem to
>> figure out how to enable it anymore.  I think I might have been using
>> ghci-haskeline in the past.  A post I read somewhere suggested that
>> ghc 7 should have innate support for vi mode, but I can't figure out
>> if it does, or how to enable it.  Does anyone know?
>
> ~/.haskeline:
>
> editMode: Vi
>
> I recommend 'historyDuplicates: IgnoreConsecutive' for a nice zsh-like 
> history.
>

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


[Haskell-cafe] Vi mode in ghci?

2011-06-10 Thread David McBride
Somehow in the distant past I managed to get vi editing mode working
for ghci on ghc 6, but when I upgraded to ghc 7, I can't seem to
figure out how to enable it anymore.  I think I might have been using
ghci-haskeline in the past.  A post I read somewhere suggested that
ghc 7 should have innate support for vi mode, but I can't figure out
if it does, or how to enable it.  Does anyone know?

I'm willing to recompile ghc to use readline to get vi mode support if
that is possible and the only way to do so.

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


Re: [Haskell-cafe] Regex multiple matches

2010-07-20 Thread David McBride
Nevermind I see that you already knew that.  But it is very cool anyways,
I'm totally going to use regexes more often now that I've discovered it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Regex multiple matches

2010-07-20 Thread David McBride
It is even simpler than that.  The type determines the return value.

>"axxfayyf" =~ "a..f" :: Bool
True

>"axxfayyf" =~ "a..f" :: Int
2

>"axxfayyf" =~ "a..f" :: String
"axxf"

>"axxfayyf" =~ "a..f" :: [[String]]
[["axxf"],["ayyf"]]

>"axxfayyf" =~ "a..f" :: [MatchArray]
[array (0,0) [(0,(0,4))],array (0,0) [(0,(4,4))]]

>"axxfayyf" =~ "a..f" :: (MatchOffset, MatchLength)
(0,4)

Among other contexts specified in :i RegexContext

On Tue, Jul 20, 2010 at 11:55 AM, Omari Norman wrote:

> > How do I use Text.Regex.PCRE to get information on multiple matches? For
> > instance, in ghci I get this error message:
> >
> > Prelude Text.Regex.PCRE> "foo" =~ "o" :: [(Int,Int)]
>
> Solved; do
>
> getAllMatches ("foo" =~ "o") :: [(Int, Int)]
>
> ___
> 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] Advice for clean code.

2007-12-03 Thread David McBride
I am still in the early stages learning haskell, which is my first foray 
into functional programming.  Well there's no better way to learn than 
to write something, so I started writing a game.


Mostly the thing looks good so far, far better than the C version did.  
However, my problem is that code like the following is showing up more 
often and it is becoming unwieldy.


gameLoop :: World -> IO ()
gameLoop w = do
  drawScreen w

  action <- processInput

  let (result, w') = processAction action w

  case result of
MoveOutOfBounds -> putStrLn "Sorry you can't move in that direction."
MoveBadTerrain a -> case a of
  Wall -> putStrLn "You walk into a wall."
  Tree -> putStrLn "There is a tree in the way."
  otherwise -> putStrLn "You can't move there."
otherwise -> return ()

  let w'' = w' { window = updateWindowLocation (window w') (location $ 
player w')}


  unless (action == Quit) (gameLoop w'')

Where world contains the entire game's state and so I end up with w's 
with multiple apostrophes at the end.  But at the same time I can't 
really break these functions apart easily.  This is error prone and 
seems pointless.


I have been reading about control.monad.state and I have seen that I 
could run execstate over this and use modify but only if each function 
took a world and returned a world.  That seems really limiting.  I'm not 
even sure if this is what I should be looking at.


I am probably just stuck in an imperative mindset, but I have no idea 
what to try to get rid of the mess and it is only going to get worse 
over time.  Any suggestions on what I can do about it?

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