Re: [Haskell-cafe] Multi-line string literals are both easy /and/elegant in Haskell

2008-10-14 Thread Don Stewart
mjm2002:
> On 10/13/08, Andrew Coppin wrote:
> > Cool. Is there any progress on getting GHC to *not* freak out when you
> > ask it to compile a CAF containing several hundred KB of string literal? :-}
> 
> Yes and no. There's dons' compiled-constants pkg which has a solution:
> 
>   http://code.haskell.org/~dons/code/compiled-constants/
> 
> And the code below would do all the haskell-side work for importing
> the data from C, but I'm not aware of a way to have ghc not freak out
> if it has to compile a huge amount of static data.

Hiding  it inside an unboxed string constant?
i.e.

"this be bits"#

Or does GHC still freak?

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


Re: [Haskell-cafe] Multi-line string literals are both easy /and/elegant in Haskell

2008-10-14 Thread Matt Morrow
On 10/13/08, Andrew Coppin wrote:
> Cool. Is there any progress on getting GHC to *not* freak out when you
> ask it to compile a CAF containing several hundred KB of string literal? :-}

Yes and no. There's dons' compiled-constants pkg which has a solution:

  http://code.haskell.org/~dons/code/compiled-constants/

And the code below would do all the haskell-side work for importing
the data from C, but I'm not aware of a way to have ghc not freak out
if it has to compile a huge amount of static data.

---
{-# LANGUAGE TemplateHaskell #-}
module FromC (fromC) where
import GHC.Ptr(Ptr(Ptr))
import Foreign.C.Types(CChar)
import System.IO.Unsafe(unsafePerformIO)
import Data.ByteString.Unsafe(unsafePackAddressLen)
import Data.ByteString(ByteString)
import Language.Haskell.TH.Syntax
import Language.Haskell.TH.Lib

-- |
-- If in asdf.c == @unsigned char stuff[1024] = {42,.,19};@, then
--
-- > $(fromC "./asdf.c" "stuff" "dat")
---
-- will produce:
--
-- > foreign import ccall unsafe "&" stuff :: Ptr CChar
-- > dat :: ByteString
-- > dat = unsafePerformIO (case stuff of
-- >   Ptr addr_0 -> unsafePackAddressLen 1024 addr_0)
--
fromC :: FilePath -> String -> Int -> String -> Q [Dec]
fromC cfile cvar bytes hsvar = do
  let hsname = mkName hsvar
  t <- [t|ByteString|]
  e <- [|unsafePerformIO
  (case $(varE . mkName $ cvar) of
Ptr addr -> unsafePackAddressLen bytes addr)
  |]
  return [ ForeignD (ImportF CCall Unsafe "&" (mkName cvar)
(AppT (ConT ''Ptr) (ConT ''CChar)))
 , SigD hsname t , ValD (VarP hsname) (NormalB e) []]
---
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Multi-line string literals are both easy /and/elegant in Haskell

2008-10-13 Thread L.Guo
Oh, that's so cool.

But, this feather is too difficult to be configured in UE32 -- my costom IDE.

Pity. Hopes I wouldn't forget it later.

--   
L.Guo
2008-10-14

-
From: Matt Morrow
At: 2008-10-14 02:15:30
Subject: [Haskell-cafe] Multi-line string literals are both easy /and/elegant 
in Haskell

The new QuasiQuotes extension arriving with ghc 6.10 is very exciting,
and handling multi-line string literals is like stealing candy from
a baby. ;)

-
-- Here.hs
module Here (here) where

import Language.Haskell.TH.Quote
import Language.Haskell.TH.Syntax
import Language.Haskell.TH.Lib

here :: QuasiQuoter
here = QuasiQuoter (litE . stringL) (litP . stringL)
-

