Building the GHC library without building GHC

2013-02-15 Thread C Rodrigues

Hi,

I was going to do some hacking on Haddock.  Haddock depends on the GHC API from 
the development version of GHC, however, stage2 crashes on my system when I try 
to build the newest GHC from the repository.  Since I don't actually need to 
compile with the new GHC, I'm hoping there's a workaround.  Is there a way to 
build only the GHC library so that I can get back to Haddock?


  
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Global constant propagation

2013-01-20 Thread C Rodrigues

I'm curious about global constant propagation in GHC.  It's a fairly basic 
optimization in the CFG-based compiler domain, and it's similar to constructor 
specialization, but it doesn't seem to be in GHC's repertoire.  Perhaps it's 
usually subsumed by other optimizations or it's more complicated than I am 
thinking.  Is this optimization worth implementing?

This optimization can help when a case expression returns a product, some 
fields of which are the same in all branches.  The following program is a 
minimal example of an optimizable situation that GHC doesn't exploit.


{-# OPTIONS_GHC -O3 -funbox-strict-fields #-}


data D = D !Int !Int


foo n = if n  0

        then D 0 0

        else D 0 n


main =

  case foo $ read 7

  of D x y - if x == 0 then return () else print y  putStrLn A


After inlining and case-of-case transformation, GHC produces


main = let n = read 7

           k x y = case x of {0 - return (); _ - print y  putStrLn A}

       in if n  0

          then k 0 0

          else k 0 n


If the simplifier could discover that x is always 0, it could eliminate one 
parameter of 'k' and the case expression.

  
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Elimination of absurd patterns

2011-05-03 Thread C Rodrigues

I tried it again using a development version of GHC 7.1 that I downloaded in 
March.
The results are the same, with GHC generating different code for the supposedly
equivalent data types. 'barName' has an impossible pattern match against
constructor 'BarExtra', whereas 'fooName' does not.



 Date: Mon, 2 May 2011 23:03:23 -0300
 Subject: Re: Elimination of absurd patterns
 From: felipe.le...@gmail.com
 To: red...@hotmail.com
 CC: glasgow-haskell-users@haskell.org

 On Mon, May 2, 2011 at 6:20 PM, C Rodrigues  wrote:
  I was experimenting with using GADTs for subtyping when I found something
  interesting.  Hopefully someone can satisfy my curiosity.
  Here are two equivalent GADTs.  My understanding was that GHC would
  translate Foo and Bar into isomorphic data types.  However, GHC 6.12.3
  generates better code for 'fooName' than for 'barName'.  In 'fooName', there
  is no pattern match against 'FooExtra'.  In 'barName', there is a pattern
  match against 'BarExtra'.  What makes these data types different?

 IIRC, GHC 6.12.3 had some problems with type equalities. Did you try GHC 
 7.0.3?

 Cheers, =)

 --
 Felipe.
  
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Elimination of absurd patterns

2011-05-02 Thread C Rodrigues

I was experimenting with using GADTs for subtyping when I found something 
interesting.  Hopefully someone can satisfy my curiosity.
Here are two equivalent GADTs.  My understanding was that GHC would translate 
Foo and Bar into isomorphic data types.  However, GHC 6.12.3 generates 
better code for 'fooName' than for 'barName'.  In 'fooName', there is no 
pattern match against 'FooExtra'.  In 'barName', there is a pattern match 
against 'BarExtra'.  What makes these data types different?

data Tagdata TagExtra

data Foo a where  Foo :: String - Foo a  FooExtra :: IORef String - Foo 
TagExtra
-- The cmm code for fooName does not match against 'FooExtra'fooName :: Foo Tag 
- StringfooName (Foo s) = s

data Bar a where  Bar :: String - Bar a  BarExtra :: a ~ TagExtra = IORef 
String - Bar a
-- The cmm code for barName will try to pattern-match against 'BarExtra'barName 
:: Bar Tag - StringbarName (Bar s) = s
  ___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Elimination of absurd patterns (reformatted)

2011-05-02 Thread C Rodrigues

I'm re-sending this e-mail, hopefully with proper line breaks this time.

I was experimenting with using GADTs for subtyping when I found something 
interesting.  Hopefully someone can satisfy my curiosity.

Here are two equivalent GADTs.  My understanding was that GHC would translate 
Foo and Bar into isomorphic data types.
However, GHC 6.12.3 generates better code for 'fooName' than for 'barName'.  In 
'fooName', there is no pattern match against 'FooExtra'.
In 'barName', there is a pattern match against 'BarExtra'.  What makes these 
data types different?


data Tag
data TagExtra



data Foo a where
  Foo :: String - Foo a
  FooExtra :: IORef String - Foo TagExtra

-- The cmm code for fooName does not match against 'FooExtra'
fooName :: Foo Tag - String
fooName (Foo s) = s



data Bar a where
  Bar :: String - Bar a
  BarExtra :: a ~ TagExtra = IORef String - Bar a

-- The cmm code for barName will try to pattern-match against 'BarExtra'
barName :: Bar Tag - String
barName (Bar s) = s
  
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Meaning of ghc-pkg package-conf flags

2011-04-14 Thread C Rodrigues

Hello,

I'd like to know how ghc-pkg searches package databases and how the 
command-line flags affect the search.

My model of ghc-pkg was that it builds a list of package databases and then 
searches them starting from the head.  I'd like to work with a sandboxed local 
package database.  Looking at what ghc-pkg list prints, I can infer what 
database list it's using:

ghc-pkg list: [user-db, global-db]

ghc-pkg list --global: [global-db]

ghc-pkg list --global --package-conf=$HOME/sandbox/package.conf.d: [sandbox-db, 
global-db]

However, even though ghc-pkg doesn't show my user database, it still reports 
broken packages that are in my user database.  So ghc-pkg isn't really scanning 
packages according to this database list.  What is it doing?
  ___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Equality constraint type mismatch

2010-03-08 Thread C Rodrigues

(Hotmail is again swallowing newlines--sorry for the re-post)

I see.  The type inference algorithm requires type variables to be
type constructors, not functions.  Equality constraints are
simplified assuming that is the case.  I knew that type
functions had to be fully applied, but I didn't know that they also
couldn't be taken apart by unification.  This explains why the
following doesn't typecheck:


type family T a :: *
my_id :: f a - f a; my_id = id
x :: T a - T a; x = my_id


IMHO, this was not clear from the documentation or from the error
message (It certainly _looks_ like T a should match f a...).
Thanks for the explanation.

-heatsink 
_
Hotmail: Trusted email with powerful SPAM protection.
http://clk.atdmt.com/GBL/go/201469227/direct/01/___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Type checker's expected and inferred types

2009-10-23 Thread C Rodrigues


I came across a type error that misled me for quite a while, because the 
expected and inferred types were backwards (from my point of view).  A 
simplified example is below.  Can someone explain how GHC's type checker 
creates the error message?
In this example, fun1 and fun2 are basically the same.  The type error is 
because they try to run an IO () together with a Maybe ().
 import Control.Monad foo :: Maybe () foo = return () bar :: IO () bar = 
 return () fun1 = let fooThen m = foo  min fooThen (bar  
 undefined) fun2 = let fooThen m = foo  min fooThen (do {bar; 
 undefined})
With ghc 6.10.4, both functions attribute the error message to `bar'. However, 
the expected and inferred monads are swapped.fun1 produces the error 
message:Couldn't match expected type `Maybe a' against inferred type `IO ()'In 
the first argument of `(=)', namely `bar'fun2 produces the error 
message:Couldn't match expected type `IO ()' against inferred type `Maybe ()'In 
a stmt of a 'do' expression: bar
It's confusing because 'bar' is inferred to have type Maybe (), even though 
it's explicitly declared to be an IO ().  
_
New Windows 7: Find the right PC for you. Learn more.
http://www.microsoft.com/windows/pc-scout/default.aspx?CBID=wlocid=PID24727::T:WLMTAGL:ON:WL:en-US:WWL_WIN_pcscout:102009___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Type checker's expected and inferred types (reformatted)

2009-10-23 Thread C Rodrigues

(Some formatting was apparently lost en route.  Trying again with extra 
newlines.)
I came across a type error that misled me for quite a while, because the 
expected and inferred types were backwards (from my point of view).  A 
simplified example is below.  Can someone explain how GHC's type checker 
creates the error message?

In this example, fun1 and fun2 are basically the same.  The type error is 
because they try to run an IO () together with a Maybe ().

 import Control.Monad

 foo :: Maybe ()
 foo = return ()

 bar :: IO ()
 bar = return ()

 fun1 = let fooThen m = foo m
        in fooThen (bar undefined)

 fun2 = let fooThen m = foo m
        in fooThen (do {bar; undefined})


With ghc 6.10.4, both functions attribute the error message to `bar'. However, 
the expected and inferred monads are swapped.