-
-- There.hs
{-# LANGUAGE QuasiQuotes #-}
module Main where
import Here (here)
main = putStr [$here|

Shall I say, I have gone at dusk through narrow streets
And watched the smoke that rises from the pipes
Of lonely men in shirt-sleeves, leaning out of windows?

I should have been a pair of ragged claws
Scuttling across the floors of silent seas.


|]
-

-
[EMAIL PROTECTED] a]$ ghc -O2 --make There.hs
[1 of 2] Compiling Here ( Here.hs, Here.o )
[2 of 2] Compiling Main ( There.hs, There.o )
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
Loading package syb ... linking ... done.
Loading package array-0.2.0.0 ... linking ... done.
Loading package packedstring-0.1.0.1 ... linking ... done.
Loading package containers-0.2.0.0 ... linking ... done.
Loading package pretty-1.0.1.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
Linking There ...
[EMAIL PROTECTED] a]$ ./There


Shall I say, I have gone at dusk through narrow streets
And watched the smoke that rises from the pipes
Of lonely men in shirt-sleeves, leaning out of windows?

I should have been a pair of ragged claws
Scuttling across the floors of silent seas.


[EMAIL PROTECTED] a]$
-
___
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] Multi-line string literals are both easy /and/ elegant in Haskell

2008-10-13 Thread Andrew Coppin

Matt Morrow wrote:

The new QuasiQuotes extension arriving with ghc 6.10 is very exciting,
and handling multi-line string literals is like stealing candy from
a baby. ;)
  


Cool. Is there any progress on getting GHC to *not* freak out when you 
ask it to compile a CAF containing several hundred KB of string literal? :-}


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


[Haskell-cafe] Multi-line string literals are both easy /and/ elegant in Haskell

2008-10-13 Thread Matt Morrow
The new QuasiQuotes extension arriving with ghc 6.10 is very exciting,
and handling multi-line string literals is like stealing candy from
a baby. ;)

-
-- Here.hs
module Here (here) where

import Language.Haskell.TH.Quote
import Language.Haskell.TH.Syntax
import Language.Haskell.TH.Lib

here :: QuasiQuoter
here = QuasiQuoter (litE . stringL) (litP . stringL)
-

-
-- There.hs
{-# LANGUAGE QuasiQuotes #-}
module Main where
import Here (here)
main = putStr [$here|

Shall I say, I have gone at dusk through narrow streets
And watched the smoke that rises from the pipes
Of lonely men in shirt-sleeves, leaning out of windows?

I should have been a pair of ragged claws
Scuttling across the floors of silent seas.


|]
-

-
[EMAIL PROTECTED] a]$ ghc -O2 --make There.hs
[1 of 2] Compiling Here ( Here.hs, Here.o )
[2 of 2] Compiling Main ( There.hs, There.o )
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
Loading package syb ... linking ... done.
Loading package array-0.2.0.0 ... linking ... done.
Loading package packedstring-0.1.0.1 ... linking ... done.
Loading package containers-0.2.0.0 ... linking ... done.
Loading package pretty-1.0.1.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
Linking There ...
[EMAIL PROTECTED] a]$ ./There


Shall I say, I have gone at dusk through narrow streets
And watched the smoke that rises from the pipes
Of lonely men in shirt-sleeves, leaning out of windows?

I should have been a pair of ragged claws
Scuttling across the floors of silent seas.


[EMAIL PROTECTED] a]$
-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Multi Line String literals

2007-04-27 Thread Bas van Dijk

On 4/26/07, Joe Thornber <[EMAIL PROTECTED]> wrote:

but it's simpler to just write something like:

test  = putStr $ unlines ["I",
   "need",
   "multiline",
   "string",
   "literals"]



Yes I know. My aim was just to see if I could do it with as less
syntax as possible and then the 'do' syntax is handy.

Another question:

If I change:


type MLS = Writer (Endo [B.ByteString]) ()

instance IsString MLS where
   fromString s = tell $ Endo (fromString s:)

instance ToString MLS where
   toString w = toString $ B.unlines $ (appEndo $ execWriter w)  []


to the simpler:


type MLS2 = Writer [B.ByteString] ()

instance IsString MLS2 where
   fromString s = tell [fromString s]

instance ToString MLS2 where
   toString = toString . B.unlines . execWriter


then MLS2 is a bit faster (about 0.4 sec. when applied to a million
strings). I thought the former MLS should be faster because it doesn't
have to mappend every [fromString s]. MLS just 'builds' a large
function: "(fromString s:) . (fromString s:) . (fromString s:) ... id
[]"

Can anybody explain why MLS2 is faster?

Thanks,

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


Re: [Haskell-cafe] Multi Line String literals

2007-04-26 Thread Matthew Sackman
Alex Queiroz <[EMAIL PROTECTED]> wrote:
> On 4/26/07, Neil Mitchell <[EMAIL PROTECTED]> wrote:
> > Like the cpp will choke and die :) Multiline string literals were one
> > of the motivations for cpphs.
> 
>  Does cpphs allow me to include a whole file into a Haskell source
> file, inserting automatically the string gaps?

My hinstaller library certainly does. Though it currently allows you to
only output that file to another file. I could easily improve it to
allow output to a Handle.
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/hinstaller

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


Re: [Haskell-cafe] Multi Line String literals

2007-04-26 Thread Alex Queiroz

Hallo,

On 4/26/07, Neil Mitchell <[EMAIL PROTECTED]> wrote:


No, but Hugs does with "Here documents".



Unfortunately I'm using GHC but thanks!

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


Re: [Haskell-cafe] Multi Line String literals

2007-04-26 Thread Neil Mitchell

Hi


 Does cpphs allow me to include a whole file into a Haskell source
file, inserting automatically the string gaps?


No, but Hugs does with "Here documents".

Thanks

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


Re: [Haskell-cafe] Multi Line String literals

2007-04-26 Thread Alex Queiroz

Hallo,

On 4/26/07, Neil Mitchell <[EMAIL PROTECTED]> wrote:


Like the cpp will choke and die :) Multiline string literals were one
of the motivations for cpphs.



Does cpphs allow me to include a whole file into a Haskell source
file, inserting automatically the string gaps?

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


Re: [Haskell-cafe] Multi Line String literals

2007-04-26 Thread Neil Mitchell

Hi


How does

test  = putStr "I\n\
   \need\n\
   \multiline\n\
   \string\n\
   \literals\n"

look?


Like the cpp will choke and die :) Multiline string literals were one
of the motivations for cpphs.

Thanks

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


Re: [Haskell-cafe] Multi Line String literals

2007-04-26 Thread Stefan O'Rear
On Thu, Apr 26, 2007 at 01:43:09PM +0100, Joe Thornber wrote:
> On 26/04/07, Bas van Dijk <[EMAIL PROTECTED]> wrote:
> >test = putStrLn $ toIsString $ do "I"
> >   "need"
> >   "MultiLine"
> >   "String"
> >   "literals!"
> 
> but it's simpler to just write something like:
> 
> test  = putStr $ unlines ["I",
>   "need",
>   "multiline",
>   "string",
>   "literals"]

How does

test  = putStr "I\n\
   \need\n\
   \multiline\n\
   \string\n\
   \literals\n"

look?

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


Re: [Haskell-cafe] Multi Line String literals

2007-04-26 Thread Joe Thornber

On 26/04/07, Bas van Dijk <[EMAIL PROTECTED]> wrote:

test = putStrLn $ toIsString $ do "I"
   "need"
   "MultiLine"
   "String"
   "literals!"


but it's simpler to just write something like:

test  = putStr $ unlines ["I",
  "need",
  "multiline",
  "string",
  "literals"]

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


[Haskell-cafe] Multi Line String literals

2007-04-26 Thread Bas van Dijk

Hello,

Just for fun I'm trying to define multi line string literals. I have
the following code and I'm wondering if it can be improved
(understandability, elegance, performance): http://hpaste.org/1582
(look at the second annotation)

regards,

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