fun1 produces the error message:
Couldn't match expected type `Maybe a' against inferred type `IO ()'
In the first argument of `(=)', namely `bar'


fun2 produces the error message:
Couldn't match expected type `IO ()' against inferred type `Maybe ()'
In a stmt of a 'do' expression: bar


It's confusing because 'bar' is inferred to have type Maybe (), even though 
it's explicitly declared to be an IO ().
  
_
Windows 7: Simplify your PC. Learn more.
http://www.microsoft.com/Windows/windows-7/default.aspx?ocid=PID24727::T:WLMTAGL:ON:WL:en-US:WWL_WIN_evergreen1:102009___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Type checker's expected and inferred types (reformatted)

2009-10-23 Thread C Rodrigues

 Which message do you prefer? I couldn't tell which it was.

I prefer fun1.  In my understanding, the 'inferred' type is gleaned by looking 
at theexpression itself, while the 'expected' type is implied by the context.   
   
_
Windows 7: It works the way you want. Learn more.
http://www.microsoft.com/Windows/windows-7/default.aspx?ocid=PID24727::T:WLMTAGL:ON:WL:en-US:WWL_WIN_evergreen2:102009___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Ghci dynamic linking (Was: C++ libraries and GHCI)

2009-10-08 Thread C Rodrigues

I've encountered the problem with weak symbols also, and filed a bug report 
against ghc (#).
Weak symbols are used by gcc (with elf) to accommodate C++'s compilation model. 
 In C++, it's permitted to define class methods and template code in header 
files.  Because header files can be included in many source files, the same 
object code will appear in many object files.  It's the linker's job to merge 
these definitions.  There's no standard way of handling C++ linking, 
unfortunately, so handling weak symbols won't necessarily solve the problem for 
every compiler.
If there will be no cross-references involving weak symbols between different 
.a files, such as when you have a C++ library that doesn't depend on other C++ 
libraries, then it should be sufficient to treat a weak defined symbol as 
'defined' and a weak undefined symbol as NULL.  However, I don't know if this 
is really a common case; most C++ code depends on libstdc++, in which case 
there may be multiple weak symbol definitions.
--heatsink
 
 Thanks for the reply, Max.
 
 If it's not something overly complex, I'll try to hack ghc
 to see if I can produce a working patch...
 
 probably that symbol type can be safely ignored by
 ghci linker.
 
 Thanks again for your help
 Paolo
 
 
 On Wed, Sep 30, 2009 at 2:29 PM, Max Bolingbroke
 batterseapo...@hotmail.com wrote:
  (Moving to ghc-users)
 
  I'd never seen V in nm output before:
 
  
  The symbol is a weak object.  When a weak defined symbol is linked
  with a normal defined symbol, the normal defined symbol is used with
  no error.  When a weak undefined symbol is linked and the symbol is
  not defined, the value of the  weak symbol becomes zero with no error.
   On some systems, uppercase indicates that a default value has been
  specified.
  
 
  
_
Hotmail: Trusted email with powerful SPAM protection.
http://clk.atdmt.com/GBL/go/177141665/direct/01/___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Type classes in GADTs

2008-10-30 Thread C Rodrigues

Thanks for the explanation.  I see how this wouldn't behave nicely with 
automatic class constraint inference.  I didn't test the example on any other 
GHC versions.

I will probably end up passing in the Eq dictionary from outside like Daniil 
suggested.  I would prefer to do the following, but GHC doesn't accept the type 
signature.

evidenceOfEq :: CAOp a - (Eq a = b) - b

Neither does it accept data EqConstraint a b = EqConstraint (Eq a = b).  
Foiled again.
_
Want to read Hotmail messages in Outlook? The Wordsmiths show you how.
http://windowslive.com/connect/post/wedowindowslive.spaces.live.com-Blog-cns!20EE04FBC541789!167.entry?ocid=TXT_TAGLM_WL_hotmail_092008___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Type classes in GADTs

2008-10-29 Thread C Rodrigues

I discovered that closed type classes can be implicitly defined using GADTs.  
The GADT value itself acts like a class dictionary.  However, GHC (6.8.3) 
doesn't know anything about these type classes, and it won't infer any class 
memberships.  In the example below, an instance of Eq is not recognized.

So is this within the domain of GHC's type inference, not something it shoud 
infer, or a bug?

{-# OPTIONS_GHC -XTypeFamilies -XGADTs -XEmptyDataDecls #-}
module CaseAnalysisOnGADTs where

-- Commutative and associative operators.
data CAOp a where
Sum:: CAOp Int
Disj   :: CAOp Bool
Concat :: CAOp String

{- For any non-bottom value of type 'CAOp a', the value will have type
-- CAOp Int, CAOp Bool, or CAOp String.  Int, Bool, and String are all
-- members of Eq.  Therefore, if we have a non-bottom value of type
-- 'CAOp a' then 'a' is a member of Eq.
-}

data D a = D !(CAOp a) (a, a)

-- However, GHC won't figure this out.

noEvidenceOfEq :: D a - Bool
noEvidenceOfEq (D op (e1, e2)) = e1 == e2 -- Error, no instance (Eq a)

-- Unless you force it to do case analysis on constructors.

evidenceOfEq :: CAOp a - a - a - Bool
evidenceOfEq Sum= (==)
evidenceOfEq Disj   = (==)
evidenceOfEq Concat = (==)

-- Then you can use the result from that, but GHC still won't
-- recognize it as an Eq instance.

useEvidenceOfEq :: D a - Bool
useEvidenceOfEq (D op (e1, e2)) = evidenceOfEq op e1 e2
_
You live life beyond your PC. So now Windows goes beyond your PC.
http://clk.atdmt.com/MRT/go/115298556/direct/01/___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: SHA1.hs woes, was Version control systems

2008-08-22 Thread C Rodrigues

I've fixed this problem by increasing the number of registers used on ia64 to 
34.  The problem will show up again if anyone finds a way to make GCC use even 
more registers.

-heatsink

 
 Sorry, I couldn't find the rest of the preceding message. Someone  
 wrote that they had to turn down cc flags to get SHA1.hs to compile on  
 IA64.
 
 Yep.
 
 What C compiler was being used, and what were the symptoms?
 
 GCC.
 
 As I recall the symptoms were that gcc used more than 32 registers and
 then the mangler balked. The reason is that a registerised ia64 build
 expects to only use the first 32 registers but does not take any
 precautions to make sure that this is the case. It just relies on the
 fact that most code coming out of the ghc backend cannot make use of
 more than a handful of registers. If gcc does actually use more then the
 mangler catches this. We tried some flags to make gcc restrict itself to
 a subset of the registers but could not get it to obey.
 
 Duncan
_
Talk to your Yahoo! Friends via Windows Live Messenger.  Find out how.
http://www.windowslive.com/explore/messenger?ocid=TXT_TAGLM_WL_messenger_yahoo_082008___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


[Haskell-cafe] Hiding side effects in a data structure

2007-10-19 Thread C Rodrigues

While thinking about how to generate unique integer IDs on demand without using 
a state variable, I came up with an interesting design pattern.  It's a way of 
doing side-effecting computation outside IO.  Referential transparency is 
preserved by making the side effects spatial rather than temporal: by hiding 
side effects behind lazy thunks in a data structure, they can be disguised as 
the output of a single, apparently nondeterministic IO function used to data 
structure.  This lets pure code use nondeterministic computation without the 
monadic plumbing required to maintain state.

The getContents function works this way, but I came up with a more interesting 
example.  The code below is a source of unique integer IDs that is modeled 
after the RandomGen class.  It uses unsafeInterleaveIO under the hood, 
preserving referential transparency but not determinism.

It seems to work.  However, I'm not entirely sure how safe my use of 
unsafeInterleaveIO is.  In particular, could the two branches of the tree get 
CSE'd?  I'm also curious what people think about the general design pattern.

module Unique where

import Control.Monad(liftM)
import Data.IORef
import System.IO.Unsafe

-- The goal is to produce an infinite tree of integers where each node in the
-- tree has a unique value.
type Unique = Int
data Supply = Supply Unique Supply Supply

-- The tree can be used in a stateful manner as a source of unique integers.
getUnique :: Supply - (Unique, Supply)
getUnique (Supply u s1 _) = (u, s1)

-- The tree can also be split into independent sources of unique integers.
split :: Supply - (Supply, Supply)
split (Supply _ s1 s2) = (s1, s2)

-- The catch is, the tree will probably be visited very sparsely, with most of
-- it being skipped.  Assigning every node its own integer is very bad, because
-- that will waste most of the 2^32 available integers very quickly.  In fact,
-- it can get used up in just 32 calls to getUnique.
--
-- Instead, we'll create a tree where integers magically appear only in places
-- where they are actually used.

-- First, we need an IO-bound supply of integers.
newtype IOSupply = IOSupply (IORef Unique)

newIOSupply :: IO IOSupply
newIOSupply = liftM IOSupply $ newIORef 0

getUniqueIO :: IOSupply - IO Unique
getUniqueIO (IOSupply s) = do
u - readIORef s
writeIORef s $ u+1
return u

-- Now we'll use the IO-bound supply to create a tree having the desired
-- properties.
{-# NOINLINE getPureSupply #-}
getPureSupply :: IOSupply - IO Supply
getPureSupply s = do
s1 - unsafeInterleaveIO $ getPureSupply s
s2 - unsafeInterleaveIO $ getPureSupply s
n  - unsafeInterleaveIO $ getUniqueIO s
return $ Supply n s1 s2

_
Climb to the top of the charts!  Play Star Shuffle:  the word scramble 
challenge with star power.
http://club.live.com/star_shuffle.aspx?icid=starshuffle_wlmailtextlink_oct___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: Login problems with trac

2007-04-03 Thread C Rodrigues
The wiki has edit links if I login as guest, but not if I login as 
heatsink.  Is that also because of the spam issue?


_
Get a FREE Web site, company branded e-mail and more from Microsoft Office 
Live! http://clk.atdmt.com/MRT/go/mcrssaub0050001411mrt/direct/01/


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


[Haskell-cafe] Type synonym application

2007-03-18 Thread C Rodrigues
Type synonyms aren't applied as I would expect during kind checking.  What's 
going on here?


type WithList a b = b [a]
type FooPair a b = (b, a - b)

-- error: `WithList' is applied to too many type arguments
ints1 :: WithList Int FooPair [Int]
ints1 = ([1], id)

-- error: `FooPair' is not applied to enough type arguments
ints2 :: (WithList Int FooPair) [Int]
ints2 = ([1], id)

-- after manually applying the first type synonym
ints3 :: FooPair [Int] [Int]
ints3 = ([1], id)

_
Live Search Maps – find all the local information you need, right when you 
need it. http://maps.live.com/?icid=hmtag2FORM=MGAC01


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


[Haskell-cafe] RE: MPTCs and rigid variables

2007-03-03 Thread C Rodrigues

{-# OPTIONS_GHC -fglasgow-exts #-}

class Foo a b | a - b where
  foo :: Foo b c = a - Maybe c

instance Foo String () where foo _ = Nothing
instance Foo Int String where foo 4 = Just (); foo _ = Nothing



There appears to be a type-safe way to use unsafeCoerce# for this:


import qualified GHC.Exts

class Foo a b | a - b where foo :: a - FooBox b
data FooBox b = forall c. Foo b c = FooBox (Maybe c)

instance Foo () ()
instance Foo String () where foo _ = FooBox Nothing
instance Foo Int String where foo 4 = FooBox $ Just (); foo _ = FooBox 
Nothing


runFoo :: (Foo a b, Foo b c) = a - Maybe c
runFoo x = case foo x of FooBox x - GHC.Exts.unsafeCoerce# x


The class constraint check of a,b,c gets moved to the runFoo method instead 
of the instance declarations.  Between the body of foo and the call to foo 
in runFoo, type 'c' is unknown to the compiler, so we have to encapsulate it 
in a FooBox.  The unsafeCoerce# is safe because the type constraint (Foo b 
c) that we've placed both on FooBox and on runFoo permits c to have only the 
type uniquely specified by b.


We actually could remove the Foo constraint on FooBox, which makes the code 
no longer typesafe but it will still work just fine.


_
Don’t miss your chance to WIN 10 hours of private jet travel from Microsoft® 
Office Live http://clk.atdmt.com/MRT/go/mcrssaub0540002499mrt/direct/01/


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


[Haskell-cafe] Space leaks in large mutable data structures

2007-02-05 Thread C Rodrigues
I'd like to hear what tips and techniques you guys have for avoiding space 
leaks.  I understand the basic techniques to force evaluation of closures.  
What I'd like to know is how you avoid space leaks in large, long-lived, 
mutable data structures.  These kind of data are particularly sensitive to 
laziness in my experience.  (I'm using functional data structures and doing 
a lot of update operations.)  If you use monads to enforce strictness, how 
do you maintain composability throughout the program?


_
Invite your Hotmail contacts to join your friends list with Windows Live 
Spaces 
http://clk.atdmt.com/MSN/go/msnnkwsp007001msn/direct/01/?href=http://spaces.live.com/spacesapi.aspx?wx_action=createwx_url=/friends.aspxmkt=en-us


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


[Haskell-cafe] (no subject)

2007-02-04 Thread C Rodrigues



_
FREE online classifieds from Windows Live Expo – buy and sell with people 
you know 
http://clk.atdmt.com/MSN/go/msnnkwex001001msn/direct/01/?href=http://expo.live.com?s_cid=Hotmail_tagline_12/06


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


[Haskell-cafe] Laziness through boxing

2007-01-16 Thread C Rodrigues
I had a problem with strictness in the Parsec library, and I'd like to know 
if there's a good way to solve it.  The following illustrates the problem.  
This raises an error when run:


main = parseTest (return undefined  return 0) 

Whereas this does not:

main = parseTest (return (Just undefined)  return 0) 

I have a parser that does parsing and name resolution at the same time, by 
passing the completed symbol table in as a part of the parser state.  
Lookups into the completed symbol table have to be lazy since that symbol 
table is not ready until parsing is complete.  My parser kept producing 
loop when it ran, which turned out to be an effect of strictness in 
Parsec.


My solution was to box all the lazy values with Just.  The result feels 
awkward to me.  It involves fromJust, and moreover, it's easy to miss a 
place where boxing is required, and hard to track down the cause of a 
loop.  Is there a better way to deal with this issue?  And why is Parsec 
strict in return values?


-Chris

_
From photos to predictions, The MSN Entertainment Guide to Golden Globes has 

it all. http://tv.msn.com/tv/globes2007/?icid=nctagline1

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


[Haskell-cafe] IA64 porting: spill code in the mangler

2006-08-09 Thread C Rodrigues

Hi folks,

I've been trying to compile a new ia64 port.  I've cross-compiled an 
unregisterised compiler that generated working binaries the first time it 
was built, which was a pleasant experience.  But I ran into issues with the 
registerised build.  The mangler is choking on floating-point spill code:


Prologue junk?: .global __divdf3#
   .global GHCziFloat_zdwlogBase_entry#
   .proc GHCziFloat_zdwlogBase_entry#
GHCziFloat_zdwlogBase_entry:
   mov r16 = r12
   .save.f 0x1
   stf.spill [r16] = f2
   .body

This saves floating-point register 2 on the stack; it's loaded again later.  
I could change the mangler to remove this code, if that's the right 
approach.  What should the mangler do about it?



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


[Haskell-cafe] Template haskell and scoping

2006-06-21 Thread C Rodrigues
The (..) in the splice is out of scope according to GHC.  If I use [||] 
then it works, but for my purposes it's easier to use the constructors.  How 
should I refer to that variable?


import Data.Bits
import Language.Haskell.TH

main = print $ $(return $ VarE $ mkName ..) 7 (14 :: Int)


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


[Haskell-cafe] Computing lazy and strict list operations at the same time

2006-06-19 Thread C Rodrigues
Here's a puzzle I haven't been able to solve.  Is it possible to write the 
initlast function?


There are functions init and last that take constant stack space and 
traverse the list at most once.  You can think of traversing the list as 
deconstructing all the (:) [] constructors in list.


init (x:xs) = init' x xs
 where init' x (y:ys) = x:init' y ys
   init' _ [] = []

last (x:xs) = last' x xs
 where last' _ (y:ys) = last' y ys
   last' x [] = x

Now, is there a way to write initlast :: [a] - ([a], a) that returns the 
result of init and the result of last, takes constant stack space, and 
traverses the list only once?  Calling reverse traverses the list again.  I 
couldn't think of a way to do it, but I couldn't figure out why it would be 
impossible.



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


Re: [Haskell-cafe] Computing lazy and strict list operations atthe same time

2006-06-19 Thread C Rodrigues
Ah, thanks for the replies.  I like the approach that uses lazy tuples of 
intermediate values because it has a recognizable similarity to the original 
two functions.



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


[Haskell-cafe] Rank 2 polymorphism in pattern matching?

2006-04-08 Thread C Rodrigues
This counterintuitive typechecking result came up when I wrote a wrapper 
around runST.  Is there some limitation of HM with respect to type checking 
pattern matching?


data X a b = X (a - a)
run :: forall a. (forall b. X a b) - a - a
-- This definition doesn't pass the typechecker
run (X f) = f
-- But this definition works
run x = (\(X f) - f) x


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